Sorry -- the vocabulary template is attached.


> From: haskell-cafe-request@haskell.org
> Subject: Haskell-Cafe Digest, Vol 70, Issue 2
> To: haskell-cafe@haskell.org
> Date: Mon, 1 Jun 2009 21:47:16 -0400
>
> Send Haskell-Cafe mailing list submissions to
> haskell-cafe@haskell.org
>
> To subscribe or unsubscribe via the World Wide Web, visit
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> or, via email, send a message with subject or body 'help' to
> haskell-cafe-request@haskell.org
>
> You can reach the person managing the list at
> haskell-cafe-owner@haskell.org
>
> When replying, please edit your Subject line so it is more specific
> than "Re: Contents of Haskell-Cafe digest..."
>
>
> Today's Topics:
>
> 1. Re: Missing a "Deriving"? (Daniel Fischer)
> 2. Re: Bool as type class to serve EDSLs. (Claus Reinke)
> 3. Re: ANN: new version of uu-parsinglib (S. Doaitse Swierstra)
> 4. Re: Re: Error message reform (Claus Reinke)
> 5. Re: Re: Error message reform (was: Strange type errorwith
> associated type synonyms) (Claus Reinke)
> 6. Re: Missing a "Deriving"? (michael rice)
> 7. Re: Bool as type class to serve EDSLs. (Sebastian Fischer)
> 8. Checking a value against a passed-in constructor? (Dan Cook)
> 9. Re: Checking a value against a passed-in constructor?
> (Jason Dagit)
> 10. Re: Missing a "Deriving"? (michael rice)
> 11. Re: Missing a "Deriving"? (Ross Mellgren)
> 12. Re: Missing a "Deriving"? (michael rice)
> 13. Re: Missing a "Deriving"? (Ross Mellgren)
> 14. Re: Missing a "Deriving"? (michael rice)
>
>
> ----------------------------------------------------------------------
>
> Message: 1
> Date: Mon, 1 Jun 2009 19:51:35 +0200
> From: Daniel Fischer <daniel.is.fischer@web.de>
> Subject: Re: [Haskell-cafe] Missing a "Deriving"?
> To: haskell-cafe@haskell.org
> Message-ID: <200906011951.35775.daniel.is.fischer@web.de>
> Content-Type: text/plain; charset="iso-8859-15"
>
> Am Montag 01 Juni 2009 19:02:36 schrieb michael rice:
>
> > All good so far, but then tried to convert Failable from Computation to
> > Monad
> >
> >
> > instance Monad Failable where
> >     return = Success
> >     fail = Fail
> >     >>= (Success x) f = f x
> >     >>= (Fail s) _ = Fail s
> >     mplus (Fail _) y = y
> >     mplus x _ = x
> >  
> >
> > and got the following error.
> >
> >
> > Prelude> :l graph5
> > [1 of 1] Compiling Main             ( graph5.hs, interpreted )
> >
> > graph5.hs:34:4: parse error on input `>>='
> > Failed, modules loaded: none.
> > Prelude>
> >
>
> When you use an operator in prefix position, you must enclose it in parentheses, like you
> must enclose a function in backticks if you use it infix.
>
> So the definition of (>>=) should read
>
>
> (>>=) (Success x) f = f x
> (>>=) (Fail s) _ = Fail s
>
> or, defining it in infix position,
> (Success x) >>= f = f x
> (Fail s) >>= _ = Fail s
>
> >
> > Complete code follows.
> >
> > Michael
> >
>
>
>
> ------------------------------
>
> Message: 2
> Date: Mon, 1 Jun 2009 19:22:10 +0100
> From: "Claus Reinke" <claus.reinke@talk21.com>
> Subject: Re: [Haskell-cafe] Bool as type class to serve EDSLs.
> To: "haskell Cafe" <haskell-cafe@haskell.org>
> Message-ID: <76CE077128014A86A2D61E5918F8BFE8@cr3lt>
> Content-Type: text/plain; format=flowed; charset="iso-8859-1";
> reply-type=original
>
> >> Do you argue that overloading logical operations like this in Haskell
> >> sacrifices type safety? Could programs "go wrong" [1] that use such
> >> abstractions?
> >
> > If I understand your point correctly, you are suggesting that such programs
> > are still type safe. I agree with the claim that such features are
> > detrimental in practice though. Instead of lumping it with type safety,
> > then what do we call it? I think I've heard of languages that do such
> > conversions as "weakly" typed. Really the issue is with implicit
> > conversions, right?
>
> Isn't it merely a matter of balance? In order for typed programs not
> to go "wrong", one has to define "right" and "wrong", and devise a type
> system that rules out anything that might go "wrong", usually at the
> expense of some programs that might go "right".
>
> Advanced type system features like overloading take that unused space
> and devise ways to redirect code that would go "wrong" (in simpler
> systems) to go "right" in useful new ways (eg: adding two functions or
> matrices or .. does not have to be "wrong", there are interpretations in
> which all of these make perfect sense, and Haskell can express many
> of them).
>
> What is happening then is that more and more of the previously "wrong"
> space is filled up with meaningful ways of going "right", until nearly every
> syntactically valid program goes somewhere. That can make for an
> extremely expressive and powerful language, but it renders the naive
> notion of going "wrong" or "right" rather meaningless: "wrong" just
> means we haven't figured out a meaningful way to interpret it, and
> going "right" can easily be a far cry from where you wanted it to go.
>
> Claus
>
> PS. this problem can be made worse if the implicit conversions
> aren't consistent, if small "twitches" in source code can lead to
> grossly different behaviour. There is a fine line between advanced
> and uncontrollable, and opinions on what side of the line any given
> definition is on can differ.
>
>
>
>
> ------------------------------
>
> Message: 3
> Date: Mon, 1 Jun 2009 20:27:05 +0200
> From: "S. Doaitse Swierstra" <doaitse@swierstra.net>
> Subject: Re: [Haskell-cafe] ANN: new version of uu-parsinglib
> To: Ross Paterson <ross@soi.city.ac.uk>
> Cc: haskell-cafe@haskell.org
> Message-ID: <8F2D399B-451A-45F4-9FE1-B7F5145C3B91@swierstra.net>
> Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes
>
> And rename "empty" to "fail"? You managed to confuse me since I always
> use pSucceed to recognise the empty string.
>
> Doaitse
>
>
> On 1 jun 2009, at 01:21, Ross Paterson wrote:
>
> > On Sun, May 31, 2009 at 09:40:38PM +0200, S. Doaitse Swierstra wrote:
> >> A new version of the uu-parsinglib has been uploaded to hackage. It
> >> is
> >> now based on Control.Applicative where possible.
> >>
> >> Be warned that functions like some and many will be redefined in the
> >> future.
> >
> > Perhaps we should make some and many methods of Alternative, <* and *>
> > methods of Applicative and <$ a method of Functor, all with the
> > current
> > definitions as defaults. (John Meacham was also asking for the first
> > of these.)
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
>
> ------------------------------
>
> Message: 4
> Date: Mon, 1 Jun 2009 19:49:44 +0100
> From: "Claus Reinke" <claus.reinke@talk21.com>
> Subject: Re: [Haskell-cafe] Re: Error message reform
> To: <haskell-cafe@haskell.org>
> Message-ID: <E0BDCB9EE5F84BEA9126D498C0F98621@cr3lt>
> Content-Type: text/plain; format=flowed; charset="UTF-8";
> reply-type=response
>
> > It's too wordy, but it's a start. This is also prime ground for wanting
> > to have configurable levels of error reports, since some users will find
> > it helpful to see both types but others will find it confusing.
>
> Indeed. For this simple example, I find Hugs' message nearly optimal,
> but as one could just as well construct examples where GHC's message
> was nearly optimal, I've tried instead to extend the example, until neither
> Hugs nor GHC gives an optimal message. Even so, it is worth comparing
> the two, and their complementary approaches to the problem:
>
> t = (let q=0 in(\y->(\x->(\z->let r=1 in x z))) ()) :: (a->b)->(a->a)
>
> D:\home\Haskell\tmp\desktop\errormessages.hs:2:41:
> Couldn't match expected type `a' against inferred type `b'
> `a' is a rigid type variable bound by
> an expression type signature
> at D:\home\Haskell\tmp\desktop\errormessages.hs:2:56
> `b' is a rigid type variable bound by
> an expression type signature
> at D:\home\Haskell\tmp\desktop\errormessages.hs:2:59
> In the expression: x z
> In the expression: let r = 1 in x z
> In the expression: (\ z -> let r = 1 in x z)
>
> ERROR file:.\errormessages.hs:2 - Inferred type is not general enough
> *** Expression : let {...} in (\y -> \x -> \z -> let {...} in x z) ()
> *** Expected type : (a -> b) -> a -> a
> *** Inferred type : (a -> a) -> a -> a
>
> GHC delivers its messages from in-the-middle of its typing process,
> which one hopes might give as little information as neccessary to
> identify the issue, without irrelevant context. It then tries to explain
> that information nicely, followed by some value-level context.
>
> Hugs delivers its messages from on-the-outside-looking-in, which one
> hopes might give the maximum potentially relevant information. It makes
> no attempt to cushion the blow.
>
> In practice, neither approach works all the time, and even for this
> tiny contrived example, one would have to engage in some "type
> debugging" (inserting type signatures, to trigger type-level printfs;
> commenting out large parts of code to see whether they contribute
> to the issue; ..) to figure it out.
>
> Note that both approaches are fairly precise in locating the error
> at the type level - it is the cross-reference from type to value level
> that runs into trouble, especially if the former is only implicit in the
> latter (which is why type debugging by adding signatures helps).
>
> > For really intricate type hacking, even this isn't enough because the
> > programming errors often happen far from where the type errors are
> > finally caught. In an ideal world, ghc could dump the entire proof
> > forest generated by inference, so an external tool[1] could be used to
> > browse through it and track the complete history of where inferred types
> > came from. This gives a partial view of the inferred types for a
> > compilation unit, something I've often wanted (rather than the manual
> > comment/reload/uncomment routine). The proof forest could even be used
> > as an interlingua over which people can write filters to generate
> > messages they find most helpful.
>
> Yes, most research papers on this ended up suggesting visual representations
> and separation between generating and presenting/querying error information.
>
> > Ah the joys of ideal worlds... ;)
>
> "if you don't have a dream, how you gonna have a dream come true?" (Bloody Mary)
>
> Claus
>
>
>
>
> ------------------------------
>
> Message: 5
> Date: Mon, 1 Jun 2009 20:00:09 +0100
> From: "Claus Reinke" <claus.reinke@talk21.com>
> Subject: Re: [Haskell-cafe] Re: Error message reform (was: Strange
> type errorwith associated type synonyms)
> To: <haskell-cafe@haskell.org>
> Message-ID: <8C39CAA7170D479D88613F7F77920916@cr3lt>
> Content-Type: text/plain; format=flowed; charset="iso-8859-1";
> reply-type=response
>
> > I once thought, that error messages must be configurable by libraries,
> > too. This would be perfect for EDSLs that shall be used by non-Haskellers.
>
> Yes, that is a problem.
>
> > But I have no idea how to design that.
>
> There was some work in that direction in the context of the Helium
> project. See the publication lists of Bastiaan Heeren and Jurriaan Hage:
>
> http://people.cs.uu.nl/bastiaan/#Publications
> http://www.cs.uu.nl/research/techreps/aut/jur.html
>
> Claus
>
>
>
>
> ------------------------------
>
> Message: 6
> Date: Mon, 1 Jun 2009 14:30:00 -0700 (PDT)
> From: michael rice <nowgate@yahoo.com>
> Subject: Re: [Haskell-cafe] Missing a "Deriving"?
> To: haskell-cafe@haskell.org, Daniel Fischer
> <daniel.is.fischer@web.de>
> Message-ID: <789959.35516.qm@web31103.mail.mud.yahoo.com>
> Content-Type: text/plain; charset="iso-8859-1"
>
> Got it.
>
> Thanks!
>
> Michael
>
> --- On Mon, 6/1/09, Daniel Fischer <daniel.is.fischer@web.de> wrote:
>
> From: Daniel Fischer <daniel.is.fischer@web.de>
> Subject: Re: [Haskell-cafe] Missing a "Deriving"?
> To: haskell-cafe@haskell.org
> Date: Monday, June 1, 2009, 1:51 PM
>
> Am Montag 01 Juni 2009 19:02:36 schrieb michael rice:
>
> > All good so far, but then tried to convert Failable from Computation to
> > Monad
> >
> >
> > instance Monad Failable where
> > return = Success
> > fail = Fail
> > >>= (Success x) f = f x
> > >>= (Fail s) _ = Fail s
> > mplus (Fail _) y = y
> > mplus x _ = x
> >
> >
> > and got the following error.
> >
> >
> > Prelude> :l graph5
> > [1 of 1] Compiling Main ( graph5.hs, interpreted )
> >
> > graph5.hs:34:4: parse error on input `>>='
> > Failed, modules loaded: none.
> > Prelude>
> >
>
> When you use an operator in prefix position, you must enclose it in parentheses, like you
> must enclose a function in backticks if you use it infix.
>
> So the definition of (>>=) should read
>
>
>     (>>=) (Success x) f = f x
>     (>>=) (Fail s) _ = Fail s
>
> or, defining it in infix position,
>     (Success x) >>= f = f x
>     (Fail s) >>= _ = Fail s
>
> >
> > Complete code follows.
> >
> > Michael
> >
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@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/20090601/5da24d47/attachment-0001.html
>
> ------------------------------
>
> Message: 7
> Date: Tue, 2 Jun 2009 02:14:08 +0200
> From: Sebastian Fischer <sebf@informatik.uni-kiel.de>
> Subject: Re: [Haskell-cafe] Bool as type class to serve EDSLs.
> To: haskell Cafe <haskell-cafe@haskell.org>
> Message-ID:
> <7E09E1CC-7C3A-4296-AE39-0148AD27A343@informatik.uni-kiel.de>
> Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes
>
> >>> Do you argue that overloading logical operations like this in
> >>> Haskell
> >>> sacrifices type safety? Could programs "go wrong" [1] that use such
> >>> abstractions?
> >> If I understand your point correctly, you are suggesting that such
> >> programs
> >> are still type safe.
>
> My asking was really meant as a question to find out what Henning
> meant when he talked about type safety.
>
> >> I agree with the claim that such features are detrimental in
> >> practice though.
>
> I also feel uncomfortable about such features, but the problem seems
> to be different from type safety. Maybe it is more about
> predictability. For example, if '1 + 23 = 24' and '1 + "23" = "123"'
> this can lead to confusion although using overloading this could be
> done in Haskell.
>
> That the compiler is able to figure out a correct instantiation of an
> overloaded operation does not mean that it is easy for the programmer
> too. And if it is not, programs are hard to understand.
>
> >> Instead of lumping it with type safety,
> >> then what do we call it? I think I've heard of languages that do
> >> such
> >> conversions as "weakly" typed. Really the issue is with implicit
> >> conversions, right?
> >
> > Isn't it merely a matter of balance? In order for typed programs not
> > to go "wrong", one has to define "right" and "wrong", and devise a
> > type
> > system that rules out anything that might go "wrong", usually at the
> > expense of some programs that might go "right".
>
> I had in mind "causes a run-time error" as definition of "goes wrong".
> But this simple view may well be inaccurate.
>
> > Advanced type system features like overloading take that unused
> > space and devise ways to redirect code that would go "wrong" (in
> > simpler systems) to go "right" in useful new ways (eg: adding two
> > functions or matrices or .. does not have to be "wrong", there are
> > interpretations in which all of these make perfect sense, and
> > Haskell can express many
> > of them).
> >
> > What is happening then is that more and more of the previously "wrong"
> > space is filled up with meaningful ways of going "right", until
> > nearly every
> > syntactically valid program goes somewhere. That can make for an
> > extremely expressive and powerful language, but it renders the naive
> > notion of going "wrong" or "right" rather meaningless: "wrong" just
> > means we haven't figured out a meaningful way to interpret it, and
> > going "right" can easily be a far cry from where you wanted it to go.
>
> I (think I) agree with you. Overloading could give a meaning to almost
> everything. Not necessarily a sensible one, and judgements about what
> is sensible seem to differ among different people.
>
> Regardless of whether a specific overloading is *sensible*, wanting it
> to be *predictable* seems like a reasonable requirement which may be
> easier to agree on.
>
> Cheers,
> Sebastian
>
>
> --
> Underestimating the novelty of the future is a time-honored tradition.
> (D.G.)
>
>
>
>
>
> ------------------------------
>
> Message: 8
> Date: Tue, 2 Jun 2009 04:39:44 +0100
> From: Dan Cook <danielkcook@gmail.com>
> Subject: [Haskell-cafe] Checking a value against a passed-in
> constructor?
> To: haskell-cafe@haskell.org
> Message-ID: <B6FFA9DD-2CC5-424B-90FD-78AD3CEB5DA4@gmail.com>
> Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes
>
> Hi,
> (Relatively new to Haskell here ..)
>
> So I have the following:
>
> data MyVal = Atom String
> | Bool Bool
>
> And I want to do something like this
>
> check :: (Bool -> MyVal) -> MyVal -> True
> check f (f x) = True
> check _ _ = False
>
> What that means is I want to pass a MyVal constructor and a MyVal, and
> return True if the second argument was constructed with the first.
> More generally, I'd like to be able to do
>
> genCheck :: (* -> MyVal) -> MyVal -> True
> genCheck f (f x) = True
> genCheck _ _ = False
>
> So that I can pass in _any_ MyVal constructor and let the function
> just check if the second argument was constructed with the first,
> without caring which constructor it is.
>
> What is the preferred way to do this, since neither of those functions
> compile?
>
> Cheers,
> - Dan
>
>
> ------------------------------
>
> Message: 9
> Date: Mon, 1 Jun 2009 18:02:09 -0700
> From: Jason Dagit <dagit@codersbase.com>
> Subject: Re: [Haskell-cafe] Checking a value against a passed-in
> constructor?
> To: Dan Cook <danielkcook@gmail.com>
> Cc: haskell-cafe@haskell.org
> Message-ID:
> <b97f58860906011802h780d2597j75d140b67d9ad753@mail.gmail.com>
> Content-Type: text/plain; charset="iso-8859-1"
>
> Hi Dan,
>
> On Mon, Jun 1, 2009 at 8:39 PM, Dan Cook <danielkcook@gmail.com> wrote:
>
> > Hi,
> > (Relatively new to Haskell here ..)
> >
> > So I have the following:
> >
> > data MyVal = Atom String
> > | Bool Bool
> >
> > And I want to do something like this
> >
> > check :: (Bool -> MyVal) -> MyVal -> True
> > check f (f x) = True
> > check _ _ = False
>
>
> You may be confusing yourself here on one point. The type 'Bool' is already
> defined by the prelude, but the data constructor is not. So you are able to
> create a data constructor for MyVal that is called "Bool" and contains a
> Bool. I think this distinction is leading to the next probem I see. Type
> signatures have to contain types and not values in Haskell. 'True' is a
> value so it can't be placed in the type signature. The type of True is
> Bool. So I think you meant to ask about:
> check :: (Bool -> MyVal) -> MyVal -> Bool
>
> Now if you define this function the first parameter can be any function Bool
> -> MyVal, not just the data constructors of MyVal. Also, the type of Atom
> :: String -> MyVal so you can't even pass it to 'check'.
>
>
> >
> > What that means is I want to pass a MyVal constructor and a MyVal, and
> > return True if the second argument was constructed with the first. More
> > generally, I'd like to be able to do
> >
> > genCheck :: (* -> MyVal) -> MyVal -> True
> > genCheck f (f x) = True
> > genCheck _ _ = False
> >
> > So that I can pass in _any_ MyVal constructor and let the function just
> > check if the second argument was constructed with the first, without caring
> > which constructor it is.
>
>
> This strikes me as a job for template haskell, but the use of TH is beyond
> what I can explain :)
>
>
> >
> >
> > What is the preferred way to do this, since neither of those functions
> > compile?
>
>
> My preferred way, is just to define isAtom and isBool both with type MyVal
> -> Bool and use them where I need them. There are a number of tools to
> generate such things like DrIFT, TH, and maybe some others?
>
> I hope that helps,
> Jason
> -------------- next part --------------
> An HTML attachment was scrubbed...
> URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090601/5c6b3080/attachment-0001.html
>
> ------------------------------
>
> Message: 10
> Date: Mon, 1 Jun 2009 18:28:09 -0700 (PDT)
> From: michael rice <nowgate@yahoo.com>
> Subject: Re: [Haskell-cafe] Missing a "Deriving"?
> To: David Menendez <dave@zednenem.com>
> Cc: haskell-cafe@haskell.org, Miguel Mitrofanov
> <miguelimo38@yandex.ru>
> Message-ID: <585584.70758.qm@web31106.mail.mud.yahoo.com>
> Content-Type: text/plain; charset="iso-8859-1"
>
> Still stumped. Maybe and [] are in the same MonadPlus monad, but how do I make monad Failable understand mplus?
>
> I'm now getting this error upon loading:
>
>
> Prelude> :l graph5
> [1 of 1] Compiling Main             ( graph5.hs, interpreted )
>
> graph5.hs:36:4: `mplus' is not a (visible) method of class `Monad'
> Failed, modules loaded: none.
> Prelude>
>
>
>
> Complete code follows.
>
> Michael
>
> =========================
>
> import Monad
>
> data Failable a = Success a | Fail String deriving (Show)
>
> data Graph v e = Graph [(Int,v)] [(Int,Int,e)]
>
> {-
> class Computation c where
>     success :: a -> c a
>     failure :: String -> c a
>     augment :: c a -> (a -> c b) -> c b
>     combine :: c a -> c a -> c a
>
> instance Computation Maybe
> where
>     success = Just
>     failure = const Nothing
>     augment (Just x) f = f x
>     augment Nothing _ = Nothing
>     combine Nothing y = y
>     combine x _ = x
>
> instance Computation Failable where
>     success = Success
>     failure = Fail
>     augment (Success x) f = f x
>     augment (Fail s) _ = Fail s
>     combine (Fail _) y = y
>     combine x _ = x
> -}
>
> instance Monad Failable where
>     return = Success
>     fail = Fail
>     (>>=) (Success x) f = f x
>     (>>=) (Fail s) _ = Fail s
>     mplus (Fail _) y = y
>     mplus x _ = x
>
> {-
> instance Computation [] where
>     success a =
> [a]
>     failure = const []
>     augment l f = concat (map f l)
>     combine = (++)
>
>
> searchAll g@(Graph vl el) src dst
>     | src == dst = success [src]
>     | otherwise = search' el
>     where search' [] = failure "no path"
>           search' ((u,v,_):es)
>               | src == u = (searchAll g v dst `augment`
>                              (success . (u:)))
>                             `combine` search'
> es
>               | otherwise = search' es
> -}
>
> searchAll g@(Graph vl el) src dst
>     | src == dst = return [src]
>     | otherwise = search' el
>     where search' [] = fail "no path"
>           search' ((u,v,_):es)
>               | src == u = (searchAll g v dst >>=
>                              (return . (u:)))
>                             `mplus` search'
> es
>               | otherwise = search' es
>  
>
>
>
> -----Inline Attachment Follows-----
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@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/20090601/011280e3/attachment-0001.html
>
> ------------------------------
>
> Message: 11
> Date: Mon, 1 Jun 2009 21:33:47 -0400
> From: Ross Mellgren <rmm-haskell@z.odi.ac>
> Subject: Re: [Haskell-cafe] Missing a "Deriving"?
> To: michael rice <nowgate@yahoo.com>
> Cc: haskell-cafe Cafe <haskell-cafe@haskell.org>
> Message-ID: <D1CAFD83-E8E1-4466-85AF-6881461F79DB@z.odi.ac>
> Content-Type: text/plain; charset="us-ascii"
>
> mplus is a method of class MonadPlus, so you need to write it in a
> separate instance from the one for Monad, e.g.
>
> instance MonadPlus Failable where
> mplus = ...
>
> -Ross
>
> On Jun 1, 2009, at 9:28 PM, michael rice wrote:
>
> > Still stumped. Maybe and [] are in the same MonadPlus monad, but how
> > do I make monad Failable understand mplus?
> >
> > I'm now getting this error upon loading:
> >
> >
> > Prelude> :l graph5
> > [1 of 1] Compiling Main ( graph5.hs, interpreted )
> >
> > graph5.hs:36:4: `mplus' is not a (visible) method of class `Monad'
> > Failed, modules loaded: none.
> > Prelude>
> >
> >
> >
> > Complete code follows.
> >
> > Michael
> >
> > =========================
> >
> > import Monad
> >
> > data Failable a = Success a | Fail String deriving (Show)
> >
> > data Graph v e = Graph [(Int,v)] [(Int,Int,e)]
> >
> > {-
> > class Computation c where
> > success :: a -> c a
> > failure :: String -> c a
> > augment :: c a -> (a -> c b) -> c b
> > combine :: c a -> c a -> c a
> >
> > instance Computation Maybe where
> > success = Just
> > failure = const Nothing
> > augment (Just x) f = f x
> > augment Nothing _ = Nothing
> > combine Nothing y = y
> > combine x _ = x
> >
> > instance Computation Failable where
> > success = Success
> > failure = Fail
> > augment (Success x) f = f x
> > augment (Fail s) _ = Fail s
> > combine (Fail _) y = y
> > combine x _ = x
> > -}
> >
> > instance Monad Failable where
> > return = Success
> > fail = Fail
> > (>>=) (Success x) f = f x
> > (>>=) (Fail s) _ = Fail s
> > mplus (Fail _) y = y
> > mplus x _ = x
> >
> > {-
> > instance Computation [] where
> > success a = [a]
> > failure = const []
> > augment l f = concat (map f l)
> > combine = (++)
> >
> >
> > searchAll g@(Graph vl el) src dst
> > | src == dst = success [src]
> > | otherwise = search' el
> > where search' [] = failure "no path"
> > search' ((u,v,_):es)
> > | src == u = (searchAll g v dst `augment`
> > (success . (u:)))
> > `combine` search' es
> > | otherwise = search' es
> > -}
> >
> > searchAll g@(Graph vl el) src dst
> > | src == dst = return [src]
> > | otherwise = search' el
> > where search' [] = fail "no path"
> > search' ((u,v,_):es)
> > | src == u = (searchAll g v dst >>=
> > (return . (u:)))
> > `mplus` search' es
> > | otherwise = search' es
> >
> >
> >
> > -----Inline Attachment Follows-----
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe@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/20090601/5ef740fd/attachment-0001.html
>
> ------------------------------
>
> Message: 12
> Date: Mon, 1 Jun 2009 18:40:43 -0700 (PDT)
> From: michael rice <nowgate@yahoo.com>
> Subject: Re: [Haskell-cafe] Missing a "Deriving"?
> To: Ross Mellgren <rmm-haskell@z.odi.ac>
> Cc: haskell-cafe Cafe <haskell-cafe@haskell.org>
> Message-ID: <903060.9615.qm@web31105.mail.mud.yahoo.com>
> Content-Type: text/plain; charset="iso-8859-1"
>
> Hi Ross,
>
> I thought of that, but return, fail, and >>= became "not visible" when I changed the instance declaration from Monad to MonadPlus.. Can Failable be in two instance declarations, one for Monad (giving it return, fail, and >>=) and one for MonadPlus (giving it mplus)?
>
> Michael
>
> --- On Mon, 6/1/09, Ross Mellgren <rmm-haskell@z.odi.ac> wrote:
>
> From: Ross Mellgren <rmm-haskell@z.odi.ac>
> Subject: Re: [Haskell-cafe] Missing a "Deriving"?
> To: "michael rice" <nowgate@yahoo.com>
> Cc: "haskell-cafe Cafe" <haskell-cafe@haskell.org>
> Date: Monday, June 1, 2009, 9:33 PM
>
> mplus is a method of class MonadPlus, so you need to write it in a separate instance from the one for Monad, e.g.
> instance MonadPlus Failable where    mplus = ...
> -Ross
> On Jun 1, 2009, at 9:28 PM, michael rice wrote:
> Still stumped. Maybe and [] are in the same MonadPlus monad, but how do I make monad Failable understand mplus?
>
> I'm now getting this error upon loading:
>
>
> Prelude> :l graph5
> [1 of 1] Compiling Main             ( graph5.hs, interpreted )
>
> graph5.hs:36:4: `mplus' is not a (visible) method of class `Monad'
> Failed, modules loaded: none.
> Prelude>
>
>
>
> Complete code follows.
>
> Michael
>
> =========================
>
> import Monad
>
> data Failable a = Success a | Fail String deriving (Show)
>
> data Graph v e = Graph [(Int,v)] [(Int,Int,e)]
>
> {-
> class Computation c where
>     success :: a -> c a
>     failure :: String -> c a
>     augment :: c a -> (a -> c b) -> c b
>     combine :: c a -> c a -> c a
>
> instance Computation Maybe where
>     success = Just
>     failure = const Nothing
>     augment (Just x) f = f x
>     augment Nothing _ = Nothing
>     combine Nothing y = y
>     combine x _ = x
>
> instance Computation Failable where
>     success = Success
>     failure = Fail
>     augment (Success x) f = f x
>     augment (Fail s) _ = Fail s
>     combine (Fail _) y = y
>     combine x _ = x
> -}
>
> instance Monad Failable where
>     return = Success
>     fail = Fail
>     (>>=) (Success x) f = f x
>     (>>=) (Fail s) _ = Fail s
>     mplus (Fail _) y = y
>     mplus x _ = x
>
> {-
> instance Computation [] where
>     success a = [a]
>     failure = const []
>     augment l f = concat (map f l)
>     combine = (++)
>
>
> searchAll g@(Graph vl el) src dst
>     | src == dst = success [src]
>     | otherwise = search' el
>     where search' [] = failure "no path"
>           search' ((u,v,_):es)
>               | src == u = (searchAll g v dst `augment`
>                              (success . (u:)))
>                             `combine` search' es
>               | otherwise = search' es
> -}
>
> searchAll g@(Graph vl el) src dst
>     | src == dst = return [src]
>     | otherwise = search' el
>     where search' [] = fail "no path"
>           search' ((u,v,_):es)
>               | src == u = (searchAll g v dst >>=
>                              (return . (u:)))
>                             `mplus` search' es
>               | otherwise = search' es
>  
>
> -----Inline Attachment Follows-----
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@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/20090601/452cfd72/attachment-0001.html
>
> ------------------------------
>
> Message: 13
> Date: Mon, 1 Jun 2009 21:43:34 -0400
> From: Ross Mellgren <rmm-haskell@z.odi.ac>
> Subject: Re: [Haskell-cafe] Missing a "Deriving"?
> To: michael rice <nowgate@yahoo.com>
> Cc: haskell-cafe Cafe <haskell-cafe@haskell.org>
> Message-ID: <CD9A895F-3EE5-48CD-84F3-E41AF288D5AD@z.odi.ac>
> Content-Type: text/plain; charset="us-ascii"
>
> Oh I wasn't clear -- you need multiple instance declarations for a
> given type (Failable, for example), one for each type class you're
> implementing.
>
> That is,
>
> instance Monad Failable where
> return = ...
> ...
>
>
> instance MonadPlus Failable where
> mplus = ...
> ...
>
> -Ross
>
> On Jun 1, 2009, at 9:40 PM, michael rice wrote:
>
> > Hi Ross,
> >
> > I thought of that, but return, fail, and >>= became "not visible"
> > when I changed the instance declaration from Monad to MonadPlus..
> > Can Failable be in two instance declarations, one for Monad (giving
> > it return, fail, and >>=) and one for MonadPlus (giving it mplus)?
> >
> > Michael
> >
> > --- On Mon, 6/1/09, Ross Mellgren <rmm-haskell@z.odi.ac> wrote:
> >
> > From: Ross Mellgren <rmm-haskell@z.odi.ac>
> > Subject: Re: [Haskell-cafe] Missing a "Deriving"?
> > To: "michael rice" <nowgate@yahoo.com>
> > Cc: "haskell-cafe Cafe" <haskell-cafe@haskell.org>
> > Date: Monday, June 1, 2009, 9:33 PM
> >
> > mplus is a method of class MonadPlus, so you need to write it in a
> > separate instance from the one for Monad, e.g.
> >
> > instance MonadPlus Failable where
> > mplus = ...
> >
> > -Ross
> >
> > On Jun 1, 2009, at 9:28 PM, michael rice wrote:
> >
> >> Still stumped. Maybe and [] are in the same MonadPlus monad, but
> >> how do I make monad Failable understand mplus?
> >>
> >> I'm now getting this error upon loading:
> >>
> >>
> >> Prelude> :l graph5
> >> [1 of 1] Compiling Main ( graph5.hs, interpreted )
> >>
> >> graph5.hs:36:4: `mplus' is not a (visible) method of class `Monad'
> >> Failed, modules loaded: none.
> >> Prelude>
> >>
> >>
> >>
> >> Complete code follows.
> >>
> >> Michael
> >>
> >> =========================
> >>
> >> import Monad
> >>
> >> data Failable a = Success a | Fail String deriving (Show)
> >>
> >> data Graph v e = Graph [(Int,v)] [(Int,Int,e)]
> >>
> >> {-
> >> class Computation c where
> >> success :: a -> c a
> >> failure :: String -> c a
> >> augment :: c a -> (a -> c b) -> c b
> >> combine :: c a -> c a -> c a
> >>
> >> instance Computation Maybe where
> >> success = Just
> >> failure = const Nothing
> >> augment (Just x) f = f x
> >> augment Nothing _ = Nothing
> >> combine Nothing y = y
> >> combine x _ = x
> >>
> >> instance Computation Failable where
> >> success = Success
> >> failure = Fail
> >> augment (Success x) f = f x
> >> augment (Fail s) _ = Fail s
> >> combine (Fail _) y = y
> >> combine x _ = x
> >> -}
> >>
> >> instance Monad Failable where
> >> return = Success
> >> fail = Fail
> >> (>>=) (Success x) f = f x
> >> (>>=) (Fail s) _ = Fail s
> >> mplus (Fail _) y = y
> >> mplus x _ = x
> >>
> >> {-
> >> instance Computation [] where
> >> success a = [a]
> >> failure = const []
> >> augment l f = concat (map f l)
> >> combine = (++)
> >>
> >>
> >> searchAll g@(Graph vl el) src dst
> >> | src == dst = success [src]
> >> | otherwise = search' el
> >> where search' [] = failure "no path"
> >> search' ((u,v,_):es)
> >> | src == u = (searchAll g v dst `augment`
> >> (success . (u:)))
> >> `combine` search' es
> >> | otherwise = search' es
> >> -}
> >>
> >> searchAll g@(Graph vl el) src dst
> >> | src == dst = return [src]
> >> | otherwise = search' el
> >> where search' [] = fail "no path"
> >> search' ((u,v,_):es)
> >> | src == u = (searchAll g v dst >>=
> >> (return . (u:)))
> >> `mplus` search' es
> >> | otherwise = search' es
> >>
> >>
> >>
> >> -----Inline Attachment Follows-----
> >>
> >> _______________________________________________
> >> Haskell-Cafe mailing list
> >> Haskell-Cafe@haskell.org
> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
> >>
> >> _______________________________________________
> >> Haskell-Cafe mailing list
> >> Haskell-Cafe@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/20090601/59913874/attachment-0001.html
>
> ------------------------------
>
> Message: 14
> Date: Mon, 1 Jun 2009 19:03:08 -0700 (PDT)
> From: michael rice <nowgate@yahoo.com>
> Subject: Re: [Haskell-cafe] Missing a "Deriving"?
> To: Ross Mellgren <rmm-haskell@z.odi.ac>
> Cc: haskell-cafe Cafe <haskell-cafe@haskell.org>
> Message-ID: <810042.76010.qm@web31101.mail.mud.yahoo.com>
> Content-Type: text/plain; charset="iso-8859-1"
>
> I didn't know I could do that. Works fine. Output below. Thanks!
>
> This is some pretty neat stuff, and I've only scratched the surface.
>
> Michael
>
> ===================
>
> [michael@localhost ~]$ ghci
> GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
> Loading package ghc-prim ... linking ... done.
> Loading package integer ... linking ... done.
> Loading package base ... linking ... done.
> Prelude> :l graph5
> [1 of 1] Compiling Main             ( graph5.hs, interpreted )
>
> graph5.hs:37:9:
>     Warning: No explicit method nor default method for `mzero'
>     In the instance declaration for `MonadPlus Failable'
> Ok, modules loaded: Main.
> *Main> let g = Graph [(1,'a'),(2,'b'),(3,'c'),(4,'d')] [(1,2,'p'),(2,3,'q'),(1,4,'r'),(4,3,'s')]
> *Main> searchAll g 1 3 :: Failable [Int]
> Success [1,2,3]
> *Main> searchAll g 3 1 :: Failable [Int]
> Fail "no path"
> *Main> searchAll g 1 3 :: Maybe [Int]
> Just [1,2,3]
> *Main> searchAll g 3 1 :: Maybe [Int]
> Nothing
> *Main> searchAll g 1 3 :: [[Int]]
> [[1,2,3],[1,4,3]]
> *Main> searchAll g 3 1 :: [[Int]]
> []
> *Main>
>
>
>
> --- On Mon, 6/1/09, Ross Mellgren <rmm-haskell@z.odi.ac> wrote:
>
> From: Ross Mellgren <rmm-haskell@z.odi.ac>
> Subject: Re: [Haskell-cafe] Missing a "Deriving"?
> To: "michael rice" <nowgate@yahoo.com>
> Cc: "haskell-cafe Cafe" <haskell-cafe@haskell.org>
> Date: Monday, June 1, 2009, 9:43 PM
>
> Oh I wasn't clear -- you need multiple instance declarations for a given type (Failable, for example), one for each type class you're implementing.
> That is, 
> instance Monad Failable where   return = ...   ...
>
> instance MonadPlus Failable where   mplus = ...   ...
> -Ross
> On Jun 1, 2009, at 9:40 PM, michael rice wrote:
> Hi Ross,
>
> I thought of that, but return, fail, and >>= became "not visible" when I changed the instance declaration from Monad to MonadPlus.. Can Failable be in two instance declarations, one for Monad (giving it return, fail, and >>=) and one for MonadPlus (giving it mplus)?
>
> Michael
>
> --- On Mon, 6/1/09, Ross Mellgren <rmm-haskell@z.odi.ac> wrote:
>
> From: Ross Mellgren <rmm-haskell@z.odi.ac>
> Subject: Re: [Haskell-cafe] Missing a "Deriving"?
> To: "michael rice" <nowgate@yahoo.com>
> Cc: "haskell-cafe Cafe" <haskell-cafe@haskell.org>
> Date: Monday, June 1, 2009, 9:33 PM
>
> mplus is a method of class MonadPlus, so you need to write it in a separate instance from the one for Monad, e.g.
> instance MonadPlus Failable where    mplus = ...
> -Ross
> On Jun 1, 2009, at 9:28 PM, michael rice wrote:
> Still stumped. Maybe and [] are in the same MonadPlus monad, but how do I make monad Failable understand mplus?
>
> I'm now getting this error upon loading:
>
>
> Prelude> :l graph5
> [1 of 1] Compiling Main             ( graph5.hs, interpreted )
>
> graph5.hs:36:4: `mplus' is not a (visible) method of class `Monad'
> Failed, modules loaded: none.
> Prelude>
>
>
>
> Complete code follows.
>
> Michael
>
> =========================
>
> import Monad
>
> data Failable a = Success a | Fail String deriving (Show)
>
> data Graph v e = Graph [(Int,v)] [(Int,Int,e)]
>
> {-
> class Computation c where
>     success :: a -> c a
>     failure :: String -> c a
>     augment :: c a -> (a -> c b) -> c b
>     combine :: c a -> c a -> c a
>
> instance Computation Maybe where
>     success = Just
>     failure = const Nothing
>     augment (Just x) f = f x
>     augment Nothing _ = Nothing
>     combine Nothing y = y
>     combine x _ = x
>
> instance Computation Failable where
>     success = Success
>     failure = Fail
>     augment (Success x) f = f x
>     augment (Fail s) _ = Fail s
>     combine (Fail _) y = y
>     combine x _ = x
> -}
>
> instance Monad Failable where
>     return = Success
>     fail = Fail
>     (>>=) (Success x) f = f x
>     (>>=) (Fail s) _ = Fail s
>     mplus (Fail _) y = y
>     mplus x _ = x
>
> {-
> instance Computation [] where
>     success a = [a]
>     failure = const []
>     augment l f = concat (map f l)
>     combine = (++)
>
>
> searchAll g@(Graph vl el) src dst
>     | src == dst = success [src]
>     | otherwise = search' el
>     where search' [] = failure "no path"
>           search' ((u,v,_):es)
>               | src == u = (searchAll g v dst `augment`
>                              (success . (u:)))
>                             `combine` search' es
>               | otherwise = search' es
> -}
>
> searchAll g@(Graph vl el) src dst
>     | src == dst = return [src]
>     | otherwise = search' el
>     where search' [] = fail "no path"
>           search' ((u,v,_):es)
>               | src == u = (searchAll g v dst >>=
>                              (return . (u:)))
>                             `mplus` search' es
>               | otherwise = search' es
>  
>
> -----Inline Attachment Follows-----
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@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/20090601/6ae3cae3/attachment.html
>
> ------------------------------
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
> End of Haskell-Cafe Digest, Vol 70, Issue 2
> *******************************************


Windows Live™: Keep your life in sync. Check it out.