Skip to content

Commit

Permalink
Implement overlapping type family instances.
Browse files Browse the repository at this point in the history
An ordered, overlapping type family instance is introduced by 'type
instance
where', followed by equations. See the new section in the user manual
(7.7.2.2) for details. The canonical example is Boolean equality at the
type
level:

type family Equals (a :: k) (b :: k) :: Bool
type instance where
  Equals a a = True
  Equals a b = False

A branched family instance, such as this one, checks its equations in
order
and applies only the first the matches. As explained in the note
[Instance
checking within groups] in FamInstEnv.lhs, we must be careful not to
simplify,
say, (Equals Int b) to False, because b might later unify with Int.

This commit includes all of the commits on the overlapping-tyfams
branch. SPJ
requested that I combine all my commits over the past several months
into one
monolithic commit. The following GHC repos are affected: ghc, testsuite,
utils/haddock, libraries/template-haskell, and libraries/dph.

Here are some details for the interested:

- The definition of CoAxiom has been moved from TyCon.lhs to a
  new file CoAxiom.lhs. I made this decision because of the
  number of definitions necessary to support BranchList.

- BranchList is a GADT whose type tracks whether it is a
  singleton list or not-necessarily-a-singleton-list. The reason
  I introduced this type is to increase static checking of places
  where GHC code assumes that a FamInst or CoAxiom is indeed a
  singleton. This assumption takes place roughly 10 times
  throughout the code. I was worried that a future change to GHC
  would invalidate the assumption, and GHC might subtly fail to
  do the right thing. By explicitly labeling CoAxioms and
  FamInsts as being Unbranched (singleton) or
  Branched (not-necessarily-singleton), we make this assumption
  explicit and checkable. Furthermore, to enforce the accuracy of
  this label, the list of branches of a CoAxiom or FamInst is
  stored using a BranchList, whose constructors constrain its
  type index appropriately.

I think that the decision to use BranchList is probably the most
controversial decision I made from a code design point of view.
Although I provide conversions to/from ordinary lists, it is more
efficient to use the brList... functions provided in CoAxiom than
always to convert. The use of these functions does not wander far
from the core CoAxiom/FamInst logic.

BranchLists are motivated and explained in the note [Branched axioms] in
CoAxiom.lhs.

- The CoAxiom type has changed significantly. You can see the new
  type in CoAxiom.lhs. It uses a CoAxBranch type to track
  branches of the CoAxiom. Correspondingly various functions
  producing and consuming CoAxioms had to change, including the
  binary layout of interface files.

- To get branched axioms to work correctly, it is important to have a
  notion
  of type "apartness": two types are apart if they cannot unify, and no
  substitution of variables can ever get them to unify, even after type
family
  simplification. (This is different than the normal failure to unify
because
  of the type family bit.) This notion in encoded in tcApartTys, in
Unify.lhs.
  Because apartness is finer-grained than unification, the tcUnifyTys
now
  calls tcApartTys.

- CoreLinting axioms has been updated, both to reflect the new
  form of CoAxiom and to enforce the apartness rules of branch
  application. The formalization of the new rules is in
  docs/core-spec/core-spec.pdf.

- The FamInst type (in types/FamInstEnv.lhs) has changed
  significantly, paralleling the changes to CoAxiom. Of course,
  this forced minor changes in many files.

- There are several new Notes in FamInstEnv.lhs, including one
  discussing confluent overlap and why we're not doing it.

- lookupFamInstEnv, lookupFamInstEnvConflicts, and
  lookup_fam_inst_env' (the function that actually does the work)
  have all been more-or-less completely rewritten. There is a
  Note [lookup_fam_inst_env' implementation] describing the
  implementation. One of the changes that affects other files is
  to change the type of matches from a pair of (FamInst, [Type])
  to a new datatype (which now includes the index of the matching
  branch). This seemed a better design.

- The TySynInstD constructor in Template Haskell was updated to
  use the new datatype TySynEqn. I also bumped the TH version
  number, requiring changes to DPH cabal files. (That's why the
  DPH repo has an overlapping-tyfams branch.)

- As SPJ requested, I refactored some of the code in HsDecls:

 * splitting up TyDecl into SynDecl and DataDecl, correspondingly
   changing HsTyDefn to HsDataDefn (with only one constructor)

 * splitting FamInstD into TyFamInstD and DataFamInstD and
   splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl

 * making the ClsInstD take a ClsInstDecl, for parallelism with
   InstDecl's other constructors

 * changing constructor TyFamily into FamDecl

 * creating a FamilyDecl type that stores the details for a family
   declaration; this is useful because FamilyDecls can appear in classes
but
   other decls cannot

 * restricting the associated types and associated type defaults for a
 * class
   to be the new, more restrictive types

 * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts,
   according to the new types

 * perhaps one or two more that I'm overlooking

None of these changes has far-reaching implications.

- The user manual, section 7.7.2.2, is updated to describe the new type
  family
  instances.
  • Loading branch information
Richard Eisenberg committed Dec 22, 2012
1 parent 4f6baef commit 80cac93
Show file tree
Hide file tree
Showing 62 changed files with 508 additions and 102 deletions.
14 changes: 14 additions & 0 deletions tests/indexed-types/should_compile/Overlap1.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
{-# LANGUAGE TypeFamilies #-}

module Overlap1 where

type family F a
type instance where
F Int = Int
F a = Bool

g :: F Int
g = 5

h :: F Char
h = False
16 changes: 16 additions & 0 deletions tests/indexed-types/should_compile/Overlap12.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
{-# LANGUAGE TypeFamilies, DataKinds, PolyKinds #-}

module Overlap12 where

type family And (a :: Bool) (b :: Bool) :: Bool
type instance where
And False x = False
And True x = x
And x False = False
And x True = x
And x x = x

data Proxy p = P

i :: Proxy (And False x)
i = (P :: Proxy False)
14 changes: 14 additions & 0 deletions tests/indexed-types/should_compile/Overlap2.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
{-# LANGUAGE TypeFamilies #-}

module Overlap2 where

type family F a b
type instance where
F a a = Int
F a b = Bool

g :: F Char Double
g = False

h :: F Double Double
h = -2
2 changes: 1 addition & 1 deletion tests/indexed-types/should_compile/T3017.stderr
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ TYPE CONSTRUCTORS
= L :: forall a. [a] -> ListColl a Stricts: _
FamilyInstance: none
COERCION AXIOMS
axiom Foo.TFCo:R:ElemListColl a :: Elem (ListColl a) ~# a
axiom Foo.TFCo:R:ElemListColl :: forall a. Elem (ListColl a) ~# a
INSTANCES
instance Coll (ListColl a) -- Defined at T3017.hs:12:11
FAMILY INSTANCES
Expand Down
4 changes: 4 additions & 0 deletions tests/indexed-types/should_compile/all.T
Original file line number Diff line number Diff line change
Expand Up @@ -196,6 +196,10 @@ test('T6152',

test('T6088', normal, compile, [''])
test('T7082', normal, compile, [''])

test('Overlap1', normal, compile, [''])
test('Overlap2', normal, compile, [''])
test('Overlap12', normal, compile, [''])
test('T7156', normal, compile, [''])
test('T5591a', normal, compile, [''])
test('T5591b', normal, compile, [''])
Expand Down
6 changes: 3 additions & 3 deletions tests/indexed-types/should_fail/NotRelaxedExamples.stderr
Original file line number Diff line number Diff line change
@@ -1,17 +1,17 @@

NotRelaxedExamples.hs:9:1:
NotRelaxedExamples.hs:9:15:
Nested type family application
in the type family application: F1 (F1 Char)
(Use -XUndecidableInstances to permit this)
In the type instance declaration for `F1'

NotRelaxedExamples.hs:10:1:
NotRelaxedExamples.hs:10:15:
Application is no smaller than the instance head
in the type family application: F2 [x]
(Use -XUndecidableInstances to permit this)
In the type instance declaration for `F2'

NotRelaxedExamples.hs:11:1:
NotRelaxedExamples.hs:11:15:
Application is no smaller than the instance head
in the type family application: F3 [Char]
(Use -XUndecidableInstances to permit this)
Expand Down
8 changes: 4 additions & 4 deletions tests/indexed-types/should_fail/Over.stderr
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@

OverB.hs:7:15:
Conflicting family instance declarations:
data instance OverA.C [Int] [a] -- Defined at OverB.hs:7:15
data instance OverA.C [a] [Int] -- Defined at OverC.hs:7:15
OverA.C [Int] [a] -- Defined at OverB.hs:7:15
OverA.C [a] [Int] -- Defined at OverC.hs:7:15

OverB.hs:9:15:
Conflicting family instance declarations:
type instance OverA.D [Int] [a] -- Defined at OverB.hs:9:15
type instance OverA.D [a] [Int] -- Defined at OverC.hs:9:15
OverA.D [Int] [a] -- Defined at OverB.hs:9:15
OverA.D [a] [Int] -- Defined at OverC.hs:9:15
15 changes: 15 additions & 0 deletions tests/indexed-types/should_fail/Overlap10.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
{-# LANGUAGE TypeFamilies #-}

module Overlap10 where

type family F a b
type instance where
F a a = Int
F a b = b

g :: F a Bool
g = False




7 changes: 7 additions & 0 deletions tests/indexed-types/should_fail/Overlap10.stderr
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@

Overlap10.hs:11:5:
Couldn't match expected type `F a Bool' with actual type `Bool'
Relevant bindings include
g :: F a Bool (bound at Overlap10.hs:11:1)
In the expression: False
In an equation for `g': g = False
15 changes: 15 additions & 0 deletions tests/indexed-types/should_fail/Overlap11.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
{-# LANGUAGE TypeFamilies #-}

module Overlap11 where

type family F a b
type instance where
F a a = Int
F a b = b

g :: F a Int
g = (5 :: Int)




6 changes: 6 additions & 0 deletions tests/indexed-types/should_fail/Overlap11.stderr
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@

Overlap11.hs:11:6:
Couldn't match expected type `F a Int' with actual type `Int'
Relevant bindings include g :: F a Int (bound at Overlap11.hs:11:1)
In the expression: (5 :: Int)
In an equation for `g': g = (5 :: Int)
15 changes: 15 additions & 0 deletions tests/indexed-types/should_fail/Overlap3.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
{-# LANGUAGE TypeFamilies #-}

module Overlap3 where

type family F a b
type instance where
F a a = Int
F a b = Bool
type instance F Char Char = Int

g :: F Char Double
g = False

h :: F Double Double
h = -2
10 changes: 10 additions & 0 deletions tests/indexed-types/should_fail/Overlap3.stderr
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@

Overlap3.hs:7:3:
Conflicting family instance declarations:
F a a -- Defined at Overlap3.hs:7:3
F Char Char -- Defined at Overlap3.hs:9:15

Overlap3.hs:8:3:
Conflicting family instance declarations:
F a b -- Defined at Overlap3.hs:8:3
F Char Char -- Defined at Overlap3.hs:9:15
16 changes: 16 additions & 0 deletions tests/indexed-types/should_fail/Overlap4.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
{-# LANGUAGE TypeFamilies #-}

module Overlap4 where

type family F a b
type instance F Char Char = Int
type instance where
F a a = Int
F a b = Bool


g :: F Char Double
g = False

h :: F Double Double
h = -2
5 changes: 5 additions & 0 deletions tests/indexed-types/should_fail/Overlap4.stderr
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@

Overlap4.hs:6:15:
Conflicting family instance declarations:
F Char Char -- Defined at Overlap4.hs:6:15
F a a -- Defined at Overlap4.hs:8:3
22 changes: 22 additions & 0 deletions tests/indexed-types/should_fail/Overlap5.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
{-# LANGUAGE TypeFamilies, DataKinds, PolyKinds #-}

module Overlap5 where

type family And (a :: Bool) (b :: Bool) :: Bool
type instance where
And False x = False
And True x = x
And x False = False
And x True = x
And x x = x

data Proxy p = P

g :: Proxy x -> Proxy (And x True)
g x = x

h :: Proxy x -> Proxy (And x x)
h x = x

i :: Proxy x -> Proxy (And False x)
i x = (P :: Proxy False)
29 changes: 29 additions & 0 deletions tests/indexed-types/should_fail/Overlap5.stderr
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@

Overlap5.hs:16:7:
Couldn't match type `x' with `And x 'True'
`x' is a rigid type variable bound by
the type signature for
g :: Proxy Bool x -> Proxy Bool (And x 'True)
at Overlap5.hs:15:6
Expected type: Proxy Bool (And x 'True)
Actual type: Proxy Bool x
Relevant bindings include
g :: Proxy Bool x -> Proxy Bool (And x 'True)
(bound at Overlap5.hs:16:1)
x :: Proxy Bool x (bound at Overlap5.hs:16:3)
In the expression: x
In an equation for `g': g x = x

Overlap5.hs:19:7:
Couldn't match type `x' with `And x x'
`x' is a rigid type variable bound by
the type signature for h :: Proxy Bool x -> Proxy Bool (And x x)
at Overlap5.hs:18:6
Expected type: Proxy Bool (And x x)
Actual type: Proxy Bool x
Relevant bindings include
h :: Proxy Bool x -> Proxy Bool (And x x)
(bound at Overlap5.hs:19:1)
x :: Proxy Bool x (bound at Overlap5.hs:19:3)
In the expression: x
In an equation for `h': h x = x
16 changes: 16 additions & 0 deletions tests/indexed-types/should_fail/Overlap6.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
{-# LANGUAGE TypeFamilies, DataKinds, PolyKinds #-}

module Overlap6 where

type family And (a :: Bool) (b :: Bool) :: Bool
type instance where
And False x = False
And True x = False -- this is wrong!
And x False = False
And x True = x
And x x = x

data Proxy p = P

g :: Proxy x -> Proxy (And x True)
g x = x
15 changes: 15 additions & 0 deletions tests/indexed-types/should_fail/Overlap6.stderr
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@

Overlap6.hs:16:7:
Couldn't match type `x' with `And x 'True'
`x' is a rigid type variable bound by
the type signature for
g :: Proxy Bool x -> Proxy Bool (And x 'True)
at Overlap6.hs:15:6
Expected type: Proxy Bool (And x 'True)
Actual type: Proxy Bool x
Relevant bindings include
g :: Proxy Bool x -> Proxy Bool (And x 'True)
(bound at Overlap6.hs:16:1)
x :: Proxy Bool x (bound at Overlap6.hs:16:3)
In the expression: x
In an equation for `g': g x = x
10 changes: 10 additions & 0 deletions tests/indexed-types/should_fail/Overlap7.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
{-# LANGUAGE TypeFamilies #-}

module Overlap7 where

type family F a b
type instance where
F Int a = Int
F a b = Bool
type instance F a Int = Int

10 changes: 10 additions & 0 deletions tests/indexed-types/should_fail/Overlap7.stderr
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@

Overlap7.hs:7:3:
Conflicting family instance declarations:
F Int a -- Defined at Overlap7.hs:7:3
F a Int -- Defined at Overlap7.hs:9:15

Overlap7.hs:8:3:
Conflicting family instance declarations:
F a b -- Defined at Overlap7.hs:8:3
F a Int -- Defined at Overlap7.hs:9:15
11 changes: 11 additions & 0 deletions tests/indexed-types/should_fail/Overlap8.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
{-# LANGUAGE TypeFamilies #-}

module Overlap8 where

type family F a b
type instance F a Int = Int
type instance where
F Int a = Int
F a b = Bool


5 changes: 5 additions & 0 deletions tests/indexed-types/should_fail/Overlap8.stderr
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@

Overlap8.hs:6:15:
Conflicting family instance declarations:
F a Int -- Defined at Overlap8.hs:6:15
F Int a -- Defined at Overlap8.hs:8:3
14 changes: 14 additions & 0 deletions tests/indexed-types/should_fail/Overlap9.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
{-# LANGUAGE TypeFamilies #-}

module Overlap9 where

type family F a
type instance where
F Int = Bool
F a = Int

g :: Show a => a -> F a
g x = length (show x)



12 changes: 12 additions & 0 deletions tests/indexed-types/should_fail/Overlap9.stderr
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@

Overlap9.hs:11:7:
Could not deduce (F a ~ Int)
from the context (Show a)
bound by the type signature for g :: Show a => a -> F a
at Overlap9.hs:10:6-23
Relevant bindings include
g :: a -> F a (bound at Overlap9.hs:11:1)
x :: a (bound at Overlap9.hs:11:3)
In the return type of a call of `length'
In the expression: length (show x)
In an equation for `g': g x = length (show x)
8 changes: 4 additions & 4 deletions tests/indexed-types/should_fail/SimpleFail11a.stderr
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@

SimpleFail11a.hs:6:15:
Conflicting family instance declarations:
data instance C9 Int Int -- Defined at SimpleFail11a.hs:6:15
data instance C9 Int Int -- Defined at SimpleFail11a.hs:8:15
C9 Int Int -- Defined at SimpleFail11a.hs:6:15
C9 Int Int -- Defined at SimpleFail11a.hs:8:15

SimpleFail11a.hs:11:15:
Conflicting family instance declarations:
type instance D9 Int Int -- Defined at SimpleFail11a.hs:11:15
type instance D9 Int Int -- Defined at SimpleFail11a.hs:13:15
D9 Int Int -- Defined at SimpleFail11a.hs:11:15
D9 Int Int -- Defined at SimpleFail11a.hs:13:15
8 changes: 4 additions & 4 deletions tests/indexed-types/should_fail/SimpleFail11b.stderr
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@

SimpleFail11b.hs:7:15:
Conflicting family instance declarations:
data instance C9 [a] Int -- Defined at SimpleFail11b.hs:7:15
data instance C9 [a] Int -- Defined at SimpleFail11b.hs:9:15
C9 [a] Int -- Defined at SimpleFail11b.hs:7:15
C9 [a] Int -- Defined at SimpleFail11b.hs:9:15

SimpleFail11b.hs:13:15:
Conflicting family instance declarations:
type instance D9 [a] Int -- Defined at SimpleFail11b.hs:13:15
type instance D9 [a] Int -- Defined at SimpleFail11b.hs:15:15
D9 [a] Int -- Defined at SimpleFail11b.hs:13:15
D9 [a] Int -- Defined at SimpleFail11b.hs:15:15

0 comments on commit 80cac93

Please sign in to comment.