type fine until you try to use it

Hal Daume III hdaume@ISI.EDU
Tue, 14 Jan 2003 10:22:34 -0800 (PST)


A few things.

If you give newFilterIS a type signature it works fine.  Note that this
requires a higher-rank type, but that's okay:

> data FilterIS = FilterIS { source :: InputStream s => s, filter 
>    :: Filter }

> newFilterIS :: (forall s . InputStream s => s) -> Filter -> FilterIS
> newFilterIS = FilterIS

this is just because ghc can't (and not because of any deficiency on its
part) infer higher-ranked types.

I'm not sure that this is what you want, though.  Presumably you want it
so that if 'x' is a type which is an instance of InputStream and 'foo
:: InputStream s => s -> Bool' then you can write:

> runFilterIS :: FilterIS -> Bool
> runFilterIS (FilterIS src _) = foo src

but this won't work, because 'source' is universally quantified.  That is,
in this above expression, src has type 'forall s . InputStream s =>
s'.  This means that whatever you do with it must have that type on the
LHS.  THis is not so for foo.  foo would need to have type '(forall s
. InputStream s => s) -> Bool', instead of 'forall s . InputStream s => s
-> Bool'.

The difference was explained quite nicely here:

  http://haskell.org/pipermail/haskell-cafe/2002-August/003300.html

Now, to get what I think you might want, you might try existential types,
as in:

> data FilterIS2 = forall s . InputStream s => FilterIS2 s Filter
>
> newFilterIS2 :: forall s . InputStream s => s -> Filter -> FilterIS2
> newFilterIS2 = FilterIS2
>
> runFilterIS2 (FilterIS2 src _) = foo src

which performs as I think you expect.

HTH and I hope I didn't say anything incorrect :P

 - Hal

--
Hal Daume III

 "Computer science is no more about computers    | hdaume@isi.edu
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

On Mon, 13 Jan 2003, Abraham Egnor wrote:

> In a project I'm working on, one data type I've defined is this:
> 
> data FilterIS = FilterIS { source :: (InputStream s) => s, filter ::
> Filter }
> 
> which, to me, just means it holds any instance of the InputStream class
> and a Filter value.  Sure, says ghci, fine by me.  However, if I try to do
> anything with that datatype, even something as simple as
> 
> newFilterIS = FilterIS
> 
> I get the following error, or something very like it:
> 
> Stream.hs:96:
>     Inferred type is less polymorphic than expected
>         Quantified type variable `s' escapes
>         Expected type: s -> t
>         Inferred type: (forall s1. (InputStream s1) => s1)
>                        -> (forall fs. (InputStream fs) => fs -> IO Word8)
> -> FilterIS
>     In the definition of `newFilterIS': FilterIS
> 
> I've gotten used to having to spend a while figuring out what error
> messages mean, but it bugs me that there seems to be some problem with the
> type that's "brought out" by just making a synonym for the constructor.  I
> know there's nothing wrong with the line where I define a synonym; there's
> practically nothing there to *be* wrong, so the problem has to be in the
> type... and yet the compiler didn't catch it until I added that synonym
> line.  What's up?
> 
> Abe
> 
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>