[Haskell-cafe] chr/ord?

michael rice nowgate at yahoo.com
Fri May 1 06:29:37 EDT 2009


Understood. Thanks.

A little further on in the tutorial they define a "parent" function.

The mplus operator is used to combine monadic values from
separate computations into a single monadic value.  Within the context
of our sheep-cloning example, we could use Maybe's
mplus to define a function,
parent s = (mother s) `mplus` (father s),
which would return a parent if there is one, and Nothing is the sheep has no parents at all.
For a sheep with both parents, the function would return one or the
other, depending on the exact definition of mplus in the
Maybe monad.

But I get this when I try to use it:

sheep.hs:30:22: Not in scope: `mplus'
[michael at localhost ~]$

And here's the sheep.hs file, attempting to use "parent" near the bottom

========= 

{- Author:     Jeff Newbern
   Maintainer: Jeff Newbern <jnewbern at nomaware.com>
   Time-stamp: <Mon Nov 10 11:59:14 2003>
   License:    GPL
-}

{- DESCRIPTION

Example 1 - Our first monad

Usage: Compile the code and execute the resulting program.
       It will print Dolly's maternal grandfather.
-}

-- everything you need to know about sheep
data Sheep = Sheep {name::String, mother::Maybe Sheep, father::Maybe Sheep}

-- we show sheep by name

instance Show Sheep where
  show s = show (name s)

-- comb is a combinator for sequencing operations that return Maybe
comb :: Maybe a -> (a -> Maybe b) -> Maybe b
comb Nothing  _ = Nothing
comb (Just x) f = f x

parent s = (mother s) `mplus` (father s)

-- now we can use `comb` to build complicated sequences
maternalGrandfather :: Sheep -> Maybe Sheep
maternalGrandfather s = (Just s) `comb` mother `comb` father

fathersMaternalGrandmother :: Sheep -> Maybe Sheep
fathersMaternalGrandmother s = (Just s) `comb` father `comb` mother `comb` mother 

mothersPaternalGrandfather :: Sheep -> Maybe Sheep
mothersPaternalGrandfather s = (Just s) `comb` mother `comb` father `comb` father 

-- this builds our sheep family tree
breedSheep :: Sheep
breedSheep = let adam   = Sheep "Adam" Nothing Nothing
                 eve    = Sheep "Eve" Nothing Nothing
         uranus = Sheep "Uranus" Nothing Nothing
         gaea   = Sheep "Gaea" Nothing Nothing
         kronos = Sheep "Kronos" (Just gaea) (Just uranus)
                 holly  = Sheep "Holly" (Just eve) (Just adam)
             roger  = Sheep "Roger" (Just eve) (Just kronos)
             molly  = Sheep "Molly" (Just holly) (Just roger)
         in Sheep "Dolly" (Just molly) Nothing

-- print Dolly's maternal grandfather
main :: IO ()
main = let dolly = breedSheep
       in do print (parent dolly)
        
-- END OF FILE

Michael



--- On Wed, 4/29/09, Anton van Straaten <anton at appsolutions.com> wrote:

From: Anton van Straaten <anton at appsolutions.com>
Subject: Re: [Haskell-cafe] chr/ord?
To: "haskell-cafe at haskell.org" <haskell-cafe at haskell.org>
Date: Wednesday, April 29, 2009, 12:33 PM

michael rice wrote:
> Since I'm trying to learn Monads, let's look at this as a teaching moment. The example code (see below), which I pulled off YAMT (Yet Another Monad Tutorial ;-)), is the source of my 'comb' function.
> 
> I understand the code as it now stands, and I understand that the Prelude (>>=) would replace the 'comb'. Adding whatever statements are needed, how would you "specialize" the (>>=) to Maybe and solve this particular problem.

Saying that "comb is just (>>=) specialized to Maybe" just means that you can define comb like this:

  comb :: Maybe a -> (a -> Maybe b) -> Maybe b
  comb = (>>=)

Which also of course means that you can typically use (>>=) instead of comb.  Although in some cases, being more specific about the type can be useful.

You can do this sort of specialization for any polymorphic function, e.g.:

  -- id is predefined in Haskell, definition given as example
  id :: a -> a
  id x = x

  intID :: Int -> Int
  intId = id

In that case, the compiler basically specializes the function for you, providing a version of it that's specific to Ints.

However, (>>=) is defined by the Monad type class, and as it happens there's also already a definition for it that's specific to the Maybe type.  You can see GHC's source for it here:
http://haskell.org/ghc/docs/latest/html/libraries/base/src/Data-Maybe.html#Maybe 

Not surprisingly, that definition is essentially identical to the definition of comb:

  (Just x) >>= k      = k x
  Nothing  >>= _      = Nothing

So defining "comb = (>>=)" just uses that definition.

Anton

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe at haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



      
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090501/f3bb9d4e/attachment.htm


More information about the Haskell-Cafe mailing list