[GHC] #10592: Allow cycles in class declarations
GHC
ghc-devs at haskell.org
Wed Dec 16 19:35:17 UTC 2015
#10592: Allow cycles in class declarations
-------------------------------------+-------------------------------------
Reporter: MikeIzbicki | Owner:
Type: feature request | Status: infoneeded
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.10.1
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by MikeIzbicki):
Awesome! I have two comments:
1. One of my use cases is very similar to the code attached below, which
causes GHC to loop. The code provides an alternate class hierarchy for
comparisons. One of the features of the hierarchy is that `(||)` and
`(&&)` can be used directly on functions. Unfortunately, the instances
for `(->)` cause GHC to loop. The instances seem like they should work to
me. I'm not sure if my reasoning is faulty or if there's a bug in the
implementation.
2. I believe there is an incorrect error message. If you take the code
below and comment out the line `instance Boolean b => Boolean (a -> b)`,
then GHC gives the error message:
{{{
[1 of 1] Compiling ClassCycles ( ClassCycles.hs, ClassCycles.o )
ClassCycles.hs:1:1: error:
solveWanteds: too many iterations (limit = 4)
Set limit with -fsolver-iterations=n; n=0 for no limit
WC {wc_simple =
[W] $dBoolean_a1KZ :: Boolean (a -> fsk_a1KH) (CDictCan)
[D] _ :: Boolean (a -> fsk_a1Ll) (CDictCan)}
}}}
But when I try to set the limit to something different, GHC complains that
the flag doesn't exist:
{{{
$ ~/proj/ghc/inplace/bin/ghc-stage2 ClassCycles.hs -fsolver-iterations=10
ghc-stage2: unrecognised flag: -fsolver-iterations=10
Usage: For basic information, try the `--help' option
}}}
----
{{{
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableSuperClasses #-}
module ClassCycles
where
import Prelude (Bool(True,False),Integer,Ordering)
import qualified Prelude
--------------------
-- class hierarchy
class Boolean (Logic a) => Eq a where
type Logic a :: *
(==) :: a -> a -> Logic a
class Eq a => POrd a where
inf :: a -> a -> a
class POrd a => MinBound a where
minBound :: a
class POrd a => Lattice a where
sup :: a -> a -> a
class (Lattice a, MinBound a) => Bounded a where
maxBound :: a
class Bounded a => Complemented a where
not :: a -> a
class Bounded a => Heyting a where
infixr 3 ==>
(==>) :: a -> a -> a
class (Complemented a, Heyting a) => Boolean a
(||) :: Boolean a => a -> a -> a
(||) = sup
(&&) :: Boolean a => a -> a -> a
(&&) = inf
--------------------
-- Bool instances
-- (these work fine)
instance Eq Bool where
type Logic Bool = Bool
(==) = (Prelude.==)
instance POrd Bool where
inf True True = True
inf _ _ = False
instance MinBound Bool where
minBound = False
instance Lattice Bool where
sup False False = False
sup _ _ = True
instance Bounded Bool where
maxBound = True
instance Complemented Bool where
not True = False
not False = True
instance Heyting Bool where
False ==> _ = True
True ==> a = a
instance Boolean Bool
--------------------
-- Integer instances
-- (these work fine)
instance Eq Integer where
type Logic Integer = Bool
(==) = (Prelude.==)
instance POrd Integer where
inf = Prelude.min
instance Lattice Integer where
sup = Prelude.max
--------------------
-- function instances
-- (these cause GHC to loop)
instance Eq b => Eq (a -> b) where
type Logic (a -> b) = a -> Logic b
f==g = \a -> f a == g a
instance POrd b => POrd (a -> b) where
inf f g = \a -> inf (f a) (g a)
instance MinBound b => MinBound (a -> b) where
minBound = \_ -> minBound
instance Lattice b => Lattice (a -> b) where
sup f g = \a -> sup (f a) (g a)
instance Bounded b => Bounded (a -> b) where
maxBound = \_ -> maxBound
instance Complemented b => Complemented (a -> b) where
not f = \a -> not (f a)
instance Heyting b => Heyting (a -> b) where
f ==> g = \a -> f a ==> g a
instance Boolean b => Boolean (a -> b)
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10592#comment:12>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list