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:  Maybe, Either (Michael Mossey)
   2. Re:  Maybe, Either (Michael Snoyman)
   3. Re:  Maybe, Either (Yusaku Hashimoto)
   4. Re:  Maybe, Either (Michael Snoyman)
   5. Re:  Maybe, Either (Brandon S. Allbery KF8NH)


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

Message: 1
Date: Tue, 15 Sep 2009 06:45:14 -0700 (PDT)
From: "Michael Mossey" <m...@alumni.caltech.edu>
Subject: Re: [Haskell-beginners] Maybe, Either
To: "Conor McBride" <co...@strictlypositive.org>
Cc: beginners@haskell.org
Message-ID:
        <1227.75.50.163.142.1253022314.squir...@mail.alumni.caltech.edu>
Content-Type: text/plain;charset=iso-8859-1

As a beginner, I'm not directly following the usefulness of these
alternative implementations. I thought I would give some example code.
Here I am trying to handle errors with Either String.

You can read it here or in hpaste.org:
<http://hpaste.org/fastcgi/hpaste.fcgi/view?id=9393#a9393>

import Data.Ratio
import qualified Data.Map as Map

-- An elemental music object such as note, rest, dynamic mark, etc.
data MusicObject = MusicObject ...

-- A composition has several "streams". A stream could be a continuous
-- melody that appears on a single staff, or other types of data that
-- are arranged serially in time.
data Time = Rational
data StreamId = StreamId ...
data MusicStream = (StreadId, Map.Map Time MusicObject)
data Comp = [MusicStream]

-- A cursor is a concept used to "point to" a note or generalized location
-- in the composition so that editing can be done at that point. For now,
-- all we need is to point to the stream and time.
data Cursor = Cursor { getCurId :: StreamId
                     , getCurTime :: Time }

-- Utility to make it easier to annotate an Either monad with a function
-- that catches an error message, prepends a context message, and rethrows.
ce :: String -> Either String a -> Either String a
ce c = (flip catchError) (\s -> throwError (c ++ "\n" ++ s))

-- Utility to replace an item in an assoc list, inside the Either String
-- monad.
replaceAlist :: Eq a => a -> b -> [(a,b)] -> Either String [(a,b)]
replaceAlist _ _ [] = throwError "Item not found in alist."
replaceAlist iid obj (x:xs) = if fst x == iid
                              then return $ (iid,obj) : xs
                              else do rem <- replaceAlist iid obj xs
                                      return $ x : rem

...

-- Delete a note from a composition. Deleting the last note in a stream is
-- an error condition.
--
-- Conditions that will cause an error:
--   - cursor stream id doesn't exist in the composition
--   - there is no note at the given cursor
--   - there is only one note in the stream (so deleting it would delete
--     the last note)
compDeleteNote :: Cursor -> Comp -> Either String Comp
compDeleteNote cur comp = ce "In compeDeleteNote:" $ do
  let Cursor { getCurId=iid, getCurTime=t } = cur
  -- First internal error might occur if no stream with the cursor's id
  -- occurs in the Comp.
  oldMap <- maybe (Left "no such stream") Right (lookup iid comp)
  -- Second internal error: no music object is found at the cursor's time.
  moAtCur <- maybe (Left "no m.o. at cursor") Right (Map.lookup t oldMap)
  let durAtCur = getDur moAtCur
      (l,r) = Map.split t oldMap
      r' = Map.mapKeys (\k -> k - durAtCur) r
      joined = Map.union l r'
  -- Third error condition: this action deleted the last note.
  if Map.null joined then (Left "deleted last note") else Right ()
  replaceAlist iid joined comp





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

Message: 2
Date: Tue, 15 Sep 2009 18:56:19 +0300
From: Michael Snoyman <mich...@snoyman.com>
Subject: Re: [Haskell-beginners] Maybe, Either
To: "Brandon S. Allbery KF8NH" <allb...@ece.cmu.edu>
Cc: beginners@haskell.org
Message-ID:
        <29bf512f0909150856l2d20889cr87b881f129789...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Tue, Sep 15, 2009 at 6:21 AM, Brandon S. Allbery KF8NH <
allb...@ece.cmu.edu> wrote:

> On Sep 14, 2009, at 14:42 , Michael Snoyman wrote:
>
> I understand that fail being in Monad is controversial, but my version of
> the function works in *all* monads. This is very
>
>
> Not really; "fail" in non-MonadPlus-es is a rather poorly defined notion,
> and there are no guarantees that the result will be at all sane.  "mzero" is
> well defined.
>

mzero also does not allow giving error messages. There are times when you
want to be able to fail with an explanation of why. fail seems to fit the
bill properly for this (fail taking a String argument and all...).

Now you point out that fail is not always properly defined. I quite agree
with that. Nonetheless, in the simple cases I am trying to address here, it
is IMO the best option available. If you end up using the function only with
monads that properly define fail, then all the better.

Michael
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090915/c1c0e99e/attachment-0001.html

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

Message: 3
Date: Wed, 16 Sep 2009 02:59:36 +0900
From: Yusaku Hashimoto <nonow...@gmail.com>
Subject: Re: [Haskell-beginners] Maybe, Either
To: Conor McBride <co...@strictlypositive.org>
Cc: beginners@haskell.org
Message-ID:
        <d17c24b90909151059y4ec668edy5145e8706613d...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

If I understood your post correctly, you said

- generalizing lookup to MonadPlus or Alternative or such classes are
not necessary
- use Maybe as usual, we should use adapters as we need

Conor, You have said this many times elsewhere, but unfortunatelly, I
heard it for the first time =) so please correct me if I'm wrong.

I thought generalizing lookup is good example for usage of the
MonadPlus as I read in RWH[1], but you said it's not necesarry.

Now, I understood there are two positions for such classes. One is
using generalizing for it, another is not.

So, I want to know that when such classes should be used from later position.

Heinrich suggested that is for overloading. But do any other usages are exist?

[1]: 
http://book.realworldhaskell.org/read/programming-with-monads.html#VCard.hs:lookupM

Cheers
-nwn

On Tue, Sep 15, 2009 at 5:21 PM, Conor McBride
<co...@strictlypositive.org> wrote:
> Hi
>
> This topic comes up a lot, and this is what I usually say when
> it does. It's a thing I learned from James McKinna, many years
> ago...
>
> Might I gently suggest that there is a much better, more
> natural way to abstract over every type-former which has
> some sort of return/pure-like thing and some sort of mzero/empty
> like thing? You could use the type-former which is inductively
> defined to be the least such thing, and as such has a canonical
> mapping to all the others, namely Maybe.
>
> It's not necessarily a good idea to fix on Monad or MonadPlus
> as there are other choices. For example,
>
> On 15 Sep 2009, at 07:14, Yusaku Hashimoto wrote:
>
>> I prefer Alternative to MonadPlus for explaining failure. It has
>> better name and operator for failure and try-another.
>>
>> import Control.Applicative
>>
>> aLookup :: (Alternative f, Eq k) => k -> [(k,v)] -> f v
>> aLookup key pairs = maybe empty pure $ lookup key pairs
>
> there are notorious non-monadic instances for the above f
> (some formulations of parsing, in particular). So,
>
>>> I understand that fail being in Monad is controversial, but my version of
>>> the function works in *all* monads.
>
> this is a touch presumptuous. On the one hand, Brent is right
> when he says
>
>> It doesn't work in *all* monads -- it only works in monads which
>> support a sensible notion of failure.
>
> but he's perhaps excessive when he says
>
>> This is exactly what is captured by the MonadPlus constraint
>> on my version of mLookup.
>
> because it's not exact: it requires mplus as well as a sensible
> notion of failure. And yes, why should we insist on (>>=) when
> we just need a return and an mzero?  Incidentally, I don't know
> where the MonadPlus instance
>
>> (IO, Maybe, [], ...) are already instances of MonadPlus.
>
> of IO is coming from, but I want it caught and locked up now (in
> STM, for example) before it does any permanent damage.
>
> Why not factor out the failure-prone operations from the business
> of interpreting failure in some failure-supporting context? Work
> concretely while you can (types stay shorter, error messages make
> more sense) then apply adapters
>
> malt :: Alternative f => Maybe x -> f x
> malt = maybe empty pure
>
> mop :: MonadPlus m => Maybe x -> m x
> mop = maybe mzero return
>
> when you need to? This also reduces the risk of connecting an
> ambiguous supplier to an ambiguous consumer, (show . read) style.
>
> The message clearly bears repeating. Inductive definition is
> a concrete form of abstraction. Don't be fooled by its
> appearance: Maybe is the most abstract choice here -- the
> classier options demand more structure than is needed and
> thus exclude use-cases.
>
> I'll crawl back under my stone now.
>
> All the best
>
> Conor
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


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

Message: 4
Date: Tue, 15 Sep 2009 23:21:46 +0300
From: Michael Snoyman <mich...@snoyman.com>
Subject: Re: [Haskell-beginners] Maybe, Either
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID:
        <29bf512f0909151321u616c63b4p81e89b093b370...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Tue, Sep 15, 2009 at 3:08 AM, Brent Yorgey <byor...@seas.upenn.edu>wrote:

>
> It doesn't work in *all* monads -- it only works in monads which
> support a sensible notion of failure.  This is exactly what is
> captured by the MonadPlus constraint on my version of mLookup.  And,
> in fact, any monad in context of which you would want to use mLookup
> (IO, Maybe, [], ...) are already instances of MonadPlus.
>

I'm looking at the Control.Monad documentation (
http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Monad.html),
and it doesn't seem that IO is an instance of MonadPlus. I get the same
results with a simple code check. Can you clarify? Calling lookup from IO is
a common use case for me.

Michael
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090915/5d6be542/attachment-0001.html

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

Message: 5
Date: Tue, 15 Sep 2009 16:49:21 -0400
From: "Brandon S. Allbery KF8NH" <allb...@ece.cmu.edu>
Subject: Re: [Haskell-beginners] Maybe, Either
To: Michael Snoyman <mich...@snoyman.com>
Cc: beginners@haskell.org
Message-ID: <20d858b9-27f9-4a76-8e73-e5edfe34e...@ece.cmu.edu>
Content-Type: text/plain; charset="us-ascii"

Skipped content of type multipart/alternative-------------- 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/20090915/683dab3a/PGP.bin

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

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


End of Beginners Digest, Vol 15, Issue 10
*****************************************

Reply via email to