[Haskell-cafe] show in monad

Damien Mattei damien.mattei at gmail.com
Thu Feb 28 10:00:18 UTC 2019


just for tracing the monad i have this :

import Control.Monad

import Data.Ratio
import Data.List (all)
import Debug.Trace

newtype Prob a = Prob { getProb :: [(a,Rational)] } deriving Show

instance Functor Prob where
    fmap f (Prob xs) = trace " Functor Prob "
                       Prob $ map (\(x,p) -> (f x,p)) xs


t


flatten :: Prob (Prob a) -> Prob a
flatten (Prob xs) = trace (" flatten " ++ show xs)
                    Prob $ concat $ map multAll xs
  where multAll (Prob innerxs,p) = trace " multAll "
                                   map (\(x,r) -> (x,p*r)) innerxs


instance Applicative Prob where
   pure = trace " Applicative Prob return " return
   (<*>) = trace " Applicative Prob ap " ap

instance Monad Prob where
  return x = trace " Monad Prob return "
             Prob [(x,1%1)]
  m >>= f = trace " Monad Prob >>= "
            flatten (fmap f m)
  fail _ = trace " Monad Prob fail "
           Prob []


{-
instance Applicative Prob where

  pure a = Prob [(a,1%1)]

  Prob fs <*> Prob as = Prob [(f a,x*y) | (f,x) <- fs, (a,y) <- as]


instance Monad Prob where

  Prob as >>= f = Prob [(b,x*y) | (a,x) <- as, let Prob bs = f a, (b,y) <-
bs]

-}



in this :

flatten :: Prob (Prob a) -> Prob a
flatten (Prob xs) = trace (" flatten " ++ show xs)
                    Prob $ concat $ map multAll xs
  where multAll (Prob innerxs,p) = trace " multAll "
                                   map (\(x,r) -> (x,p*r)) innerxs


i have this error:

[1 of 1] Compiling Main             ( monade.hs, interpreted )

monade.hs:22:43: error:
    • No instance for (Show a) arising from a use of ‘show’
      Possible fix:
        add (Show a) to the context of
          the type signature for:
            flatten :: forall a. Prob (Prob a) -> Prob a
    • In the second argument of ‘(++)’, namely ‘show xs’
      In the first argument of ‘trace’, namely ‘(" flatten " ++ show xs)’
      In the expression: trace (" flatten " ++ show xs) Prob
   |
22 | flatten (Prob xs) = trace (" flatten " ++ show xs)
   |                                           ^^^^^^^
Failed, no modules loaded.

how can i implement a show for xs ?
regards,
damien
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20190228/38cab47e/attachment.html>


More information about the Haskell-Cafe mailing list