[Haskell-beginners] Using Debug.Trace
Daniel Fischer
daniel.is.fischer at web.de
Sun Jan 31 05:33:00 EST 2010
Am Sonntag 31 Januar 2010 10:25:58 schrieb legajid:
> Hi,
>
> Starting with trace, i have trouble with my calcul'' function while
> calcul' is ok.
> When afftrace in calcul'' is commented, the program compiles.
> When uncommented ( afftrace (" calcul'' vide") ), i get
> the following messages :
>
> ------------------------------------------------------------------------
>------------------- *Main> :r
> [1 of 1] Compiling Main ( sud3c.hs, interpreted )
>
> sud3c.hs:62:3:
> Couldn't match expected type `[Char]'
> against inferred type `(Plateau, Char)'
> In a stmt of a 'do' expression: afftrace (" calcul'' vide")
> In the expression:
> do afftrace (" calcul'' vide")
> (pxv, False)
> In the definition of `calcul''':
> calcul'' pxv _ []
> = do afftrace (" calcul'' vide")
> (pxv, False)
> Failed, modules loaded: none.
> ------------------------------------------------------------------------
>-------------------
>
> I don't understand why, in calcul', it's ok and why, in calcul'', it's
> problematic. Because return value of calcul'' is a tuple ?
You defined
> afftrace x= if modetrace then trace x " "
> else " "
If you ask ghci the type of that, you'll get
ghci> :t afftrace
afftrace :: String -> [Char]
(or afftrace :: [Char] -> [Char], or String -> String)
since
ghci> :t trace
trace :: String -> a -> a
Now you use afftrace in a do-block, which means "afftrace x" must have type
(Monad m) => m a
for some m and a.
Well, afftrace x has type [Char], so m is [] and a is Char, fine.
That means you can use afftrace in any calculation returning a list of some
kind (outside of do-blocks, also in other calculations).
But calcul'' doesn't return a list, it returns a pair. So
calcul'' pxv _ [] = afftrace (" calcul'' vide") >> (pxv,False)
, which is what the first equation of calcul'' is desugared to, isn't well
typed.
(>>) :: Monad m => m a -> m b -> m b
afftrace " calcul'' vide" :: [] Char -- m === [], a === Char
(pxv,False) :: (,) Plateau Bool -- m === ((,) Plateau), b === Bool
(actually, ((,) Plateau) is indeed a monad, but it's a different one from
[], so the expression is not well typed).
You could
- modify calcul'' to return [(Plateau,Bool)]
- not use do-blocks just for the sake of tracing and restructure your code
(I recommend the second)
infixl 0 `debug`
debug = flip trace
calcul' pxv [] = pxv `debug` " Calcul' vide"
calcul' pxv (c:cs)
| ok1 = calcul' xv1 cs `debug` " Calcul' suite"
| otherwise = pxv `debug` " Calcul' pas de valeur"
where
vallib = [1 .. length pxv] ++ [5 .. 7]
nbvlib = length vallib
(xv1,ok1) = calcul'' pxv c vallib `debug` (" " ++ show xv1)
`debug` (" Calcul' ok1=" ++ show ok1 ++ "
c:cs= " ++ show (c:cs))
calcul'' pxv _ [] = (pxv,False) `debug` " calcul'' vide"
calcul'' pxv c (li:lis)
| False `debug` " " ++ show pvx ++ "..." = undefined
| li == 4 || li `elem` pxv = calcul'' pxv c lis `debug` "quoi?"
| otherwise = (calcul'' pxv c li,True) `debug` " calcul'''"
Now the code reads more natural (except for the "False `debug` ... " to
produce general debugging output), and removing the debugging output isn't
any harder.
>
> When my program is ok, should i remove all trace instructions (and
> associated do commands too) or just set my modetrace value to False ?
>
Remove, resp. comment out.
>
> Thanks for helping,
> Didier
>
> Below my code :
>
>
> calcul' :: Plateau -> [Cellule] -> Plateau
> calcul' pxv [] = do
> afftrace (" Calcul' vide")
> pxv
> calcul' pxv (c:cs)= do
> afftrace (" Calcul' ok1="++show ok1++" c:cs= "++show
> (c:cs)) afftrace (" "++show xv1)
>
> if ok1 then do
> afftrace (" Calcul' suite")
> calcul' xv1 cs
> else do
> afftrace (" Calcul' pas de valeur")
> pxv
> where
> vallib=[1..length pxv]++[5..7]
> nbvlib=length vallib
> (xv1,ok1)=calcul'' pxv c vallib
>
>
>
> calcul'' :: Plateau -> Cellule -> [Valeur] -> (Plateau, Bool)
> calcul'' pxv _ [] = do
> --afftrace (" calcul'' vide")
> (pxv, False)
>
> calcul'' pxv c (li : lis) = do
> --afftrace (" "++show pxv)
> --afftrace (" "++show c ++ " "++show(li:lis))
> v2
> where
> v2= if (elem li pxv || li==4)
> then
> calcul'' pxv c lis
> else do
> --afftrace (" calcul'''")
> (calcul''' pxv c li, True)
>
> calcul''' :: Plateau -> Cellule -> Valeur -> Plateau
> calcul''' pxv c li =
> take (c-1) pxv ++ [li] ++ drop c pxv
>
> afftrace x= if modetrace then trace x " "
> else " "
More information about the Beginners
mailing list