[Haskell-cafe] Missing a "Deriving"?

Miguel Mitrofanov miguelimo38 at yandex.ru
Sat May 30 17:36:44 EDT 2009


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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list