[Haskell-cafe] Fwd: Type families - how to resolve ambiguities?
Paolo Giarrusso
p.giarrusso at gmail.com
Sat Sep 11 19:55:20 EDT 2010
On Aug 25, 11:22 pm, Dan Doel <dan.d... at gmail.com> wrote:
> On Wednesday 25 August 2010 5:05:11 pm DavidA wrote:
> > The code below defines a type synonym family:
>
> > {-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}
> > {-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-}
[snip]
> The problem with mult is that k is not specified unambiguously. You either
> need v to determine k (which is probably not what you want, at a guess), mult
> to take a dummy argument that determines what k is:
[...]
> or, to make Tensor a data family instead of a type family.
What is the difference making it work?
However, it would make more sense to have it be a type family, without
the overhead of data (both in space and in typing). Is there a non-
hacky approach, without dummies and without making Tensor a data
family without a semantic need?
I am having a similar problem with the vector package, with the
Data.Vector.Generic.Mutable module, because of the PrimState type
family. How am I expected to best solve this?
This function is easy to write:
fillVector n elems = do
arr <- VectorGM.new n
VectorG.copy arr $ VectorG.fromList elems
return arr
However, what I have below is not easy to write for me - some specific
type annotations are needed. Interestingly, I needed to annotate a
statement rather than the return value, because unifying PrimState IO
and PrimState m fails, rather than producing m = IO. While I managed
to make them work, it looks like type inference is not helping much -
the code seems more complicated to properly type-annotate than it
would be in a language with just typechecking.
V1, not generic - it works for arrays of integers:
fillSortVector n elems = do
arr <- VectorGM.new n :: IO (VectorU.MVector (PrimState IO) Int) --
I can't annotate just arr, I need to annotate the IO action!
-- arr :: (VectorU.MVector (PrimState IO) Int) <- VectorGM.new n --
doesn't compile!
let arrI :: VectorU.Vector Int = VectorG.fromList elems
VectorG.copy arr arrI
(timing, _) <- timed $ VectorI.sort arr
return timing
V2, almost fully generic - but not in the array types (that was even
more complicated IIRC):
fillSortVector :: forall a. (Ord a, VectorG.Vector VectorU.Vector a,
VectorGM.MVector VectorU.MVector a) =>
Int -> [a] -> IO Double
fillSortVector n elems = do
arr <- VectorGM.new n :: IO (VectorU.MVector (PrimState IO) a) -- I
can't annotate just arr, I need to annotate the IO action!
-- arr :: (VectorU.MVector (PrimState IO) a) <- VectorGM.new n --
doesn't compile!
let arrI :: VectorU.Vector a = VectorG.fromList elems
VectorG.copy arr arrI
(timing, _) <- timed $ VectorI.sort arr
return timing
Best regards
Paolo G. Giarrusso -- PhD student
More information about the Haskell-Cafe
mailing list