No subject
Sun Oct 23 10:51:38 CEST 2011
l be equal.=C2=A0</blockquote>
<div><br></div><div>This version works as expected:</div><div><div><br></di=
v><div>import System.Mem.StableName</div><div>import Control.Monad.State</d=
iv><div><br></div><div>eq :: a -> b -> IO Bool</div><div>
eq a b =3D do</div>
<div>=C2=A0 =C2=A0 =C2=A0 =C2=A0 =C2=A0 =C2=A0 =C2=A0pa <- makeStableNam=
e a</div><div>=C2=A0 =C2=A0 =C2=A0 =C2=A0 =C2=A0 =C2=A0 =C2=A0pb <- make=
StableName b</div><div>=C2=A0 =C2=A0 =C2=A0 =C2=A0 =C2=A0 =C2=A0 =C2=A0retu=
rn (hashStableName pa =3D=3D hashStableName pb)</div><div><br></div><div>su=
ccessor :: (Num a, Monad m) =3D> a -> m a</div>
<div>successor n =3D return (n+1)</div><div><br></div></div><div>-- =C2=A0m=
ain :: IO ()</div><div>-- =C2=A0main =3D do</div><div>-- =C2=A0 =C2=A0 =C2=
=A0 =C2=A0 b2 <- eq (successor :: Int -> State Int Int) (successor ::=
Int -> State Int Int)</div>
<div>-- =C2=A0 =C2=A0 =C2=A0 =C2=A0 b1 <- eq (successor :: Int -> May=
be Int) (successor :: Int -> Maybe Int)</div>
<div>-- =C2=A0 =C2=A0 =C2=A0 =C2=A0 print (show b1 ++ " " ++ show=
b2)</div><div><div><br></div><div>main :: IO ()</div><div>main =3D do</div=
></div><div>=C2=A0 =C2=A0 =C2=A0 =C2=A0b2 <- eq f2 f2</div><div>=C2=A0 =
=C2=A0 =C2=A0 =C2=A0b1 <- eq f1 f1</div><div>
<div>=C2=A0 =C2=A0 =C2=A0 =C2=A0print (show b1 ++ " " ++ show b2)=
</div>
</div><div>=C2=A0 =C2=A0where f1 =3D (successor :: Int -> Maybe Int)</di=
v><div>=C2=A0 =C2=A0 =C2=A0 =C2=A0 =C2=A0f2 =3D (successor :: Int -> Sta=
te Int Int)</div><div><br></div><div><br></div><div><br></div><div>hth,</di=
v><div>L.</div><div><br></div><div>
<br></div>
<div><br></div><br><div class=3D"gmail_quote"><div><div>On Tue, Jun 26, 201=
2 at 1:15 PM, Ismael Figueroa Palet <span dir=3D"ltr"><<a href=3D"mailto=
:ifigueroap at gmail.com" target=3D"_blank">ifigueroap at gmail.com</a>></span=
> wrote:<br>
</div></div><blockquote class=3D"gmail_quote" style=3D"margin:0 0 0 .8ex;bo=
rder-left:1px #ccc solid;padding-left:1ex"><div><div>
I'm using StableNames to have a notion of function equality, and I'=
m running into problems when using monadic functions.<div><br></div><div>Co=
nsider the code below, file Test.hs</div><div><br></div><div><div>import Sy=
stem.Mem.StableName</div>
<div>import Control.Monad.State</div><div><br></div><div>eq :: a -> b -&=
gt; IO Bool</div><div>eq a b =3D do</div><div>=C2=A0 =C2=A0 =C2=A0 =C2=A0 =
=C2=A0 =C2=A0 =C2=A0pa <- makeStableName a</div><div>=C2=A0 =C2=A0 =C2=
=A0 =C2=A0 =C2=A0 =C2=A0 =C2=A0pb <- makeStableName b</div><div>=C2=A0 =
=C2=A0 =C2=A0 =C2=A0 =C2=A0 =C2=A0 =C2=A0return (hashStableName pa =3D=3D h=
ashStableName pb)</div>
<div><br></div><div>successor :: (Num a, Monad m) =3D> a -> m a</div>=
<div>successor n =3D return (n+1)</div><div><br></div><div>main :: IO ()=C2=
=A0</div><div>main =3D do=C2=A0</div><div>=C2=A0 =C2=A0 =C2=A0 =C2=A0b1 <=
;- eq (successor :: Int -> Maybe Int) (successor :: Int -> Maybe Int)=
=C2=A0 =C2=A0 =C2=A0=C2=A0</div>
<div>=C2=A0 =C2=A0 =C2=A0 =C2=A0b2 <- eq (successor :: Int -> State I=
nt Int) (successor :: Int -> State Int Int)</div><div>=C2=A0 =C2=A0 =C2=
=A0 =C2=A0print (show b1 ++ " " ++ show b2)</div></div><div><br><=
/div><div>Running the code into ghci the result is "False False".=
There is some old post saying that this is due to the dictionary-passing s=
tyle for typeclasses, and compiling with optimizations improves the situati=
on.</div>
<div><br></div><div>Compiling with ghc --make -O Tests.hs and running the p=
rogram, the result is "True True", which is what I expect.</div><=
div>However, if I change main to be like the following:</div><div><br>
</div>
<div><div>main :: IO ()=C2=A0</div><div>main =3D do=C2=A0=C2=A0 =C2=A0 =C2=
=A0 =C2=A0</div><div>=C2=A0 =C2=A0 =C2=A0 =C2=A0b2 <- eq (successor :: I=
nt -> State Int Int) (successor :: Int -> State Int Int)</div><div>=
=C2=A0 =C2=A0 =C2=A0 =C2=A0b1 <- eq (successor :: Int -> Maybe Int) (=
successor :: Int -> Maybe Int) =C2=A0 =C2=A0 =C2=A0=C2=A0</div>
<div>=C2=A0 =C2=A0 =C2=A0 =C2=A0print (show b1 ++ " " ++ show b2)=
</div></div><div><br></div><div>i.e. just changing the sequential order, an=
d then compiling again with the same command, I get "True False",=
which is very confusing for me.</div>
<div>Similar situations happens when using the state monad transformer, and=
manually built variations of it.=C2=A0</div><div><br></div><div>It sounds =
the problem is with hidden closures created somewhere that do not point to =
the same memory locations, so StableNames yields false for that cases, but =
it is not clear to me under what circumstances this situation happens. Is t=
here other way to get some approximation of function equality? or a way to =
"configure" the behavior of StableNames in presence of class cons=
traints?</div>
<div><br></div><div>I'm using the latests Haskell Platform on OS X Lion=
, btw.</div><div><br></div><div>Thanks=EF=9C=A9</div><span><font color=3D"#=
888888"><div><div><div><br></div>-- <br>Ismael<br><br>
</div></div>
</font></span><br></div></div>_____________________________________________=
__<br>
Haskell-Cafe mailing list<br>
<a href=3D"mailto:Haskell-Cafe at haskell.org" target=3D"_blank">Haskell-Cafe@=
haskell.org</a><br>
<a href=3D"http://www.haskell.org/mailman/listinfo/haskell-cafe" target=3D"=
_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
<br></blockquote></div><br></div>
</blockquote></div><br><br clear=3D"all"><div><br></div></div></div><span><=
font color=3D"#888888">-- <br>Ismael<br><br>
</font></span></div>
</blockquote></div><br></div></div></div></div></div>
</blockquote></div></div></div><span><font color=3D"#888888"><br><br clear=
=3D"all"><div><br></div>-- <br>Ismael<br><br>
</font></span></blockquote></div><br></div></div></div></div></div>
</blockquote></div><br></div></div></div>
</blockquote></div><br><br clear=3D"all"><div><br></div></div></div><span c=
lass=3D"HOEnZb"><font color=3D"#888888">-- <br>Ismael<br><br>
</font></span></blockquote></div><br></div>
--90e6ba5bcaeb78acaa04c362bbe8--
More information about the Haskell-Cafe
mailing list