Re: [Haskell-cafe] Missing a Deriving?

2009-06-01 Thread michael rice
I went back and tried to convert the YAHT example to Monad, importing Monad, 
commenting out all but the data descriptions and the searchAll function, and 
finally replacing success, failure, augment, and combine in the searchAll 
function with return, fail, =, and mplus.

*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 :: [[Int]]
[[1,2,3],[1,4,3]]
*Main searchAll g 1 3 :: Maybe [Int]
Just [1,2,3]
*Main searchAll g 3 1 :: Maybe [Int]
Nothing
*Main searchAll g 3 1 :: [[Int]]
[]


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


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
 


  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-06-01 Thread Daniel Fischer
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


Re: [Haskell-cafe] Missing a Deriving?

2009-06-01 Thread michael rice
Got it.

Thanks!

Michael

--- On Mon, 6/1/09, Daniel Fischer daniel.is.fisc...@web.de wrote:

From: Daniel Fischer daniel.is.fisc...@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



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-06-01 Thread michael rice
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


Re: [Haskell-cafe] Missing a Deriving?

2009-06-01 Thread Ross Mellgren
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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-06-01 Thread michael rice
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-hask...@z.odi.ac wrote:

From: Ross Mellgren rmm-hask...@z.odi.ac
Subject: Re: [Haskell-cafe] Missing a Deriving?
To: michael rice nowg...@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




  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-06-01 Thread Ross Mellgren
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-hask...@z.odi.ac wrote:

From: Ross Mellgren rmm-hask...@z.odi.ac
Subject: Re: [Haskell-cafe] Missing a Deriving?
To: michael rice nowg...@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





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-06-01 Thread michael rice
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

===

[mich...@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-hask...@z.odi.ac wrote:

From: Ross Mellgren rmm-hask...@z.odi.ac
Subject: Re: [Haskell-cafe] Missing a Deriving?
To: michael rice nowg...@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-hask...@z.odi.ac wrote:

From: Ross Mellgren rmm-hask...@z.odi.ac
Subject: Re: [Haskell-cafe] Missing a Deriving?
To: michael rice nowg...@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


   



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-06-01 Thread Ryan Ingram
 graph5.hs:37:9:
 Warning: No explicit method nor default method for `mzero'
 In the instance declaration for `MonadPlus Failable'

This warning is saying you didn't finish the declaration.

Try something like

instance MonadPlus Failable where
mplus (Fail _) y = y
mplus x _ = x

mzero = Fail mzero

Also, I'd use import Control.Monad instead of import Monad.

  -- ryan

On Mon, Jun 1, 2009 at 7:03 PM, michael rice nowg...@yahoo.com wrote:
 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

 ===

 [mich...@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-hask...@z.odi.ac wrote:

 From: Ross Mellgren rmm-hask...@z.odi.ac
 Subject: Re: [Haskell-cafe] Missing a Deriving?
 To: michael rice nowg...@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-hask...@z.odi.ac wrote:

 From: Ross Mellgren rmm-hask...@z.odi.ac
 Subject: Re: [Haskell-cafe] Missing a Deriving?
 To: michael rice nowg...@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

[Haskell-cafe] Missing a Deriving?

2009-05-30 Thread michael rice
The following code is from Section 8.4.2, pgs. 111-112 (PDF paging) of YAHT.

It compiles fine, but upon trying it I get the following error message.

It seems to be trying to 'Show' the Computation class but I'm not sure where to 
put the 'Deriving'.

Michael




Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( graph4.hs, interpreted )
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

interactive:1:0:
    No instance for (Show (c [Int]))
  arising from a use of `print' at interactive:1:0-14
    Possible fix: add an instance declaration for (Show (c [Int]))
    In a stmt of a 'do' expression: print it



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




  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread Miguel Mitrofanov
It's trying to 'Show' the 'c [Int]' type, but doesn't know which 'c'  
to use; so it's trying to find a generic instance, which doesn't  
exist. You can't fix this with 'deriving' or anything like this;  
instead, provide the type annotation like this:


*Main searchAll g 1 3 :: Maybe [Int]

On 31 May 2009, at 00:50, michael rice wrote:

The following code is from Section 8.4.2, pgs. 111-112 (PDF paging)  
of YAHT.


It compiles fine, but upon trying it I get the following error  
message.


It seems to be trying to 'Show' the Computation class but I'm not  
sure where to put the 'Deriving'.


Michael




Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( graph4.hs, interpreted )
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

interactive:1:0:
No instance for (Show (c [Int]))
  arising from a use of `print' at interactive:1:0-14
Possible fix: add an instance declaration for (Show (c [Int]))
In a stmt of a 'do' expression: print it



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


___
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


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread Ketil Malde
michael rice nowg...@yahoo.com writes:

 The following code is from Section 8.4.2, pgs. 111-112 (PDF paging) of YAHT.
 It compiles fine, but upon trying it I get the following error message.
 It seems to be trying to 'Show' the Computation class but I'm not sure where 
 to put the 'Deriving'.

My guess is that your expression is polymorphic, returning 
   Computation c = c [Int]

Since Haskell knows how to show this for both of the instances defined
for Computation (i.e. Maybe [Int] and [[Int]]), perhaps you could give
one of those as an explicit type signature?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread michael rice
Hi Miguel,

That works. but it gives just a single solution [1,2,3] when there are supposed 
to be two [[1,2,3],[1,4,3]]. Of course the code in YAHT may be in error.

Also, how the heck does Haskell decide which success, failure, augment, 
and combine to use in function searchAll, since there are five 
possibilities.

MIchael

--- On Sat, 5/30/09, Miguel Mitrofanov miguelim...@yandex.ru wrote:

From: Miguel Mitrofanov miguelim...@yandex.ru
Subject: Re: [Haskell-cafe] Missing a Deriving?
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Saturday, May 30, 2009, 5:36 PM

It's trying to 'Show' the 'c [Int]' type, but doesn't know which 'c' to use; so 
it's trying to find a generic instance, which doesn't exist. You can't fix this 
with 'deriving' or anything like this; instead, provide the type annotation 
like this:

*Main searchAll g 1 3 :: Maybe [Int]

On 31 May 2009, at 00:50, michael rice wrote:

 The following code is from Section 8.4.2, pgs. 111-112 (PDF paging) of YAHT.
 
 It compiles fine, but upon trying it I get the following error message.
 
 It seems to be trying to 'Show' the Computation class but I'm not sure where 
 to put the 'Deriving'.
 
 Michael
 
 
 
 
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 [1 of 1] Compiling Main             ( graph4.hs, interpreted )
 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
 
 interactive:1:0:
     No instance for (Show (c [Int]))
       arising from a use of `print' at interactive:1:0-14
     Possible fix: add an instance declaration for (Show (c [Int]))
     In a stmt of a 'do' expression: print it
 
 
 
 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 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
 
 
 ___
 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


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread David Menendez
On Sat, May 30, 2009 at 9:00 PM, michael rice nowg...@yahoo.com wrote:
 That works. but it gives just a single solution [1,2,3] when there are
 supposed to be two [[1,2,3],[1,4,3]]. Of course the code in YAHT may be in
 error.

Works for me.

*Main searchAll g 1 3 :: [[Int]]
[[1,2,3],[1,4,3]]
*Main searchAll g 1 3 :: Maybe [Int]
Just [1,2,3]
*Main searchAll g 1 3 :: Failable [Int]
Success [1,2,3]


 Also, how the heck does Haskell decide which success, failure,
 augment, and combine to use in function searchAll, since there are
 five possibilities.

*Main :t searchAll
searchAll :: (Computation c) = Graph t t1 - Int - Int - c [Int]

The way searchAll is written, the choice of which functions to use
depends on the type variable c. That's determined by the calling
context of searchAll, which is why you need to provide a type
signature when using it at the GHCi command line.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread Ryan Ingram
On Sat, May 30, 2009 at 6:33 PM, David Menendez d...@zednenem.com wrote:
 *Main :t searchAll
 searchAll :: (Computation c) = Graph t t1 - Int - Int - c [Int]

 The way searchAll is written, the choice of which functions to use
 depends on the type variable c. That's determined by the calling
 context of searchAll, which is why you need to provide a type
 signature when using it at the GHCi command line.

This is actually one of the most interesting and important things to
get about typeclasses; it's not *just* like an interface, because
the instance type can appear in the result of a function and *not* in
the arguments at all.

In contrast, in Java/C++, the method to use is always chosen by the
object being called; one could argue that all of COM is an attempt to
get around this problem.

Some examples:

 fromInteger :: Num a = Integer - a
 fromDynamic :: Typeable a = Dynamic - Maybe a

In both of these cases, the choice of which instance to use is made by
the caller, and often automatically by type inference:

 test x = case fromDynamic x of
Just s - s == hello
Nothing - False

Now (test $ toDynamic hello) = True, but (test $ toDynamic 'a') =
False.  Notice that I never directly specified what type fromDynamic
should return; but the case statement forces it to return Maybe
String, since I compare (s == hello)

  -- ryan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread michael rice
I figured out the [[Int]] case for myself, but hadn't considered the Failure 
case. Thanks.

In function searchAll, given a calling context Failable [Int],  for the line

   where search' [] = failure no path

failure would be Fail, a constructor that takes a String. Right?

But using either of the other two contexts, where failure equals either const 
Nothing or const [] it would seem like that same string argument no path 
would be passed to either Nothing or [], which doesn't make any sense. 
Explanation?

Michael

--- On Sat, 5/30/09, David Menendez d...@zednenem.com wrote:

From: David Menendez d...@zednenem.com
Subject: Re: [Haskell-cafe] Missing a Deriving?
To: michael rice nowg...@yahoo.com
Cc: Miguel Mitrofanov miguelim...@yandex.ru, haskell-cafe@haskell.org
Date: Saturday, May 30, 2009, 9:33 PM

On Sat, May 30, 2009 at 9:00 PM, michael rice nowg...@yahoo.com wrote:
 That works. but it gives just a single solution [1,2,3] when there are
 supposed to be two [[1,2,3],[1,4,3]]. Of course the code in YAHT may be in
 error.

Works for me.

*Main searchAll g 1 3 :: [[Int]]
[[1,2,3],[1,4,3]]
*Main searchAll g 1 3 :: Maybe [Int]
Just [1,2,3]
*Main searchAll g 1 3 :: Failable [Int]
Success [1,2,3]


 Also, how the heck does Haskell decide which success, failure,
 augment, and combine to use in function searchAll, since there are
 five possibilities.

*Main :t searchAll
searchAll :: (Computation c) = Graph t t1 - Int - Int - c [Int]

The way searchAll is written, the choice of which functions to use
depends on the type variable c. That's determined by the calling
context of searchAll, which is why you need to provide a type
signature when using it at the GHCi command line.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread michael rice
Belay that last question. I just realized that its the const function being 
used rather than a constant declaration in const Nothing and const [].

MIchael

--- On Sat, 5/30/09, David Menendez d...@zednenem.com wrote:

From: David Menendez d...@zednenem.com
Subject: Re: [Haskell-cafe] Missing a Deriving?
To: michael rice nowg...@yahoo.com
Cc: Miguel Mitrofanov miguelim...@yandex.ru, haskell-cafe@haskell.org
Date: Saturday, May 30, 2009, 9:33 PM

On Sat, May 30, 2009 at 9:00 PM, michael rice nowg...@yahoo.com wrote:
 That works. but it gives just a single solution [1,2,3] when there are
 supposed to be two [[1,2,3],[1,4,3]]. Of course the code in YAHT may be in
 error.

Works for me.

*Main searchAll g 1 3 :: [[Int]]
[[1,2,3],[1,4,3]]
*Main searchAll g 1 3 :: Maybe [Int]
Just [1,2,3]
*Main searchAll g 1 3 :: Failable [Int]
Success [1,2,3]


 Also, how the heck does Haskell decide which success, failure,
 augment, and combine to use in function searchAll, since there are
 five possibilities.

*Main :t searchAll
searchAll :: (Computation c) = Graph t t1 - Int - Int - c [Int]

The way searchAll is written, the choice of which functions to use
depends on the type variable c. That's determined by the calling
context of searchAll, which is why you need to provide a type
signature when using it at the GHCi command line.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread nowgate
Hi Ryan,

Is there something missing or mislabeled in your post, because I don't see any 
definition of toDynamic.

Michael

--- On Sun, 5/31/09, Ryan Ingram ryani.s...@gmail.com wrote:

From: Ryan Ingram ryani.s...@gmail.com
Subject: Re: [Haskell-cafe] Missing a Deriving?
To: David Menendez d...@zednenem.com
Cc: michael rice nowg...@yahoo.com, haskell-cafe@haskell.org, Miguel 
Mitrofanov miguelim...@yandex.ru
Date: Sunday, May 31, 2009, 12:45 AM

On Sat, May 30, 2009 at 6:33 PM, David Menendez d...@zednenem.com
 wrote:
 *Main :t searchAll
 searchAll :: (Computation c) = Graph t t1 - Int - Int - c [Int]

 The way searchAll is written, the choice of which functions to use
 depends on the type variable c. That's determined by the calling
 context of searchAll, which is why you need to provide a type
 signature when using it at the GHCi command line.

This is actually one of the most interesting and important things to
get about typeclasses; it's not *just* like an interface, because
the instance type can appear in the result of a function and *not* in
the arguments at all.

In contrast, in Java/C++, the method to use is always chosen by the
object being called; one could argue that all of COM is an attempt to
get around this problem.

Some examples:

 fromInteger :: Num a = Integer - a
 fromDynamic :: Typeable a = Dynamic - Maybe
 a

In both of these cases, the choice of which instance to use is made by
the caller, and often automatically by type inference:

 test x = case fromDynamic x of
    Just s - s == hello
    Nothing - False

Now (test $ toDynamic hello) = True, but (test $ toDynamic 'a') =
False.  Notice that I never directly specified what type fromDynamic
should return; but the case statement forces it to return Maybe
String, since I compare (s == hello)

  -- ryan



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread Ryan Ingram
Oops, it's called toDyn; from Data.Dynamic [1]

 toDyn :: Typeable a = a - Dynamic

  -- ryan

[1] http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Dynamic.html

On Sat, May 30, 2009 at 10:18 PM,  nowg...@yahoo.com wrote:
 Hi Ryan,

 Is there something missing or mislabeled in your post, because I don't see
 any definition of toDynamic.

 Michael

 --- On Sun, 5/31/09, Ryan Ingram ryani.s...@gmail.com wrote:

 From: Ryan Ingram ryani.s...@gmail.com
 Subject: Re: [Haskell-cafe] Missing a Deriving?
 To: David Menendez d...@zednenem.com
 Cc: michael rice nowg...@yahoo.com, haskell-cafe@haskell.org, Miguel
 Mitrofanov miguelim...@yandex.ru
 Date: Sunday, May 31, 2009, 12:45 AM

 On Sat, May 30, 2009 at 6:33 PM, David Menendez d...@zednenem.com wrote:
 *Main :t searchAll
 searchAll :: (Computation c) = Graph t t1 - Int - Int - c [Int]

 The way searchAll is written, the choice of which functions to use
 depends on the type variable c. That's determined by the calling
 context of searchAll, which is why you need to provide a type
 signature when using it at the GHCi command line.

 This is actually one of the most interesting and important things to
 get about typeclasses; it's not *just* like an interface, because
 the instance type can appear in the result of a function and *not* in
 the arguments at all.

 In contrast, in Java/C++, the method to use is always chosen by the
 object being called; one could argue that all of COM is an attempt to
 get around this problem.

 Some examples:

 fromInteger :: Num a = Integer - a
 fromDynamic :: Typeable a = Dynamic - Maybe a

 In both of these cases, the choice of which instance to use is made by
 the caller, and often automatically by type inference:

 test x = case fromDynamic x of
    Just s - s == hello
    Nothing - False

 Now (test $ toDynamic hello) = True, but (test $ toDynamic 'a') =
 False.  Notice that I never directly specified what type fromDynamic
 should return; but the case statement forces it to return Maybe
 String, since I compare (s == hello)

   -- ryan


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe