-fallow-incoherent-instances not working
Marc Weber
marco-oweber at gmx.de
Wed Feb 21 21:48:13 EST 2007
I'm trying to learn more about HList.
While setting up a small test application I got the following error..
ghc(i) tells me to add -fallow-incoherent-instances but doesn't
recognize it ?
Is this a bug?
marc at localhost /pr/haskell/test/HList $ ghci -package HList HListTestMain.hs
___ ___ _
/ _ \ /\ /\/ __(_)
/ /_\// /_/ / / | | GHC Interactive, version 6.6, for Haskell 98.
/ /_\\/ __ / /___| | http://www.haskell.org/ghc/
\____/\/ /_/\____/|_| Type :? for help.
Loading package base ... linking ... done.
Loading package HList-0.1 ... linking ... done.
[1 of 2] Compiling HListTest.HList ( HListTest/HList.hs, interpreted )
HListTest/HList.hs:12:11:
Overlapping instances for HOccursMany (Maybe Int)
(HCons t
(HCons t1 (HCons [Char] (HCons (Maybe t2) HNil))))
arising from use of `hOccursMany' at HListTest/HList.hs:12:11-24
Matching instances:
instance [overlap ok] (HOccursMany e l, HList l) =>
HOccursMany e (HCons e' l)
-- Defined in HOccurs
instance [overlap ok] (HOccursMany e l, HList l) =>
HOccursMany e (HCons e l)
-- Defined in HOccurs
(The choice depends on the instantiation of `t, t1, t2'
Use -fallow-incoherent-instances to use the first choice above)
In the expression: hOccursMany l1
In the second argument of `($)', namely
`(hOccursMany l1 :: [Maybe Int])'
In the expression: print $ (hOccursMany l1 :: [Maybe Int])
Failed, modules loaded: none.
Prelude> Leaving GHCi.
marc at localhost /pr/haskell/test/HList $ cat HListTest/HList.hs
{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}
{-# OPTIONS -fallow-overlapping-instances #-}
{-# OPTIONS -fallow-incoherent-instances #-} -- <<<<<<<<<<<< given here
module HListTest.HList where
import HList
l1 = 2 .*. 3 .*. "abc" .*. (Just 4) .*. HNil
hlistTest = do
print $ 2 .*. HNil
print $ (hOccursMany l1 :: [Maybe Int])
marc at localhost /pr/haskell/test/HList $
Marc
More information about the Glasgow-haskell-users
mailing list