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: Ambigous Types with Haskell Functional Graph Library
      (Christian Maeder)
   2. Re:  my ugly code and the Maybe monad (Simon Parry)
   3. Re:  my ugly code and the Maybe monad (Jan Jakubuv)
   4.  type inference question (I. J. Kennedy)
   5. Re:  type inference question (Daniel Fischer)
   6.  definition of combinator (Michael Mossey)
   7. Re:  definition of combinator (Brandon S. Allbery KF8NH)
   8. Re:  definition of combinator (Jan Jakubuv)


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

Message: 1
Date: Wed, 19 Aug 2009 17:16:41 +0200
From: Christian Maeder <christian.mae...@dfki.de>
Subject: [Haskell-beginners] Re: Ambigous Types with Haskell
        Functional Graph        Library
To: Joe Schafer <joesmo...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <4a8c1759.5020...@dfki.de>
Content-Type: text/plain; charset=ISO-8859-1

The type constructor variable "gr" can be instantiated with
"Data.Graph.Inductive.Tree.Gr" via a type signature:

Prelude Data.Graph.Inductive.Example> ucycle 5 ::
 Data.Graph.Inductive.Tree.Gr () ()

1:()->[((),2)]
2:()->[((),3)]
3:()->[((),4)]
4:()->[((),5)]
5:()->[((),1)]

HTH Christian

Joe Schafer wrote:
> Hey all,
> 
> New to Haskell and I'm trying to use the FGL but I keep running into the
> same error.
> 
> If I load Data.Graph.Inductive.Example and use one of the example
> functions such as ucycle I get:
> 
>     Ambiguous type variable `gr' in the constraint:
>       `Graph gr' arising from a use of `ucycle' at <interactive>:1:0-7
>     Probable fix: add a type signature that fixes these type variable(s)
> 
> Here's the type of ucycle for reference.
> 
> ucycle :: Graph gr => Int -> gr () ()
> 
> I'm using GHC 6.10.1 and FGL 5.4.2.2
> 
> Thanks,
> Joe


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

Message: 2
Date: Wed, 19 Aug 2009 23:57:47 +0100
From: Simon Parry <sparr...@googlemail.com>
Subject: Re: [Haskell-beginners] my ugly code and the Maybe monad
To: Jan Jakubuv <jaku...@gmail.com>, "; beginners"@haskell.org
Message-ID: <1250722667.2431.65.ca...@localhost.localdomain>
Content-Type: text/plain; charset="UTF-8"

Thanks Jan, very helpful and you're right I am just trying to combine 2
lists; one with 'wrapped' values, one without.

> You can write your own version of `liftM2` (from
> `Control.Monad`) like this:
> 
>     liftM2snd f a mb = do { b <- mb; return (f a b) }
> 

so the b <- mb bit is 'unwrapping' the Maybe b to use it with the pure
function f?  I guess I didn't realise this as I've only seen it in the
IO monad, but naturally it would work with all monads.

> You can verify that
> 
>     liftM2snd == (fmap .)

if I look at this in GHCi the liftM2snd acts over monads and the (fmap .) acts 
over functors.  
Now I'm still trying to get comfortable with simple monad manipulations so 
maybe I should just 
read this as functors are equivalent to monads and not worry too much about it 
yet?  
With that in mind fmap acts to map some pure function over a 'wrapped' value? 

Thanks also for the other suggestions, its always helpful to see a progression 
rather than 
jumping in at say pvs5.

> 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?

I did want it to only perform the calc if the yield was sensible.

thanks again

Simon

On Wed, 2009-08-19 at 12:53 +0100, Jan Jakubuv wrote:
> 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
> 
> 



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

Message: 3
Date: Thu, 20 Aug 2009 11:29:24 +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: <20090820102924.ga24...@lxultra2.macs.hw.ac.uk>
Content-Type: text/plain; charset=utf-8

On Wed, Aug 19, 2009 at 11:57:47PM +0100, Simon Parry wrote:
> Thanks Jan, very helpful and you're right I am just trying to combine 2
> lists; one with 'wrapped' values, one without.
> 
> > You can write your own version of `liftM2` (from
> > `Control.Monad`) like this:
> > 
> >     liftM2snd f a mb = do { b <- mb; return (f a b) }
> > 
> 
> so the b <- mb bit is 'unwrapping' the Maybe b to use it with the pure
> function f?  

That's correct. In fact it is just a syntactic abbreviation (sugar) for

    liftM2snd f a mb = mb >>= \b -> return (f a b) 

You can always rewrite expressions with `do` using just `>>=`, `>>`, and
`->`. (Note that `<-` becomes the “dot” `->`.)

> I guess I didn't realise this as I've only seen it in the IO monad, but
> naturally it would work with all monads.
> 
> > You can verify that
> > 
> >     liftM2snd == (fmap .)
> 
> if I look at this in GHCi the liftM2snd acts over monads and the (fmap .) 
> acts over functors.  
> Now I'm still trying to get comfortable with simple monad manipulations so 
> maybe I should just 
> read this as functors are equivalent to monads and not worry too much about 
> it yet?  
> With that in mind fmap acts to map some pure function over a 'wrapped' value? 
> 

Every Monad is automatically a Functor as well. You can define `fmap` using
monadic operations:

    fmap f ma = ma >>= return . f

Anyway, for some reasons this is not done automatically. You can do it
automatically with some GHC extensions. Load this into GHCi (don't forget
the first line):

    {-# OPTIONS -XFlexibleInstances -XUndecidableInstances #-}

    instance Monad m => Functor m where
        fmap f ma = ma >>= return . f

And here we go (in my GHCi 6.10.4):

    *Main> :t fmap
    fmap :: (Monad f) => (a -> b) -> f a -> f b

Usually, however, you don't need to do this because all instances of Monad
are already instances of Functor.

Also note that 

    fmap :: (Functor f) => (a -> b) -> f a -> f b

holds as well, that is, the type of `fmap` is ambiguous (because of the
GHC extensions above).

Sincerely,
    Jan.
    


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



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

Message: 4
Date: Sun, 23 Aug 2009 13:12:16 -0500
From: "I. J. Kennedy" <j...@realmode.com>
Subject: [Haskell-beginners] type inference question
To: beginners@haskell.org
Message-ID:
        <1008bfc90908231112o466c036ey24530ce89c09...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Given a sort function that works on numbers, you can sort
in reverse order by first negating the list, then sorting, then
negating again:

 Prelude Data.List> let revsort = (map negate) . sort . (map negate)

The function sort takes any list of Ord; negate works on any Num.

 Prelude Data.List> :t negate
 negate :: (Num a) => a -> a
 Prelude Data.List> :t sort
 sort :: (Ord a) => [a] -> [a]

I'd therefore expect my revsort function to work on any type that is
both an Ord and a Num.  However:

Prelude Data.List> :t revsort
revsort :: [Integer] -> [Integer]

I was expecting something like
 revsort :: (Ord a, Num a) => [a] -> [a]
instead.

Question: Why did the GHCI's type inference mechanism jump to
the conclusion that revsort should only work with Integer lists?


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

Message: 5
Date: Sun, 23 Aug 2009 20:44:25 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] type inference question
To: beginners@haskell.org
Message-ID: <200908232044.25233.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

Am Sonntag 23 August 2009 20:12:16 schrieb I. J. Kennedy:
> Given a sort function that works on numbers, you can sort
> in reverse order by first negating the list, then sorting, then
> negating again:
>
>  Prelude Data.List> let revsort = (map negate) . sort . (map negate)
>
> The function sort takes any list of Ord; negate works on any Num.
>
>  Prelude Data.List> :t negate
>  negate :: (Num a) => a -> a
>  Prelude Data.List> :t sort
>  sort :: (Ord a) => [a] -> [a]
>
> I'd therefore expect my revsort function to work on any type that is
> both an Ord and a Num.  However:
>
> Prelude Data.List> :t revsort
> revsort :: [Integer] -> [Integer]
>
> I was expecting something like
>  revsort :: (Ord a, Num a) => [a] -> [a]
> instead.
>
> Question: Why did the GHCI's type inference mechanism jump to
> the conclusion that revsort should only work with Integer lists?

Because you defined it without an argument or type signature.
By the monomorphism restriction ( 
http://www.haskell.org/haskellwiki/Monomorphism_Restriction ), such values must 
have a 
monomorphic type and by the defaulting rules, that is chosen as Integer.

You can
a) specify a type signature (good in source files)
b) define it as a function binding
let revsort xs = map negate . sort . map negate $ xs
c) turn off the monomorphism restriction in ghci:
Prelude> :set -XNoMonomorphismRestriction
Prelude> :m +Data.List
Prelude Data.List> let revsort = map negate . sort . map negate
Prelude Data.List> :t revsort
revsort :: (Num a, Ord a) => [a] -> [a]
(might put :set -XNoMonomorphismRestriction in your .ghci file)

btw, another way to revsort is
let revsort = sortBy (flip compare)



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

Message: 6
Date: Sun, 23 Aug 2009 17:44:27 -0700
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: [Haskell-beginners] definition of combinator
To: beginners <beginners@haskell.org>
Message-ID: <4a91e26b.9010...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Although I can use libraries like Parsec, I don't really understand what a 
combinator is, theoretically. There is an article here

http://en.wikipedia.org/wiki/Combinator

with the statement "A combinator is a higher-order function that uses only 
function application and earlier defined combinators to define a result 
from its arguments."

Okay, so I believe a "higher-order function" is a function that takes 
function(s) as its argument(s). I don't know what "uses only function 
application" means. Application of what functions to what? Can someone give 
a concrete example that's simple?

Thanks,
Mike


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

Message: 7
Date: Sun, 23 Aug 2009 21:06:25 -0400
From: "Brandon S. Allbery KF8NH" <allb...@ece.cmu.edu>
Subject: Re: [Haskell-beginners] definition of combinator
To: Michael Mossey <m...@alumni.caltech.edu>
Cc: beginners <beginners@haskell.org>
Message-ID: <6df41b5b-6437-4e71-b9bf-c3cb5e8db...@ece.cmu.edu>
Content-Type: text/plain; charset="us-ascii"

On Aug 23, 2009, at 20:44 , Michael Mossey wrote:
> Although I can use libraries like Parsec, I don't really understand  
> what a combinator is, theoretically. There is an article here


Example:  in Parsec, "many" is a combinator which takes a parser as an  
argument and produces a parser that matches multiple successive copies  
of whatever the argument matches.  It doesn't need to know anything  
about its argument except that it's a parser.  This kind of function  
lets you build up complex but general parsers from smaller pieces.

-- 
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university    KF8NH


-------------- next part --------------
A non-text attachment was scrubbed...
Name: PGP.sig
Type: application/pgp-signature
Size: 195 bytes
Desc: This is a digitally signed message part
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20090823/a5cb87bd/PGP-0001.bin

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

Message: 8
Date: Mon, 24 Aug 2009 11:23:29 +0100
From: Jan Jakubuv <jaku...@gmail.com>
Subject: Re: [Haskell-beginners] definition of combinator
To: Michael Mossey <m...@alumni.caltech.edu>
Cc: beginners <beginners@haskell.org>
Message-ID: <20090824102329.ga13...@lxultra2.macs.hw.ac.uk>
Content-Type: text/plain; charset=utf-8

Hi Michael,

On Sun, Aug 23, 2009 at 05:44:27PM -0700, Michael Mossey wrote:
> "A combinator is a higher-order function that uses only function
> application and earlier defined combinators to define a result from its
> arguments."
> 
> Okay, so I believe a "higher-order function" is a function that takes 
> function(s) as its argument(s). I don't know what "uses only function 
> application" means. Application of what functions to what? 

Briefly, a combinator applies “earlier defined combinators” to “its
arguments”. But remember that a combinator's argument can be a function as
well, so it may become more complicated. Then it simply applies functions
(other combinators, combinator's arguments, library functions) to their
arguments (other combinators, combinator's arguments, library functions,
constants, ...).

Finally, I guess that the word “only” suggests that it doesn't read any
parsed text by itself but it only calls (combine) other parsers.

Sincerely,
    Jan.



-- 
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 12
*****************************************

Reply via email to