Skip to content

Commit

Permalink
Remove extraneous fundeps on (~)
Browse files Browse the repository at this point in the history
  • Loading branch information
Richard Eisenberg committed Feb 17, 2016
1 parent aff5bb4 commit 7d8031b
Showing 1 changed file with 5 additions and 1 deletion.
6 changes: 5 additions & 1 deletion libraries/base/Data/Type/Equality.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,14 +54,18 @@ import Data.Type.Bool
-- | Lifted, homogeneous equality. By lifted, we mean that it can be
-- bogus (deferred type error). By homogeneous, the two types @a@
-- and @b@ must have the same kind.
class a ~~ b => (a :: k) ~ (b :: k) | a -> b, b -> a
class a ~~ b => (a :: k) ~ (b :: k)
-- See Note [The equality types story] in TysPrim
-- NB: All this class does is to wrap its superclass, which is
-- the "real", inhomogeneous equality; this is needed when
-- we have a Given (a~b), and we want to prove things from it
-- NB: Not exported, as (~) is magical syntax. That's also why there's
-- no fixity.

-- It's tempting to put functional dependencies on (~), but it's not
-- necessary because the functional-depedency coverage check looks
-- through superclasses, and (~#) is handled in that check.

instance {-# INCOHERENT #-} a ~~ b => a ~ b
-- See Note [The equality types story] in TysPrim
-- If we have a Wanted (t1 ~ t2), we want to immediately
Expand Down

0 comments on commit 7d8031b

Please sign in to comment.