Should exhaustiveness testing be on by default?

Claus Reinke claus.reinke at talk21.com
Wed May 20 08:33:36 EDT 2009


>I was looking for something which works in optimized builds too.

{-# OPTIONS_GHC -fno-ignore-asserts #-}

overrides the -O default setting -fignore-asserts.

> I know I could do it with preprocessor or (I think) template haskell too 
> but these tools seem to heavy for such a simple goal.

Given how long http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack
has been under discussion, it is probably time to provide a short-term
workaround in GHC, just a token to be replaced by the current source
location. Then assert could be redefined in terms of it, so GHC wouldn't
be any more complicated than it is, and users would have access to the 
same functionality for their uses, while the more useful variations are still 
being discussed.

Below is another hacked-up version, this time using quasiquoting to
generate a piece of code that will trigger an error with source location,
which will only be forced when we need the source location info:-)

It is reasonably easy to use (though one should trim the part of the error 
message one is not interested in, and I don't like that I can't simply call
error in 'f', because that would trigger the nested error before printing 'f's
message), but a standard solution in the libraries would be a lot better.

Claus

------------------------------------------
{-# LANGUAGE QuasiQuotes #-}
{-# OPTIONS_GHC -fno-ignore-asserts #-}

import Control.Exception(assert)
import SrcLocQQ
import Debug.Trace

f srcloc Nothing = "okay"
f srcloc _       = trace "error: f applied to not-Nothing in: "  srcloc

main = do
  print $ f [$srcloc||] Nothing
  print $ f [$srcloc||] (Just ())
  print $ assert False True

------------------------------------------
{-# LANGUAGE TemplateHaskell #-}
module SrcLocQQ where
import Language.Haskell.TH.Quote
import Language.Haskell.TH

srcloc = QuasiQuoter 
            (\_->return $ CaseE (ConE 'True)
                                [Match (ConP 'False [])
                                  (NormalB (LitE (StringL "srcloc"))) []])
            (error "pattern srclocs not supported")

------------------------------------------

$ ghc -e main srcloc.hs
"okay"
error: f applied to not-Nothing in:
<interactive>: srcloc.hs:13:12-22: Non-exhaustive patterns in case




More information about the Glasgow-haskell-users mailing list