Ok, I went with the preprocessor solution only. It is simple, stupid and
works well enough ... and template haskell alternative needs it anyway
not to be too unportable.
Both template haskell alternatives reported "Pattern match(es) are
non-exhaustive" of their own. The second alternative moreover needs a
change of '$ case True of False -> "srcloc"' to '$ case True of False ->
undefined' to be usable.
The warning problem is critical by its own since the goal of using it is
to selectively disable the very same warning for a specific case
statement. Although the warning can be eliminated probably in the first
template haskell alternative. Not sure since I do not know template
haskell. As well as I still do not know how to write a haskell function
in C-- which is the reason there is no :next command in ghci yet :)
Thanks,
Peter.
Claus Reinke wrote:
The second solution requires QuasiQuotes, so I do not know. If I
would want to compile with a different compiler it would break. If
srcloc can be defined as a simple token (not requiring special
extensions at places where it is used) then I could define it to an
empty string in some low level module if trying to compile with a
different haskell compiler which does not know srcloc.
You can do better than that, if you combine the QuasiQuotes hack with
the CPP hack (I've also simplified the srcloc handling by adding a
version
of error that adds source location info, moving the exception
manipulation
out into SrcLocQQ, avoiding the need for Debug.Trace alltogether).
The portable version does get a bit uglier because you need macros,
not functions (you'll probably want to check for GHC version or
-better, but not supported- QuasiQuotes availability). Also, CPP only
gives you the line number, not the position, but that is better than
nothing, and often sufficient.
Still, it would be much nicer if GHC inserted the location info at the
call sites if a pragma at the definition site asked it to do so. Then
this
{-# SRCLOC f #-}
f Nothing = "okay"
f _ = error "f applied to not-Nothing in: "
could be equivalent to the code below, without QuasiQuotes or CPP
or ERRORSRC all over the place. But such niceties are on hold while
the discussion of even nicer help is ongoing.. (which is partly justified
because we cannot easily build nicer abstractions over a barebones
solution, due to the macro vs function issue, so the design does need
thought). Perhaps the code below is sufficient as an interim workaround.
Claus
-----------------------------
{-# LANGUAGE CPP #-}
{-# LANGUAGE QuasiQuotes #-}
#ifdef __GLASGOW_HASKELL__
#define SRCLOC [$srcloc||]
#define ERRORSRC [$errorSrc||]
#else
#define SRCLOC (show (__FILE__,__LINE__))
#define ERRORSRC (\msg->error $ msg++SRCLOC)
#endif
import SrcLocQQ
f errorSrc Nothing = "okay"
f errorSrc _ = errorSrc "f applied to not-Nothing in: "
main = do
print $ f ERRORSRC Nothing
print $ f ERRORSRC (Just ())
print $ SRCLOC
-----------------------------
{-# LANGUAGE TemplateHaskell #-}
module SrcLocQQ where
import Language.Haskell.TH.Quote
import Language.Haskell.TH
import Control.Exception
srcloc = QuasiQuoter (\_->[| mapException (\(PatternMatchFail fail)->
let srcloc = reverse (dropWhile (/=':')
(reverse fail))
in PatternMatchFail srcloc)
$ case True of False -> "srcloc" |])
(error "pattern srclocs not supported")
errorSrc = QuasiQuoter
(\_->[| \msg->mapException (\(PatternMatchFail fail)->
let srcloc = reverse (dropWhile (/=':')
(reverse fail))
in PatternMatchFail (msg++srcloc))
$ case True of False -> "srcloc" |])
(error "pattern srclocs not supported")
-----------------------------
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users