
Hi, i wrote a program that doesn't behave as i wanted. So i tried to putStrLn my data structures to see what happened. Since i did this, all my functions changed type, so i had to modify them (main and calcul : use <- instead of let , add returns) and so on for each function called. Debugging this way causes more trouble than it should save. What is the way to trace data thru function recursive calls without changing program structures? Is putStrLn a good idea ? I'm not used to ghci debug and i find it hard to manage (:break, :trace, :cont ...). Is the 'debugged' version as efficient as the first one, due to impure functional code? What if i want to remove 'debug code' ? Should i modify back my functions ? Here are two very simplified versions of my program, the first one without 'trace', the second modified to include putStrLn as wanted. Thanks in advance, Didier First version ------------- main=do let valeurs=[0,1,3,0] let (valeurs_new)=calcul valeurs afficher_resultat valeurs afficher_resultat valeurs_new calcul :: [Int] -> [Int] calcul xv | nblibr == 0 = map (*2) xv | otherwise = map (+1) xv where libres = [ x | x <- [1..length xv] , xv !! (x-1) == 0] nblibr=length libres afficher_resultat xv = do putStrLn (show xv) Second version ---------------- main=do let valeurs=[0,1,3,0] valeurs_new <- calcul valeurs afficher_resultat valeurs afficher_resultat valeurs_new calcul :: [Int] -> IO [Int] calcul xv | nblibr == 0 = do putStrLn "ok" return (map (*2) xv) | otherwise = return (map (+1) xv) where libres = [ x | x <- [1..length xv] , xv !! (x-1) == 0] nblibr=length libres afficher_resultat xv = do putStrLn (show xv)

I think you want the Debug.Trace module. The documentation is available at
http://haskell.org/ghc/docs/latest/html/libraries/base/Debug-Trace.html.
Let me know if you have any questions,
Michael
On Sun, Jan 31, 2010 at 12:00 AM, legajid
Hi,
i wrote a program that doesn't behave as i wanted. So i tried to putStrLn my data structures to see what happened. Since i did this, all my functions changed type, so i had to modify them (main and calcul : use <- instead of let , add returns) and so on for each function called. Debugging this way causes more trouble than it should save.
What is the way to trace data thru function recursive calls without changing program structures? Is putStrLn a good idea ? I'm not used to ghci debug and i find it hard to manage (:break, :trace, :cont ...). Is the 'debugged' version as efficient as the first one, due to impure functional code? What if i want to remove 'debug code' ? Should i modify back my functions ?
Here are two very simplified versions of my program, the first one without 'trace', the second modified to include putStrLn as wanted.
Thanks in advance, Didier
First version -------------
main=do let valeurs=[0,1,3,0] let (valeurs_new)=calcul valeurs afficher_resultat valeurs afficher_resultat valeurs_new
calcul :: [Int] -> [Int] calcul xv | nblibr == 0 = map (*2) xv | otherwise = map (+1) xv where libres = [ x | x <- [1..length xv] , xv !! (x-1) == 0] nblibr=length libres
afficher_resultat xv = do putStrLn (show xv)
Second version ----------------
main=do let valeurs=[0,1,3,0]
valeurs_new <- calcul valeurs
afficher_resultat valeurs afficher_resultat valeurs_new
calcul :: [Int] -> IO [Int] calcul xv | nblibr == 0 = do putStrLn "ok" return (map (*2) xv) | otherwise = return (map (+1) xv) where libres = [ x | x <- [1..length xv] , xv !! (x-1) == 0] nblibr=length libres
afficher_resultat xv = do putStrLn (show xv)
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Am Samstag 30 Januar 2010 23:01:57 schrieb Michael Snoyman:
I think you want the Debug.Trace module. The documentation is available at http://haskell.org/ghc/docs/latest/html/libraries/base/Debug-Trace.html.
Yes. Definitely. As a further tip: import Debug.Trace infixl 0 `debug` debug :: a -> String -> a debug = flip trace (of course you can call it something else) With 'debug', it's more convenient to add and comment out tracing output: fonction x = trace ("fonction " ++ show x) (travail x) ~> fonction x = {- trace ("fonction " ++ show x) -} (travail x) vs. fonction x = travail x `debug` "fonction " ++ show x ~> fonction x = travail x -- `debug` "fonction " ++ show x
Let me know if you have any questions, Michael
On Sun, Jan 31, 2010 at 12:00 AM, legajid
wrote: Hi,
i wrote a program that doesn't behave as i wanted. So i tried to putStrLn my data structures to see what happened. Since i did this, all my functions changed type, so i had to modify them (main and calcul : use <- instead of let , add returns) and so on for each function called. Debugging this way causes more trouble than it should save.
What is the way to trace data thru function recursive calls without changing program structures? Is putStrLn a good idea ? I'm not used to ghci debug and i find it hard to manage (:break, :trace,
:cont ...).
Is the 'debugged' version as efficient as the first one, due to impure functional code? What if i want to remove 'debug code' ? Should i modify back my functions ?
Here are two very simplified versions of my program, the first one without 'trace', the second modified to include putStrLn as wanted.
Thanks in advance, Didier
First version -------------
main=do let valeurs=[0,1,3,0] let (valeurs_new)=calcul valeurs afficher_resultat valeurs afficher_resultat valeurs_new
calcul :: [Int] -> [Int] calcul xv | nblibr == 0 = map (*2) xv
| otherwise = map (+1) xv
where libres = [ x | x <- [1..length xv] , xv !! (x-1) == 0] nblibr=length libres
afficher_resultat xv = do putStrLn (show xv)
Second version ----------------
main=do let valeurs=[0,1,3,0]
valeurs_new <- calcul valeurs
afficher_resultat valeurs afficher_resultat valeurs_new
calcul :: [Int] -> IO [Int] calcul xv | nblibr == 0 = do putStrLn "ok" return (map (*2) xv)
| otherwise = return (map (+1) xv)
where libres = [ x | x <- [1..length xv] , xv !! (x-1) == 0] nblibr=length libres
afficher_resultat xv = do putStrLn (show xv)
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

OK, that's a great help. Michael Snoyman a écrit :
I think you want the Debug.Trace module. The documentation is available at http://haskell.org/ghc/docs/latest/html/libraries/base/Debug-Trace.html.
Let me know if you have any questions, Michael
On Sun, Jan 31, 2010 at 12:00 AM, legajid
mailto:legajid@free.fr> wrote: Hi,
i wrote a program that doesn't behave as i wanted. So i tried to putStrLn my data structures to see what happened. Since i did this, all my functions changed type, so i had to modify them (main and calcul : use <- instead of let , add returns) and so on for each function called. Debugging this way causes more trouble than it should save.
What is the way to trace data thru function recursive calls without changing program structures? Is putStrLn a good idea ? I'm not used to ghci debug and i find it hard to manage (:break, :trace, :cont ...). Is the 'debugged' version as efficient as the first one, due to impure functional code? What if i want to remove 'debug code' ? Should i modify back my functions ?
Here are two very simplified versions of my program, the first one without 'trace', the second modified to include putStrLn as wanted.
Thanks in advance, Didier
First version -------------
main=do let valeurs=[0,1,3,0] let (valeurs_new)=calcul valeurs afficher_resultat valeurs afficher_resultat valeurs_new
calcul :: [Int] -> [Int] calcul xv | nblibr == 0 = map (*2) xv | otherwise = map (+1) xv where libres = [ x | x <- [1..length xv] , xv !! (x-1) == 0] nblibr=length libres
afficher_resultat xv = do putStrLn (show xv)
Second version ----------------
main=do let valeurs=[0,1,3,0]
valeurs_new <- calcul valeurs
afficher_resultat valeurs afficher_resultat valeurs_new
calcul :: [Int] -> IO [Int] calcul xv | nblibr == 0 = do putStrLn "ok" return (map (*2) xv) | otherwise = return (map (+1) xv) where libres = [ x | x <- [1..length xv] , xv !! (x-1) == 0] nblibr=length libres
afficher_resultat xv = do putStrLn (show xv)
_______________________________________________ Beginners mailing list Beginners@haskell.org mailto:Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (3)
-
Daniel Fischer
-
legajid
-
Michael Snoyman