
Ah, ok, so the reason what I trying didn't work is because I used an
actual type instead of a type variable? I got confused because of the
emphasis you put on * distinct *.
And so, if I want to make Maps applicative functors without dealing
with FlexibleInstances, I'd have to do something like this?
import Control.Applicative
import qualified Data.Map as M
import Data.Monoid
instance (Monoid k, Ord k) => Applicative (M.Map k) where
pure x = M.fromList [(mempty,x)]
fs <*> xs = M.fromList [(k1 `mappend` k2,v1 v2) | (k1,v1) <-
M.assocs fs, (k2,v2) <- M.assocs xs]
(sacrificing some functionality, since spaces won't get intercalated
between keys if i use strings)
On Thu, Sep 2, 2010 at 4:31 PM, Daniel Fischer
On Thursday 02 September 2010 22:06:45, Alec Benzer wrote:
Because the language specification imposed that instance declarations must have the form
I guess I meant why does the language specification impose this?
Historical accident, probably. Perhaps it's easier to implement.
instance Class (T a1 a2 ... an) where ...
where T is a type constructor, 0 <= n and a1, a2, ..., an are *distinct* type variables.
I don't understand, what you you mean by distinct? Like how is String not a distinct type variable by itself?
distinct = different, however, String is not a type variable, it's a type (more specifically, a type synonym). Type variables start with a lowercase letter, things starting with an uppercase letter are type constructors (in this context), same as for values
f True = whatever -- True is a data constructor f true = whatever -- true is a variable, matches anything
So in Haskell98 (and Haskell2010),
instance Class (Either a b) where ...
is a legal instance declaration, the instance head is a type constructor (Either) applied to two distinct type variables.
Not legal are
instance Class (Either a a) where ...
(type variables not distinct),
instance Class (Either Char a) where ...
(Char is not a type variable).
It's an inconvenient restriction, so you can turn on FlexibleInstances to allow the latter two instances (not both in the same programme, though, that would need the dreaded OverlappingInstances).