[Haskell-cafe] default function definitions
Daniel Fischer
daniel.is.fischer at web.de
Sat Jul 24 14:28:56 EDT 2010
On Saturday 24 July 2010 19:59:26, Patrick Browne wrote:
>
> module A where
> data Person = Person String Integer deriving Show
> data Employee = Employee String Integer deriving Show
>
> class C1 c1 where
> age :: c1 -> Integer
> -- add default impl, can this be defined only once at class level?
> -- Can this function be redefined in a *class* lower down the heirarchy?
> age(c1) = 1
That would normally be written
age _ = 1
Yes, a default implementation of a class method can only be given in the
class definition, it can't be redefined, but it can be overridden in an
instance declaration. For example
instance C1 Person where
age _ = 3
instance C1 Employee where
age (Employee _ n) = n
>
>
> -- Is it true that instances must exists before we can run function or
> make subclasses?
> instance C1 Person where
> instance C1 Employee where
You can *call* class methods only for types which are instances of that
class.
You can define "subclasses" [not to confuse with OO-subclasses] of C1 even
if there are no instances of C1 in scope.
>
>
> -- Is it true that C2 can inherit age, provided an instance of C1 exists
> class C1 c2 => C2 c2 where
> name :: c2 -> String
> name(c2) = "C2"
A compiler/interpreter can accept an instance declaration of C2 for a type
only if an instance of C1 for that type in scope [defined in the same
module or in a module directly or indirectly imported; class instances are
always re-exported from a module].
Since an instance of C2 must also be an instance of C1, all methods of C1
can be applied to that type.
>
>
> instance C2 Person where
> instance C2 Employee where
>
> -- Is it true that C3 cannot override C1 or C2 existing defaults?
> -- Is it true that this must be done at instance level?
> -- class Cx c3 => C3 c3 where
> -- age(c3) = 3
> --
>
True. Default methods can only be overridden in instance declarations for
the class.
More information about the Haskell-Cafe
mailing list