[Haskell-cafe] source line annotations
Bas van Dijk
v.dijk.bas at gmail.com
Thu Jan 20 15:36:21 CET 2011
On 20 January 2011 14:33, Bas van Dijk <v.dijk.bas at gmail.com> wrote:
> On 20 January 2011 10:48, Evan Laforge <qdunkan at gmail.com> wrote:
>> I still like the pragma...
>
> Maybe Template Haskell can help:
>
>
> module Location where
>
> import Language.Haskell.TH
> import Data.Functor ((<$>))
>
> loc :: Q Exp
> loc = LitE . StringL . show . loc_start <$> location
>
>
> {-# LANGUAGE TemplateHaskell #-}
>
> module Main where
>
> import Location
> main = do
> putStrLn $loc
> putStrLn $loc
> putStrLn $loc
>
>
> *Main> main
> (7,12)
> (8,12)
> (9,12)
>
> Regards,
>
> Bas
>
You should also take a look at the control-monad-exception package
which provides, among other things, support for exception call traces
(with source locations). Take a look at the description to see an
example:
http://hackage.haskell.org/package/control-monad-exception
Regards,
Bas
More information about the Haskell-Cafe
mailing list