<div dir="ltr"><div dir="ltr"><div dir="ltr"><div class="gmail_default" style="font-size:large">it's not clear, redaing back the thread it seems that it is not possible in a monad with the bind operator to have a display with show and now that adding the constraint and changing the type of flatten will do it, so i change the definition of flatten but it does not compile:</div><div class="gmail_default" style="font-size:large">flatten :: Show a => Prob (Prob a) -> Prob a<br>flatten (Prob xs) = trace (" flatten " ++ (show xs))<br> Prob $ concat $ map multAll xs<br> where multAll (Prob innerxs,p) = trace (" multAll p= " ++ (show p) ++ " ")<br> map (\(x,r) -> (x,p*r)) innerxs </div><div class="gmail_default" style="font-size:large"><br></div><div class="gmail_default" style="font-size:large">Prelude> :load monade.hs<br>[1 of 1] Compiling Main ( monade.hs, interpreted )<br><br>monade.hs:37:13: error:<br> • No instance for (Show b) arising from a use of ‘flatten’<br> Possible fix:<br> add (Show b) to the context of<br> the type signature for:<br> (>>=) :: forall a b. Prob a -> (a -> Prob b) -> Prob b<br> • In the second argument of ‘trace’, namely ‘flatten’<br> In the expression: trace " Monad Prob >>= " flatten (fmap f m)<br> In an equation for ‘>>=’:<br> m >>= f = trace " Monad Prob >>= " flatten (fmap f m)<br> |<br>37 | flatten (fmap f m)<br> | ^^^^^^^<br>Failed, no modules loaded.<br></div><div class="gmail_default" style="font-size:large"><br></div><div class="gmail_default" style="font-size:large">Damien<br></div><div class="gmail_default" style="font-size:large"><br></div></div></div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Thu, Feb 28, 2019 at 4:58 PM Jos Kusiek <<a href="mailto:jos.kusiek@tu-dortmund.de">jos.kusiek@tu-dortmund.de</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex">
<div bgcolor="#FFFFFF">
You do not need to change the Show instance. The one generated by
deriving Show is fine. As I said, you need to change the type of
flatten and add the constraint.<br>
<br>
flatten :: Show a => Prob (Prob a) -> Prob a<br>
<br>
<div class="gmail-m_-3794938751638412599moz-cite-prefix">On 28.02.19 15:30, Damien Mattei wrote:<br>
</div>
<blockquote type="cite">
<div dir="ltr">
<div dir="ltr">
<div dir="ltr">
<div class="gmail_default" style="font-size:large">even with
a definition of show i can not use it in flatten:</div>
<div class="gmail_default" style="font-size:large">import
Control.Monad<br>
<br>
import Data.Ratio<br>
import Data.List (all)<br>
import Debug.Trace<br>
<br>
newtype Prob a = Prob { getProb :: [(a,Rational)] }--
deriving Show<br>
<br>
<br>
<br>
instance Show a => Show (Prob a) where<br>
show (Prob [(x,r)]) = ((show x) ++ " _ " ++ (show r))<br>
<br>
<br>
instance Functor Prob where<br>
fmap f (Prob xs) = trace " Functor Prob "<br>
Prob $ map (\(x,p) -> (f x,p))
xs<br>
<br>
<br>
<br>
<br>
flatten :: Prob (Prob a) -> Prob a<br>
flatten (Prob xs) = trace (" flatten " ++ (show xs))<br>
Prob $ concat $ map multAll xs<br>
where multAll (Prob innerxs,p) = trace (" multAll p= "
++ (show p) ++ " ")<br>
map (\(x,r) ->
(x,p*r)) innerxs </div>
<div class="gmail_default" style="font-size:large"><br>
</div>
<div class="gmail_default" style="font-size:large">monade.hs:23:44:
error:<br>
• No instance for (Show a) arising from a use of
‘show’<br>
Possible fix:<br>
add (Show a) to the context of<br>
the type signature for:<br>
flatten :: forall a. Prob (Prob a) -> Prob
a<br>
• In the second argument of ‘(++)’, namely ‘(show xs)’<br>
In the first argument of ‘trace’, namely<br>
‘(" flatten " ++ (show xs))’<br>
In the expression: trace (" flatten " ++ (show xs))
Prob<br>
|<br>
23 | flatten (Prob xs) = trace (" flatten " ++ (show xs))<br>
| ^^^^^^^<br>
Failed, no modules loaded.</div>
<div class="gmail_default" style="font-size:large"><br>
</div>
<div class="gmail_default" style="font-size:large">it seems
show i defined is not in the context of flatten???</div>
<div class="gmail_default" style="font-size:large"><br>
</div>
<div class="gmail_default" style="font-size:large">damien<br>
</div>
<div class="gmail_default" style="font-size:large"><br>
</div>
<div class="gmail_default" style="font-size:large"><br>
</div>
</div>
</div>
</div>
<br>
<div class="gmail_quote">
<div dir="ltr" class="gmail_attr">On Thu, Feb 28, 2019 at 12:57
PM Jos Kusiek <<a href="mailto:jos.kusiek@tu-dortmund.de" target="_blank">jos.kusiek@tu-dortmund.de</a>>
wrote:<br>
</div>
<blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex">
<div bgcolor="#FFFFFF"> You simply cannot do that. To be more
precise, you cannot use show inside the bind operator on
Prob (but you could use it in flatten). Deriving Show
creates a Show instance which looks something like that:<br>
<br>
instance Show a => Show (Prob a) where ...<br>
<br>
This instance needs "a" to instanciate Show, so you can only
use show with Prob types, where "a" is an instance of Show
itself, e. g. Prob Int. Your flatten function does not
guarantee that "a" is an instance of Show. The type says,
any type for "a" will do it. You can easily restrict that
with a class constraint:<br>
<br>
flatten :: Show a => Prob (Prob a) -> Prob a<br>
<br>
But now you have a problem with the bind operator. You can
no longer use flatten here. The bind operator for Prob has
the following type:<br>
<br>
(>>=) :: Prob a -> (a -> Prob b) -> Prob b<br>
<br>
There are no constraints here and you cannot add any
constraints. The type is predefined by the Monad class. So
it is not guaranteed, that this Prob type has a show
function and you cannot guarantee it in any way. So you
cannot use show on your first parameter type (Prob a) or
your result type (Prob b) inside the bind or any function
that is called by bind.<br>
<br>
<div class="gmail-m_-3794938751638412599gmail-m_-5752800832379613477moz-cite-prefix">On
28.02.19 11:00, Damien Mattei wrote:<br>
</div>
<blockquote type="cite">
<div dir="ltr">
<div dir="ltr">
<div dir="ltr">
<div class="gmail_default" style="font-size:large">just
for tracing the monad i have this :</div>
<div class="gmail_default" style="font-size:large"><br>
</div>
<div class="gmail_default" style="font-size:large">import
Control.Monad<br>
<br>
import Data.Ratio<br>
import Data.List (all)<br>
import Debug.Trace<br>
<br>
newtype Prob a = Prob { getProb :: [(a,Rational)]
} deriving Show<br>
<br>
instance Functor Prob where<br>
fmap f (Prob xs) = trace " Functor Prob "<br>
Prob $ map (\(x,p) -> (f
x,p)) xs<br>
<br>
<br>
t<br>
<br>
<br>
flatten :: Prob (Prob a) -> Prob a<br>
flatten (Prob xs) = trace (" flatten " ++ show xs)<br>
Prob $ concat $ map multAll xs<br>
where multAll (Prob innerxs,p) = trace " multAll
"<br>
map (\(x,r)
-> (x,p*r)) innerxs <br>
<br>
<br>
instance Applicative Prob where<br>
pure = trace " Applicative Prob return " return<br>
(<*>) = trace " Applicative Prob ap " ap<br>
<br>
instance Monad Prob where<br>
return x = trace " Monad Prob return "<br>
Prob [(x,1%1)]<br>
m >>= f = trace " Monad Prob >>= "<br>
flatten (fmap f m)<br>
fail _ = trace " Monad Prob fail "<br>
Prob []<br>
<br>
<br>
{-<br>
instance Applicative Prob where<br>
<br>
pure a = Prob [(a,1%1)]<br>
<br>
Prob fs <*> Prob as = Prob [(f a,x*y) |
(f,x) <- fs, (a,y) <- as]<br>
<br>
<br>
instance Monad Prob where<br>
<br>
Prob as >>= f = Prob [(b,x*y) | (a,x)
<- as, let Prob bs = f a, (b,y) <- bs]<br>
<br>
-}</div>
<div class="gmail_default" style="font-size:large"><br>
</div>
<div class="gmail_default" style="font-size:large"><br>
</div>
<div class="gmail_default" style="font-size:large"><br>
</div>
<div class="gmail_default" style="font-size:large">in
this :</div>
<div class="gmail_default" style="font-size:large"><br>
</div>
<div class="gmail_default" style="font-size:large">flatten
:: Prob (Prob a) -> Prob a<br>
flatten (Prob xs) = trace (" flatten " ++ show xs)<br>
Prob $ concat $ map multAll xs<br>
where multAll (Prob innerxs,p) = trace " multAll
"<br>
map (\(x,r)
-> (x,p*r)) innerxs <br>
</div>
<div class="gmail_default" style="font-size:large"><br>
</div>
<div class="gmail_default" style="font-size:large"><br>
</div>
<div class="gmail_default" style="font-size:large">i
have this error:</div>
<div class="gmail_default" style="font-size:large"><br>
</div>
<div class="gmail_default" style="font-size:large">[1
of 1] Compiling Main ( monade.hs,
interpreted )<br>
<br>
monade.hs:22:43: error:<br>
• No instance for (Show a) arising from a use
of ‘show’<br>
Possible fix:<br>
add (Show a) to the context of<br>
the type signature for:<br>
flatten :: forall a. Prob (Prob a)
-> Prob a<br>
• In the second argument of ‘(++)’, namely
‘show xs’<br>
In the first argument of ‘trace’, namely ‘("
flatten " ++ show xs)’<br>
In the expression: trace (" flatten " ++
show xs) Prob<br>
|<br>
22 | flatten (Prob xs) = trace (" flatten " ++
show xs)<br>
|
^^^^^^^<br>
Failed, no modules loaded.<br>
</div>
<div class="gmail_default" style="font-size:large"><br>
</div>
<div class="gmail_default" style="font-size:large">how
can i implement a show for xs ?</div>
<div class="gmail_default" style="font-size:large">regards,</div>
<div class="gmail_default" style="font-size:large">damien<br>
</div>
</div>
</div>
</div>
<br>
<fieldset class="gmail-m_-3794938751638412599gmail-m_-5752800832379613477mimeAttachmentHeader"></fieldset>
<pre class="gmail-m_-3794938751638412599gmail-m_-5752800832379613477moz-quote-pre">_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
<a class="gmail-m_-3794938751638412599gmail-m_-5752800832379613477moz-txt-link-freetext" href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a>
Only members subscribed via the mailman list are allowed to post.</pre>
</blockquote>
<br>
<pre class="gmail-m_-3794938751638412599gmail-m_-5752800832379613477moz-signature" cols="72">--
Dipl.-Inf. Jos Kusiek
Technische Universität Dortmund
Fakultät 4 - Informatik / Lehrstuhl 1 - Logik in der Informatik
Otto-Hahn-Straße 12, Raum 3.020
44227 Dortmund
Tel.: +49 231-755 7523</pre>
</div>
</blockquote>
</div>
</blockquote>
<br>
<pre class="gmail-m_-3794938751638412599moz-signature" cols="72">--
Dipl.-Inf. Jos Kusiek
Technische Universität Dortmund
Fakultät 4 - Informatik / Lehrstuhl 1 - Logik in der Informatik
Otto-Hahn-Straße 12, Raum 3.020
44227 Dortmund
Tel.: +49 231-755 7523</pre>
</div>
</blockquote></div>