[Haskell-cafe] Context for type parameters of type constructors

Dylan Thurston dpt at lotus.bostoncoop.net
Sat Apr 3 10:04:56 EST 2004


On Sat, Apr 03, 2004 at 01:35:44PM +0200, Henning Thielemann wrote:
>   (I like to omit  -fallow-undecidable-instances
>    before knowing what it means)

There's a nice section in the GHC user's manual on it.  I can't add
anything to that.

> > -- a classical linear space
> > class VectorSpace v a where
> >    zero  :: v
> >    add   :: v -> v -> v
> >    scale :: a -> v -> v

You might want to add a functional dependency, if you only have one
type of scalars per vertor space:

> class VectorSpace v a | v -> awhere
>    zero  :: v
>    add   :: v -> v -> v
>    scale :: a -> v -> v

But then again, you might not.

> > instance Num a => VectorSpace a a where
> >    zero  = 0
> >    add   = (+)
> >    scale = (*)
> 
> Here the compiler complains the first time:
> 
> VectorSpace.lhs:27:
>     Illegal instance declaration for `VectorSpace a a'
>         (There must be at least one non-type-variable in the instance head
>          Use -fallow-undecidable-instances to permit this)
>     In the instance declaration for `VectorSpace a a'

Well, you know how to fix this...

Another way to fix it is to add a dummy type constructor:

> newtype Vector a = Vector a
>
> instance Num a => VectorSpace (Vector a) a

Later:
> > instance Num a => VectorSpace [a] a where

By the way, depending how you resolve the issue above, you might want
instead

> instance (RealFloat a, VectorSpace b a) => VectorSpace [b] a where
> ...


> Now I introduce a new datatype for a vector valued quantity.
> The 'show' function in this simplified example
> may show the vector with the magnitude separated
> from the vector components.
> ...
> The problem which arises here is that the type 'a' is used for
> internal purposes of 'show' only. Thus the compiler can't decide
> which instance of 'Normed' to use if I call 'show':

This is exactly what is fixed by adding the functional dependency
above.

Alternatively, if you want to consider varying the scalars, you can
add 'a' as a dummy type variable to 'Quantity':

> data Quantity v a = Quantity v
>
> instance (Show v, Fractional a, Normed v a) =>
>         Show (Quantity v a) where
>    show (Quantity v) =
>        let nv::a = norm v
>        in  (show (scale (1/nv) v)) ++ "*" ++
>            (show nv)

GHC still won't accept this without prompting, but now at least you
can provide a complete type:

*VectorSpace> show (Quantity [1,2,3] :: Quantity [Double] Double)
"[0.16666666666666666,0.3333333333333333,0.5]*6.0"

Note that this makes sense semantically: if you have a vector space
over both, say, the reals and the complexes, you need to know which
base field to work over when you normalize.

> So I tried the approach which is more similar
> to what I tried before with a single-parameter type class:
> I use a type constructor 'v' instead of a vector type 'v'
> ...

> > data QuantityC v a = QuantityC (v a)
> >
> > instance (Fractional a, NormedC v a, Show (v a)) =>
> >         Show (QuantityC v a) where
> >    show (QuantityC v) =
> >        let nv = normC v
> >        in  (show (scaleC (1/nv) v)) ++ "*" ++
> >            (show nv)
> 
> It lead the compiler eventually fail with:
> VectorSpace.lhs:138:
>     Non-type variables in constraint: Show (v a)
>     (Use -fallow-undecidable-instances to permit this)
>     In the context: (Fractional a, NormedC v a, Show (v a))
>     While checking the context of an instance declaration
>     In the instance declaration for `Show (QuantityC v a)'

Hmm, I don't know how to fix up this version.

Peace,
	Dylan
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://www.haskell.org//pipermail/haskell-cafe/attachments/20040403/46a1d7eb/attachment.bin


More information about the Haskell-Cafe mailing list