Defaulting
Ambiguous Types, and Defaults for Overloaded Numeric Operations in the Haskell 98 Report.
Problems with the current defaulting rule:
-
Defaults are limited to Prelude numeric classes. A tool like Hat, which transforms Haskell source, cannot transform the defaults, because there is no way make defaults apply to the transformed classes rather than the original ones.
-
Defaults cannot be applied to user-defined classes. It would be nice for some applications to be able to allow a default clause to name the class being defaulted over, as well as the type to choose. Examples include QuickCheck, where you might wish to default the
Arbitrary
class to something small (e.g.Bool
) when a value is otherwise unconstrained. -
Report specification of defaulting is impossible to implement in the presence of recursive modules. (Should it be specified that a group of mutually recursive modules must have exactly the same defaulting?)
-
A default clause applies only within the module containing the declaration. Defaults can be neither exported nor imported. Does anyone wish to propose import/export of defaults?
- For import/export: easier to propagate user-defined class defaults throughout a project
- Against import/export: a change in the imports of a module might silently change behavior
- A compromise might be to allow defaults which will be inherited to be specified only in the module that defines a class, but groups of mutually recursive modules may override defaulting locally. this will avoid the import changing behavior problem and allow some sort of inheritence of defaults.
Proposal 1 - name the class
Allow defaulting clauses of the following form
default <classname> (type1,type2,type3,...)
The defaulting rule will simply choose the first unambiguous type that satisfies all the constrained classes listed in the default decls.
Classes without defaults will have the equivalent of an empty list of types, so defaulting will not occur.
One problem of course is what does "unambiguous" mean? In the case of
default A (Int, String, ())
default B (String, Int, ())
(A t, B t) => t
any of the three types would satisfy the rule that it is an instance of all the classes. So what is the intepretation of "first" in the list? The only unambiguous interpretation of "first" valid type in both classes A and B would be (), to avoid making an arbitrary choice between Int and String. However, this is still far from clearcut. Consider the following examples:
default A (Int,String,())
default B (String,(),Int)
(A t, B t) => t
default C (Int, Double, String, ())
default D (Double,String,Int,())
(C t, D t) => t
Pro
- very useful in interactive interpreter
- less ad hoc than current method
- overcomes the Hat transformation problem
Con
- can not exactly replicate behavior of existing defaulting mechanism, but can come close.
- might hide errors, an optional warning on defaulting should be possible.
- not clear how to choose a single unambiguous member of more than one list of types
Proposal 2 - name the class + no lists
Change default decls to (a) name the class being defaulted, and (b) permit only one default type per class, rather than a list. Possible syntax, by analogy with instance decls:
topdecl -> default tycls type
Semantically, which type is chosen is determined by the class context at the choice point (after context simplification). That is, in
default C T
(C a) => a
the type 'a', constrained by class 'C' but otherwise unresolved, is instantiated to the sole type 'T'.
-
If there is no unique choice, for instance because more than one class-with-a-default is mentioned in the context (and their default types are different), then it is a static error.
-
Note that it is OK to have several classes in the context of the defaultable value,
- provided only one of them is declared to yield a default type,
- or if more than one yields a type, those types are the same.
-
Choosing a default after context simplification means that no conflicts between super- and sub-classes can arise.
Examples
Here are some examples, to clarify the idea:
default Eq Integer
default Fractional Float
(Eq a, Fractional a) => a
After simplification, this becomes (Fractional a)⇒a, because Eq is a superclass of Fractional. Thus, there is a single class to be defaulted, and Float is chosen.
default Ord Integer
default Fractional Float
(Ord a, Fractional a) => a
A static error, because Ord is not a superclass of Fractional, so the context does not simplify, and the default types disagree.
default Bounded Int
default Ord Int
(Ord a, Bounded a) => a
Default is Int, because even though the context does not simplify, the classes involved do agree on which default to choose.
default Bounded Int
default Ord Int
(Ord a, Bounded a, Show a) => a
Default is Int, same as above, except for the extra constraint Show a. There is no default declared for Show, so the remaining context is used to make the choice.
(Show a, Read a) => a
A static error, because there are no defaults declared for any of the classes involved.
Backwards compatibility
The current Haskell'98 default-default behaviour can (nearly) be specified as:
default Num Integer
default Real Integer
default Enum Integer
default Integral Integer
default Fractional Double
default RealFrac Double
default Floating Double
default RealFloat Double
However, there are some incompatible cases where the new rule would cause a valid H'98 program to be rejected. For instance the expression toRational pi
has the constraints Floating
on pi and Real
on toRational: in H'98, the type Double is the first type that satisfies both constraints, but with the proposed new rule no type would satisfy the constraints, so the expression would be rejected. To fix, you would need to annotate pi
with a type.
Turning off defaults
In Haskell'98, the default decl not only declares a new default type for some classes, but can also implicitly remove defaults for other classes (at the same time!).
Whilst default ()
switches off all defaulting, default (Int)
changes the default type for the Num, Real, Enum, Integral classes, and also declares there is no
default for the Fractional, RealFrac, Floating, and RealFloat classes (by virtue of Int's failure to be a instance of those).
Under the current proposal, there is no explicit means to turn off defaults. A minor modification rectifies this shortcoming - simply permit the omission of the type part of the default decl. An omitted type indicates there is no default type for this class.
Multi-parameter type classes
Defaulting for MPTC follows the scheme for single-parameter classes.
topdecl -> default tycls type_1 type_2 ... type_n
That is, there is a single unique relation between types that can be chosen if all of its variables are otherwise unconstrained.
Open questions: if some of the variables are already resolved to actual types, is it OK to default the remaining variables? Assuming the resolved types are in the default relation anyway? What if the already-resolved types are not in the default relation? Would anyone ever want to use defaulting to choose different types depending on what other types have already been resolved?
What happens if the choice of default types is not confluent? For example:
instance Foo Float Integer
instance Foo Double Int
default Fractional Double
default Num Integer
(Fractional a, Foo a b, Num b) => e
Here, if you choose 'a' first, using the default Fractional Double, then because you have an instance of Foo Double Int, then 'b' must be Int. But if you choose 'b' first, using the default Num Integer, then because you have an instance Foo Float Integer, then 'a' must be Float. One suggestion might be that defaulting will only occur if the results are confluent, i.e. the compiler should try all possible orderings in which to default variables, and if they do not come up with the same answer, then reject the program.
Pros
- simpler, more general, and less ad hoc than current method
- overcomes the Hat transformation problem
- does not rely on textual ordering of decl
- permits defaulting of user-defined classes, not just Prelude ones
Cons
- not sure if this exactly captures the existing Haskell'98 module (but because defaults are currently limited to Prelude classes, it probably does)
- the story for MPTC is not altogether clear yet
Proposal 3 - global scope
Orthogonal to the issue of how to specify defaults, is the question of whether they should be module-local, or if instead we should treat them like instance declarations - global in scope. One can also imagine permitting explicit lexical scoping, i.e. a local override of the defaults, purely within a single function definition.
Concrete proposal: a default decl can occur anywhere that a type signature would be valid, and has the same scope. However, because default decls cannot be named, all default topdecls must be unique throughout a program. By contrast, a local default decl can override one at an outer scope, but only within its own inner scope.
Pros
- Arguably, when user-defined classes and types are involved, it is a lot clearer to make any necessary default decls once only, in a library, and just have them apply everywhere, rather than to require end-users to understand the issues and make their own default decls.
- Having consistent defaults throughout a program is semantically nicer (but you still get the opportunity to override them locally if you really need to - just like with operator fixities).
Cons
- Changes the Haskell'98 behaviour (where defaults are module-local). Question: Do any real programs actually rely on the Haskell'98 spec here?
Proposal 4 - remove defaulting
It is generally agreed that defaulting, in its current form at least, is a wart on the language. The main motivation behind it is to make simple calculator-like uses of interactive Haskell environments possible.
This proposal, then, is to remove defaulting from the language; we would expect that interactive environments will continue to default as they think best. Note that implementations already go beyond what is stated in the report when defaulting.
Most(?) instances of defaulting in Real Programs are due to (^). If this proposal is adopted then we would recommend changing the type of (^) and introducing genericPower (or some better name) thus:
(^) :: (Num a) => a -> Int -> a
genericPower :: (Num a, Integral b) => a -> b -> a
This is similar to the scheme used by, for example, genericIndex.
Pros
- Easy to implement and explain.
- Makes the language smaller.
- Trivially fixes any problems tools like hat have with defaulting.
Cons
- No pretense at trying to remain compatible with Haskell '98, but how many uses of defaulting are there in the wild? And how many not covered by (^)?