[Haskell-cafe] Questions about haskell CPP macros

2009-07-13 Thread Matthew Elder
Hello Cafe,

I am trying to improve the error reporting in my sendfile library, and I
know I can find out the current file name and line number with something
like this:

{-# LANGUAGE CPP #-}
main = putStrLn (__FILE__ ++ : ++ show __LINE__)

This outputs:
test.hs:2

Unfortunately, if your file is in a hierarchy of folders, this flat file
name doesn't give much context. Is there a macro to find out the current
module? IE if I had a module Foo.Bar.Car.MyModule, I would like to be able
to output something like this on error:
Foo.Bar.Car.MyModule:2

Any help is appreciated!

Thanks,
Matt

-- 
Need somewhere to put your code? http://patch-tag.com
Want to build a webapp? http://happstack.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Questions about haskell CPP macros

2009-07-13 Thread Claus Reinke

I am trying to improve the error reporting in my sendfile library, and I
know I can find out the current file name and line number with something
like this:

{-# LANGUAGE CPP #-}
main = putStrLn (__FILE__ ++ : ++ show __LINE__)

This outputs:
test.hs:2

Unfortunately, if your file is in a hierarchy of folders, this flat file
name doesn't give much context. Is there a macro to find out the current
module? IE if I had a module Foo.Bar.Car.MyModule, I would like to be able
to output something like this on error:
Foo.Bar.Car.MyModule:2


Sounds like a job for cabal or ghc, to define appropriate macros for
package and module when compiling the source?


Any help is appreciated!


For actually making use of such information, see 

   http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack 
   http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack/StackTraceExperience


and also the recent thread on how to improve the quality of +RTS -xc
output via mapException (hmm, can't reach the archive at the moment,
one subject was Should exhaustiveness testing be on by default?, about
May; http://www.haskell.org/mailman/listinfo/glasgow-haskell-users ).

If you really mean any help, you could also use Template Haskell:-)

   {-# LANGUAGE TemplateHaskell #-}
   module Oh.Hi where 
   
   import Language.Haskell.TH
   
   main = print $( location = \(Loc f p m s e)- 
   stringE (f++:++p++:++m++:++show s++:++show e))


Claus


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Questions about haskell CPP macros

2009-07-13 Thread Stephan Friedrichs
Matthew Elder wrote:
 {-# LANGUAGE CPP #-}
 main = putStrLn (__FILE__ ++ : ++ show __LINE__)
 
 This outputs:
 test.hs:2
 
 Unfortunately, if your file is in a hierarchy of folders, this flat file
 name doesn't give much context. Is there a macro to find out the current
 module? IE if I had a module Foo.Bar.Car.MyModule, I would like to be
 able to output something like this on error:
 Foo.Bar.Car.MyModule:2

As mentioned by Claus, template-haskell offers a solution. But in some
cases, this is an overkill; consider using Control.Exception.assert, it
will provide module and line information without having to use CPP:

myHead :: [a] - a
myHead (x:_) = x
myHead []= assert False undefined

 
 [...]

//Stephan

-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

 - Dieter Nuhr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Questions about haskell CPP macros

2009-07-13 Thread Malcolm Wallace

{-# LANGUAGE CPP #-}
main = putStrLn (__FILE__ ++ : ++ show __LINE__)

This outputs:
test.hs:2


if I had a module Foo.Bar.Car.MyModule, I would like to be able to  
output something like this on error:

Foo.Bar.Car.MyModule:2


It works for me.  If you place that text in Try/Me.hs and call
ghc -E Try/Me.hs
you get
Try/Me.hs:2

If you just want to turn slashes into dots, and remove the suffix,  
that is a simple exercise in Haskell itself


main = putStrLn (mangle __FILE__)
  where mangle ('/':cs) = '.': mangle cs
mangle .

Regards,
Malcolm

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Questions about haskell CPP macros

2009-07-13 Thread Stephan Friedrichs
Malcolm Wallace wrote:
  {-# LANGUAGE CPP #-}
 main = putStrLn (__FILE__ ++ : ++ show __LINE__)

 This outputs:
 test.hs:2
 
 if I had a module Foo.Bar.Car.MyModule, I would like to be able to
 output something like this on error:
 Foo.Bar.Car.MyModule:2
 
 It works for me.  If you place that text in Try/Me.hs and call
 ghc -E Try/Me.hs
 you get
 Try/Me.hs:2
 
 If you just want to turn slashes into dots, and remove the suffix, that
 is a simple exercise in Haskell itself
 
 main = putStrLn (mangle __FILE__)
   where mangle ('/':cs) = '.': mangle cs
 mangle .

Careful, '/' might be '\\' on another OS, the file might end with .hsc
instead of .hs, the line numbers might not fit in the .hsc case...


-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

 - Dieter Nuhr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe