
with ghc 7.8.4 and hflags 0.4 the following program: {-# LANGUAGE TemplateHaskell #-} module Main where import HFlags defineFlag "f" True "A flag." --defineFlag "g" True "Another flag." main = do _ <- $initHFlags "flags demo" print Main.flags_f gives me a runtime error about the flag f not being found, unless I add the declaration of a second flag. It seems like the last flag definition is not seen. Any idea/suggestion? Thanks, Maurizio

On 06/02/15 06:26, Maurizio Vitale wrote:
with ghc 7.8.4 and hflags 0.4 the following program:
{-# LANGUAGE TemplateHaskell #-}
module Main where
import HFlags
defineFlag "f" True "A flag." --defineFlag "g" True "Another flag."
return [] -- see http://hackage.haskell.org/package/QuickCheck-2.7.6/docs/Test-QuickCheck-All... - I haven't tested with hflags but it looks like the same issue from first glance
main = do _ <- $initHFlags "flags demo" print Main.flags_f
gives me a runtime error about the flag f not being found, unless I add the declaration of a second flag. It seems like the last flag definition is not seen.
Any idea/suggestion?
Thanks,
Maurizio
Claude -- http://mathr.co.uk

That was it, thanks.
I would have never figured it out on my own.
I've reported this issue in the hflags bugtracker (to get the workaround in
the docs). Hope it will be propagated to ghc if it is not already known.
On Fri, Feb 6, 2015 at 4:28 AM, Claude Heiland-Allen
On 06/02/15 06:26, Maurizio Vitale wrote:
with ghc 7.8.4 and hflags 0.4 the following program:
{-# LANGUAGE TemplateHaskell #-}
module Main where
import HFlags
defineFlag "f" True "A flag." --defineFlag "g" True "Another flag."
return []
-- see http://hackage.haskell.org/package/QuickCheck-2.7.6/docs/ Test-QuickCheck-All.html#v:quickCheckAll - I haven't tested with hflags but it looks like the same issue from first glance
main = do _ <- $initHFlags "flags demo" print Main.flags_f
gives me a runtime error about the flag f not being found, unless I add the declaration of a second flag. It seems like the last flag definition is not seen.
Any idea/suggestion?
Thanks,
Maurizio
Claude -- http://mathr.co.uk
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

This issue was known in hflags:
https://github.com/errge/hflags/issues/8 (Opened Jun 30, 2014)
and in ghc: https://ghc.haskell.org/trac/ghc/ticket/9768
And it's not a bug, as you can see from discussion in both tickets and
reference to ghc-7.8 documentation.
On 6 February 2015 at 17:28, Maurizio Vitale
That was it, thanks. I would have never figured it out on my own.
I've reported this issue in the hflags bugtracker (to get the workaround in the docs). Hope it will be propagated to ghc if it is not already known.
On Fri, Feb 6, 2015 at 4:28 AM, Claude Heiland-Allen
wrote: On 06/02/15 06:26, Maurizio Vitale wrote:
with ghc 7.8.4 and hflags 0.4 the following program:
{-# LANGUAGE TemplateHaskell #-}
module Main where
import HFlags
defineFlag "f" True "A flag." --defineFlag "g" True "Another flag."
return []
-- see http://hackage.haskell.org/package/QuickCheck-2.7.6/docs/Test-QuickCheck-All... - I haven't tested with hflags but it looks like the same issue from first glance
main = do _ <- $initHFlags "flags demo" print Main.flags_f
gives me a runtime error about the flag f not being found, unless I add the declaration of a second flag. It seems like the last flag definition is not seen.
Any idea/suggestion?
Thanks,
Maurizio
Claude -- http://mathr.co.uk
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alexander
participants (3)
-
Alexander V Vershilov
-
Claude Heiland-Allen
-
Maurizio Vitale