I can put constraints superclass; I can put constraints on particular methods in the class; I can put extra constraints on instances for the class. Constraints are implemented as dictionary-passing. Does that mean different overloadings for a method get different numbers of dictionary arguments? Consider:
class Bar1 a -- just some classes
class Bar2 a
class Bar3 a
class Bar4 a
class Bar5 a
class (Bar1 a, Bar2 a) => Foo a where
foo :: Bar3 b => a -> b -> Bool -- `b` is not in class head
instance (Bar1 (Maybe a), Bar2 (Maybe a), -- needed from superclass
-- ?but (Bar3 b) not needed (nor could it be expressed)
Bar4 (Maybe a), Bar5 a) -- additional instance-specific, Bar5 is for part of instance head
=> Foo (Maybe a) where
foo x y = True
As I understand from this q, the Bar
s not having methods doesn't matter.
So different instances of Foo
might have different instance-specific constraints, some maybe for the whole instance head, some for only part -- like Bar5 a
within the Maybe a
. Does that mean that function foo
specialised for (Maybe a)
needs a different number of dictionaries passed, vs say for Int
? How is that organised?
Reason for asking is this thread, where SPJ talks about "bindSet
takes two Ord
parameters at
run-time, whereas ordinary bind
does not". (Yes quite true, but bindSet
is not a method of a class.) I'm wondering if there's already a mechanism for a method's instances taking different numbers of dictionary parameters?
Superclasses are compiled as additional fields in the class dictionary, so the class definition:
class (Bar1 a, Bar2 a) => Foo a where
foo :: Bar3 b => a -> b -> Bool
compiles to the rough equivalent of an explicit dictionary data type Foo
with three fields:
{-# LANGUAGE RankNTypes #-}
data Foo a = C:Foo { $p1Foo :: Bar1 a
, $p2Foo :: Bar2 a
, foo :: forall b. Bar3 b -> a -> b -> Bool }
Note that the foo
field accessor in this type, which also serves as the foo
class method function, ultimately has polymorphic type:
foo :: Foo a -> Bar3 b -> a -> b -> Bool
meaning that it accepts four arguments: a Foo a
dictionary (which contains the fields for the two superclass dictionaries Bar1 a
and Bar2 a
); a Bar3 b
dictionary as a separate argument; and then a
and b
arguments before yielding a Bool
.
When a polymorphic instance with constraints is defined:
instance (Bar1 (Maybe a), Bar2 (Maybe a),
Bar4 (Maybe a), Bar5 a)
=> Foo (Maybe a) where
foo x y = True
this defines a "dictionary function" for constructing dictionaries of Maybe
s.
$fFooMaybe :: Bar1 (Maybe a) -> Bar2 (Maybe a)
-> Bar 4 (Maybe a) -> Bar5 a -> Foo (Maybe a)
$fFooMaybe $dBar1 $dBar2 $dBar4 $dBar5 = C:Foo $dBar1 $dBar2 (\_ _ _ -> True)
Note that foo
itself still always takes four arguments, but the field in the C:Foo
dictionary for a concrete Maybe X
type will be closed over the dictionaries $dBar1
, $dBar2
, $dBar4
, and $dBar5
supplied at the time the Foo
dictionary is created by a $fFooMaybe
call.
Sooo....
Bar1
and Bar2
) are extra fields in the dictionaryfoo
) are field accessors for the class dictionary for function-valued fieldsBar3
) on the function in the class
declaration, these will be reflected as additional arguments to the function value of the fieldinstance Foo (Maybe a)
) are implemented as dictionary factories, and any constraints in the instance declaration (Bar1
, Bar2
, Bar4
, Bar5
) are closed over in creating the dictionary, which can copy over the super classes and use any other available in-scope constraints in constructing the necessary function values for methodsThe method foo
always takes the same number of parameters, though it will take a different number of dictionary parameters than, say, a bar :: a -> Double
method with no additional constraints. When instantiated at different types, additional constraint dictionaries are handled through closures when creating the dictionary for the type.
Does that make it clear?
Note that ghc -ddump-simpl
with or without -dsuppress-all
is very helpful for figuring out how this works under the hood.