[Haskell-cafe] example of monad from http://learnyouahaskell.com not working

Yuji Yamamoto whosekiteneverfly at gmail.com
Wed Feb 27 10:09:56 UTC 2019


It's the one of the biggest changes of Haskell since LYHG was released.
As you guess, now any instance of Monad must be an instance of Applicative.

So you have to declare Prob as an instance of Applicative:

instance Applicative Prob where
   pure = ...
   f <*> x = ...


2019年2月27日(水) 18:56 Damien Mattei <damien.mattei at gmail.com>:

> i'm trying this example (see code below) from :
> http://learnyouahaskell.com/for-a-few-monads-more#making-monads
>
> when trying to compile this:
>
> import Data.Ratio
>
> newtype Prob a = Prob { getProb :: [(a,Rational)] } deriving Show
>
>
> instance Functor Prob where
>     fmap f (Prob xs) = Prob $ map (\(x,p) -> (f x,p)) xs
>
>
> thisSituation :: Prob (Prob Char)
> thisSituation = Prob
>     [( Prob [('a',1%2),('b',1%2)] , 1%4 )
>     ,( Prob [('c',1%2),('d',1%2)] , 3%4)
>     ]
>
> flatten :: Prob (Prob a) -> Prob a
> flatten (Prob xs) = Prob $ concat $ map multAll xs
>     where multAll (Prob innerxs,p) = map (\(x,r) -> (x,p*r)) innerxs
>
>
> instance Monad Prob where
>   return x = Prob [(x,1%1)]
>   m >>= f = flatten (fmap f m)
>   fail _ = Prob []
>
>
>
> l1 = Prob [('a',2%3),('b',1%3)]
>
> multAllExt :: (Prob a, Rational) -> [(a, Rational)]
> multAllExt (Prob innerxs,p) = map (\(x,r) -> (x,p*r)) innerxs
>
> --Main> :type multAllExt
> --multAllExt :: (Prob a, Rational) -> [(a, Rational)]
>
>
> --Main> multAllExt (l1,1 % 4)
> --[('a',1 % 6),('b',1 % 12)]
>
>
> i get this error:
>
> GHCi, version 8.4.3: http://www.haskell.org/ghc/  :? for help
> Prelude> :load monade.hs
> [1 of 1] Compiling Main             ( monade.hs, interpreted )
>
> monade.hs:21:10: error:
>     • No instance for (Applicative Prob)
>         arising from the superclasses of an instance declaration
>     • In the instance declaration for ‘Monad Prob’
>    |
> 21 | instance Monad Prob where
>    |          ^^^^^^^^^^
> Failed, no modules loaded.
>
> it fails when i add the last part of the example:
>
> instance Monad Prob where
>   return x = Prob [(x,1%1)]
>   m >>= f = flatten (fmap f m)
>   fail _ = Prob []
>
>
> seems the Monad needs an instance of the Applicative to be instanciated...
>
> what is wrong?
>
> regards,
> Damien
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.



-- 
山本悠滋
twitter: https://twitter.com/igrep
GitHub: https://github.com/igrep
GitLab: https://gitlab.com/igrep
Facebook: http://www.facebook.com/igrep
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20190227/ee8eecd0/attachment.html>


More information about the Haskell-Cafe mailing list