Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Re: learning to use Haskell types (Heinrich Apfelmus)
   2.  Start file with associated prog (windows only?)
      (Bernhard Lehnert)
   3. Re:  Start file with associated prog (windows     only?)
      (Magnus Therning)
   4. Re:  Start file with associated prog (windows     only?)
      (Bernhard Lehnert)
   5. Re:  Start file with associated prog (windows     only?)
      (Isaac Dupree)
   6. Re:  Start file with associated prog (windows     only?)
      (Magnus Therning)
   7.  Re: learning to use Haskell types (Heinrich Apfelmus)
   8.  my ugly code and the Maybe monad (Simon Parry)
   9. Re:  my ugly code and the Maybe monad (Jan Jakubuv)


----------------------------------------------------------------------

Message: 1
Date: Mon, 17 Aug 2009 08:18:47 +0200
From: Heinrich Apfelmus <apfel...@quantentunnel.de>
Subject: [Haskell-beginners] Re: learning to use Haskell types
To: beginners@haskell.org
Message-ID: <h6aso8$6t...@ger.gmane.org>
Content-Type: text/plain; charset=ISO-8859-1

Michael Mossey wrote:
> This is really a general question, but any advice is welcome.
> 
> I'm currently working through Typeclassopedia and all the tutorials it
> links to. I'm really enjoying it, but a kind of scary question is: when
> I begin to write "real" software in Haskell, how will I find natural
> places to use the types and how will I make the transition to idiomatic
> Haskell?
> 
> [...]
> 
> Then it occurred to me that a common theme in Haskell is to provide a
> way to express a solution to a problem in an expressive form that is
> natural to that problem. So maybe what I need to do is stop thinking,
> "Where can I use this type," and instead dream up ways to express ideas
> in a simple and natural form, then make use of Haskell types and type
> classes to make that expressive form a reality.

Yes, that's the best approach. The hard part is finding a formulation
that is natural to the problem; and by definition it's hard to give
general advice there. I know of no other way than learning from
examples, like this one

    Simon Peyton Jones, Jean-Marc Eber, Julian Seward.
    "Composing contracts: an adventure in financial engineering"
    http://research.microsoft.decenturl.com/composing-contracts

What the Typeclassopedia can help with is to provide a few known
concepts where it's always worth checking whether they apply naturally.
I'd recommend the following order

    Monoid
    |
    |
    Applicative
    Monad
    |
    Arrow

In particular, Monoids are very common. The others usually only apply
when the problem domain involves polymorphism, i.e. when the object of
discourse is a type constructor.


That being said, the many concrete applicative functors and monads like
state monads, the list monad, zip lists, parser combinators,
probabilistic monads etc. are very useful implementation techniques. But
they are limited to "small scale" simplifications, they generally do
*not* help with finding a formulation that is natural to the whole
problem domain. (Except when it's very obvious, i.e. when the problem
*is* to model a state machine, to parse something, to sample a
probability distribution, etc.)


> For example, in a music editor, there are many actions that create new
> notes. A note needs many pieces of information to describe it: the
> note's place in time, its duration, dynamics, whether tied to successive
> notes, type of flag or beam... Much of this information can be inferred
> from the context in which the note is created, and so a natural
> expressive language would bring a new note into existence with a minimal
> need for providing details. Those details would be inferred from the
> context. So that's a Reader monad right there.

This would be an example where I think that the Reader monad is an
implementation detail, not a model of the problem domain. (Not to
mention that I think that the Reader monad has very limited
applications.) The latter would be about trying to eliminate the need
for a context altogether, to group the many details so that they can be
"polymorphized away", etc.


Regards,
apfelmus

--
http://apfelmus.nfshost.com



------------------------------

Message: 2
Date: Tue, 18 Aug 2009 16:12:50 +0200
From: Bernhard Lehnert <b.lehn...@gmx.de>
Subject: [Haskell-beginners] Start file with associated prog (windows
        only?)
To: beginners@haskell.org
Message-ID: <1250604770.3888.17.ca...@sol>
Content-Type: text/plain

Hello list,

I believe I am looking for a haskell equivalent to a python library
function called os.startfile(...) which starts any given file with its
associated program. 

http://docs.python.org/library/os.html#os.startfile says:
"...this acts like double-clicking the file in Windows Explorer, or
giving the file name as an argument to the start command from the
interactive command shell: the file is opened with whatever application
(if any) its extension is associated.
[...]
startfile() returns as soon as the associated application is launched."

So to show a readme you just write:
import os
os.startfile("README.rtf")

to show your programs documentation you just write
os.startfile("documentation.pdf") 
and windows will decide which program to use to open a PDF.

The must urgent thing I actually want to do is open an Internet Browser
with my sponsors URL. 

Any good ideas?

Thanks in advance,
Bernhard



------------------------------

Message: 3
Date: Tue, 18 Aug 2009 16:07:46 +0100
From: Magnus Therning <mag...@therning.org>
Subject: Re: [Haskell-beginners] Start file with associated prog
        (windows        only?)
To: Bernhard Lehnert <b.lehn...@gmx.de>
Cc: beginners@haskell.org
Message-ID:
        <e040b520908180807n34e747e0s3452af0e28f08...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Tue, Aug 18, 2009 at 3:12 PM, Bernhard Lehnert<b.lehn...@gmx.de> wrote:
> Hello list,
>
> I believe I am looking for a haskell equivalent to a python library
> function called os.startfile(...) which starts any given file with its
> associated program.
>
> http://docs.python.org/library/os.html#os.startfile says:
> "...this acts like double-clicking the file in Windows Explorer, or
> giving the file name as an argument to the start command from the
> interactive command shell: the file is opened with whatever application
> (if any) its extension is associated.
> [...]
> startfile() returns as soon as the associated application is launched."
>
> So to show a readme you just write:
> import os
> os.startfile("README.rtf")
>
> to show your programs documentation you just write
> os.startfile("documentation.pdf")
> and windows will decide which program to use to open a PDF.
>
> The must urgent thing I actually want to do is open an Internet Browser
> with my sponsors URL.
>
> Any good ideas?

Windows has a command "start" which you can use e.g. via System.Process.proc.

/M

-- 
Magnus Therning                        (OpenPGP: 0xAB4DFBA4)
magnus@therning.org          Jabber: magnus@therning.org
http://therning.org/magnus         identi.ca|twitter: magthe


------------------------------

Message: 4
Date: Tue, 18 Aug 2009 19:56:55 +0200
From: Bernhard Lehnert <b.lehn...@gmx.de>
Subject: Re: [Haskell-beginners] Start file with associated prog
        (windows        only?)
To: Magnus Therning <mag...@therning.org>
Cc: beginners@haskell.org
Message-ID: <1250618215.3888.21.ca...@sol>
Content-Type: text/plain

Am Dienstag, den 18.08.2009, 16:07 +0100 schrieb Magnus Therning:

> Windows has a command "start" which you can use e.g. via System.Process.proc.

Thank you, Magnus - this is exactly what I was looking for. (By the way,
someone should implement something like this for GNOME and KDE,
too ;-) )



------------------------------

Message: 5
Date: Tue, 18 Aug 2009 15:34:09 -0400
From: Isaac Dupree <m...@isaac.cedarswampstudios.org>
Subject: Re: [Haskell-beginners] Start file with associated prog
        (windows        only?)
To: Bernhard Lehnert <b.lehn...@gmx.de>
Cc: Magnus Therning <mag...@therning.org>, beginners@haskell.org
Message-ID: <4a8b0231.1090...@isaac.cedarswampstudios.org>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Bernhard Lehnert wrote:
> Am Dienstag, den 18.08.2009, 16:07 +0100 schrieb Magnus Therning:
> 
>> Windows has a command "start" which you can use e.g. via System.Process.proc.
> 
> Thank you, Magnus - this is exactly what I was looking for. (By the way,
> someone should implement something like this for GNOME and KDE,
> too ;-) )

Well, there is `xdg-open` command, which is not as well-known as it 
should be.  OS X calls the equivalent command "open".  I'm not sure what 
xdg-open does with executable files (Does it really make sense, in a 
unixy context, to just execute them?)

-Isaac


------------------------------

Message: 6
Date: Tue, 18 Aug 2009 21:57:04 +0100
From: Magnus Therning <mag...@therning.org>
Subject: Re: [Haskell-beginners] Start file with associated prog
        (windows        only?)
To: Isaac Dupree <m...@isaac.cedarswampstudios.org>
Cc: beginners@haskell.org, Bernhard Lehnert <b.lehn...@gmx.de>
Message-ID: <4a8b15a0.4010...@therning.org>
Content-Type: text/plain; charset="utf-8"

Isaac Dupree wrote:
> Bernhard Lehnert wrote:
>> Am Dienstag, den 18.08.2009, 16:07 +0100 schrieb Magnus Therning:
>>
>>> Windows has a command "start" which you can use e.g. via 
>>> System.Process.proc.
>>
>> Thank you, Magnus - this is exactly what I was looking for. (By the way,
>> someone should implement something like this for GNOME and KDE,
>> too ;-) )
> 
> Well, there is `xdg-open` command, which is not as well-known as it 
> should be.  OS X calls the equivalent command "open".  I'm not sure what 
> xdg-open does with executable files (Does it really make sense, in a 
> unixy context, to just execute them?)

In Gnome there's also 'gnome-open'.

% xdg-open /usr/bin/gedit
Error showing url: No application is registered as handling this file

Same behaviour for gnome-open.

/M

-- 
Magnus Therning                        (OpenPGP: 0xAB4DFBA4)
magnus@therning.org          Jabber: magnus@therning.org
http://therning.org/magnus         identi.ca|twitter: magthe

-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 197 bytes
Desc: OpenPGP digital signature
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20090818/dc32ce3c/signature-0001.bin

------------------------------

Message: 7
Date: Tue, 18 Aug 2009 12:35:18 +0200
From: Heinrich Apfelmus <apfel...@quantentunnel.de>
Subject: [Haskell-beginners] Re: learning to use Haskell types
To: Michael Mossey <m...@alumni.caltech.edu>
Cc: beginners@haskell.org
Message-ID: <ee4899e8-3a95-46dd-94ad-e46444f35...@quantentunnel.de>
Content-Type: text/plain; charset=US-ASCII; delsp=yes; format=flowed

Michael Mossey wrote:
> Heinrich Apfelmus wrote:
>> This would be an example where I think that the Reader monad is an
>> implementation detail, not a model of the problem domain. (Not to
>> mention that I think that the Reader monad has very limited
>> applications.) The latter would be about trying to eliminate the need
>> for a context altogether, to group the many details so that they  
>> can be
>> "polymorphized away", etc.
>
> Can you explain more about what it means to "polymorphize away"  
> details? I'm not clear about that.
>
> You mention "grouping" details. Does this mean creating data which  
> types that hold all the details, and the data type itself is some  
> kind of larger concept? For example, you could say a note has many  
> details such as time, duration, dynamic, etc. And you could also  
> create
>
> data Note = Note { time :: Ratio, duration :: Ratio, dyn :: Dynamic }
>
> and work with Notes as much as possible without peering inside them.


Yes, the goal is to avoid peering inside. Creating a new abstraction  
(= no peeking inside) is the only way to make things elegant. Using  
record data types are a first step towards that goal.

Another technique is to use parametric polymorphism, that's what I  
intend to convey with the phrase "polymorphize away". The idea is  
that the type system can make sure that you don't peek inside.  
Consider the following (almost too trivial) example:

     length :: [Note] -> Int

This function is intended to calculate the length of a list of notes.  
But of course, it's wholly unimportant that the lists consists of  
notes, it could as well be a list of apples or integers. In fact, the  
specialization to notes is a mental burden, and it's much simpler to  
write a length function that does not care about the contents

     length :: [a] -> Int

The key point is that the type alone already ensures that  length   
*cannot* peek inside the list elements, because it's polymorphic in  a .

Another example is the function

     sortBy :: (a -> a -> Ordering) -> [a] -> [a]

which does not want to know anything about the list elements except  
that they can be compared.

Of course, these were rather general and well-known examples; the key  
is to find similar patterns in your own code and problem domain. For  
instance, notes in staff notation don't really care about velocities,  
notes in a piano roll are actually just rectangles in a grid, etc.  
The goal is to focus solely on the relevant details and hide the  
unimportant details behind a type variable  a .


Regards,
apfelmus

--
http://apfelmus.nfshost.com



------------------------------

Message: 8
Date: Tue, 18 Aug 2009 22:41:45 +0100
From: Simon Parry <sparr...@googlemail.com>
Subject: [Haskell-beginners] my ugly code and the Maybe monad
To: beginners@haskell.org
Message-ID: <1250631705.2431.24.ca...@localhost.localdomain>
Content-Type: text/plain

hello all,

Intro: I'm fairly new to Haskell, read some tutorials/books, this is my
first real attempt at making something rather than doing tutorial
problems - I thought I'd recode some financial maths up in Haskell...see
below.

It seems to work ok (I haven't properly tested it yet) but I feel the
pvs function is just ugly.  However it seems like its a fairly common
requirement for maths modelling ie using Maybe or Error or such to
represent conditions on the input variables and then later having to
combine those 'wrapped' values with other things.

Basically it seems inelegant and I feel like I'm confusing the monadic
and non-monadic parts?

help/criticism welcome,

thanks

Simon


module TimeValueMoney1 where

--taken from Financial Numerical Recipes in C++ by B A Odegaard (2006):
--Chapter 3

import Control.Monad

--time periods - assumes now is time 0--
times :: [Int]
times = [0..]

minusOne :: Double
minusOne = -1.0

--can have eg discrete or continuous compounding
type Compounding = Double -> Int -> Maybe Double

--discounting and present value--
discreteCompounding :: Compounding
discreteCompounding yield elapsed 
    | yield > minusOne = Just ( 1.0/ (1.0 + yield)^elapsed )
    | otherwise = Nothing

continuousCompounding :: Compounding
continuousCompounding yield elapsed 
    | yield > minusOne = Just (exp( minusOne * yield * fromIntegral
elapsed ) )
    | otherwise = Nothing

pvs :: Compounding -> Double -> [Double] -> Maybe [Double]
pvs df yield cashflow = zipWithM ( \c -> (>>= \d -> return $ c*d ) )
cashflow discounts
    where discounts = map discount times
          discount = df yield



------------------------------

Message: 9
Date: Wed, 19 Aug 2009 12:53:42 +0100
From: Jan Jakubuv <jaku...@gmail.com>
Subject: Re: [Haskell-beginners] my ugly code and the Maybe monad
To: Simon Parry <sparr...@googlemail.com>
Cc: beginners@haskell.org
Message-ID: <20090819115342.ga25...@lxultra2.macs.hw.ac.uk>
Content-Type: text/plain; charset=utf-8

Hi Simon,

On Tue, Aug 18, 2009 at 10:41:45PM +0100, Simon Parry wrote:
> It seems to work ok (I haven't properly tested it yet) but I feel the
> pvs function is just ugly.  However it seems like its a fairly common
> requirement for maths modelling ie using Maybe or Error or such to
> represent conditions on the input variables and then later having to
> combine those 'wrapped' values with other things.
> 

I don't quite understand what is function `pvs` supposed to do ?? Anyway,
I try to guess. It seems that it just applies `(df yield)` to `times` and
then multiply the resulting values one by one with `cashflow`. So it seems
that you need to lift multiplication `(*)` to the Maybe monad in the second
argument only. You can write your own version of `liftM2` (from
`Control.Monad`) like this:

    liftM2snd f a mb = do { b <- mb; return (f a b) }

You can verify that

    liftM2snd == (fmap .)

Thus you can rewrite `pvs` as:

    pvs2 df yield cashflow = multiply cashflow discounts
        where multiply = zipWithM (fmap . (*)) 
              discounts = map (df yield) times

You could alternatively use the library version of `liftM2` but then you
need to “lift” the `cashflow` list using `return`. Like this:

    pvs3 df yield cashflow = multiply (map return cashflow) discounts
        where multiply = zipWithM (liftM2 (*))
              discounts = map (df yield) times

When you take the advantage of commutativity of `*` you can write:

    pvs4 df yield = multiply discounts . map return 
        where multiply = zipWithM (liftM2 (*))
              discounts = map (df yield) times

or maybe even better:

    pvs5 df yield = multiply discounts 
        where multiply = zipWithM (flip $ fmap . (*))
              discounts = map (df yield) times

Anyway, note that all the `pvs` functions (including the your one) return
`Nothing` when `(df yield)` returns `Nothing` for at least one related
member of `times`. Is that what you want?

> Basically it seems inelegant and I feel like I'm confusing the monadic
> and non-monadic parts?
> 

You are using this function:

    fce = \c -> (>>= \d -> return $ c*d)

which is pretty ugly and not very intuitive. Note that this is simply
`liftM2snd (*)` from above, that is, `fmap . (*)`.

> help/criticism welcome,

You might want to look at the `liftM` functions from `Control.Monad`.

Note that I have inlined the only use of `discount`. In my opinion it
improves readability. But it's up to you to judge.

I hope this helps a little. I don't know any financial stuff so maybe I
didn't understand well what is going on.

Sincerely,
    Jan.

> 
> thanks
> 
> Simon
> 
> 
> module TimeValueMoney1 where
> 
> --taken from Financial Numerical Recipes in C++ by B A Odegaard (2006):
> --Chapter 3
> 
> import Control.Monad
> 
> --time periods - assumes now is time 0--
> times :: [Int]
> times = [0..]
> 
> minusOne :: Double
> minusOne = -1.0
> 
> --can have eg discrete or continuous compounding
> type Compounding = Double -> Int -> Maybe Double
> 
> --discounting and present value--
> discreteCompounding :: Compounding
> discreteCompounding yield elapsed 
>     | yield > minusOne = Just ( 1.0/ (1.0 + yield)^elapsed )
>     | otherwise = Nothing
> 
> continuousCompounding :: Compounding
> continuousCompounding yield elapsed 
>     | yield > minusOne = Just (exp( minusOne * yield * fromIntegral
> elapsed ) )
>     | otherwise = Nothing
> 
> pvs :: Compounding -> Double -> [Double] -> Maybe [Double]
> pvs df yield cashflow = zipWithM ( \c -> (>>= \d -> return $ c*d ) )
> cashflow discounts
>     where discounts = map discount times
>           discount = df yield
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners


-- 
Heriot-Watt University is a Scottish charity
registered under charity number SC000278.



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 14, Issue 11
*****************************************

Reply via email to