[Haskell-cafe] global, modifiable variable for debugging

aditya siram aditya.siram at gmail.com
Sun Dec 26 22:44:57 CET 2010


If you don't want go the unsafePerformIO route you might use implicit
parameters [1]. You can add an hidden parameter to a function like:
{-# LANGUAGE ImplicitParams #-}

func1 :: (?dbg :: Bool) => String -> String
func1 s = if ?dbg then (func2 ("func1 : " ++ s))
          else s

func2 :: (?dbg :: Bool) => String -> String
func2 s = if ?dbg then (let ?dbg = not ?dbg in func3 ("func2 : " ++ s))
          else s

func3 :: (?dbg :: Bool) => String -> String
func3 s =  if ?dbg then ("func3 : " ++ s)
           else s

test bool = do
  let ?dbg = bool
  putStrLn $ func1 "hello world"
  putStrLn $ func3 "goodbye world"

> test True
func2 : func1 : hello world
func3 : goodbye world

> test False
hello world
goodbye world

Notice that the value of ?dbg is propagated even though it is never
explicitly passed into func1. Similarly func1 never explicitly passes
?dbg to func2.  Also as in func2 you can change ?dbg for other
functions downstream, but not the original ?dbg as shown by the second
"putStrLn ... ".

It seems a more flexible approach to a global variable but it does
litter your function signatures with "(?dbg :: Bool)".

-deech

[1] http://www.haskell.org/ghc/docs/7.0-latest/html/users_guide/other-type-extensions.html#implicit-parameters

On Sun, Dec 26, 2010 at 1:53 PM,  <briand at aracnet.com> wrote:
> Hi,
>
> I have a program with a debug flag in it (Strangely I've yet to be
> able to write bug-free code).  I'd like to change the state of the
> debug flag based on command line args.
>
> I looked at IOVar but that would cause all the pure procedures to get
> swallowed by the IO Monad.
>
> Is a better way to get this behavior ?
>
> Thanks,
>
> Brian
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



More information about the Haskell-Cafe mailing list