[Haskell-cafe] reading existential types

Claus Reinke claus.reinke at talk21.com
Mon Jul 9 16:41:32 EDT 2007


>>  which is the important hint! the parser used for 'read' depends on
>>  the return type, but the existential type _hides_ the internal type
>>  which would be needed to select a read parser.
> 
> forall e . (MyClass e, Show e, Read e) => MT (e,Int)

the 'Read' there ensures that we only inject types that have a reader,
but it doesn't help us select one of the many possible types which
have such a reader.
 
>>     readMT :: ReadPrec MyType
>>     readMT = prec 10 $ do
>>            Ident "MT" <- lexP
>>            parens $ (do { m <- readPrec; return (MT (m::(TipoA,Int))) })
>>             `mplus` (do { m <- readPrec; return (MT (m::(TipoB,Int))) })
> 
> The problem is that I was trying to find a way to define the class
> (MyClass) and not writing a parser for every possible type (or even
> using their show-representation): I wanted a polymorphic list of types
> over which I could use the method defined for their class, but, as far
> as I can get it, this is not possible.

i'm not sure i understand the problem correctly, but note that the branches
in 'readMT' have identical implementations, the only difficulty is instantiating
them at different hidden types, so that they try the appropriate 'Read' 
instances for those types. there's no need for different parsers beyond 
the 'Read' instances for every possible type.

hiding concrete types in existentials sometimes only defers problems
instead of solving them, but exposing class interfaces instead of types 
is a useful way to mitigate that effect. it just so happens that this 
particular problem, reading an existential type, slightly exceeds that 
pattern, as 'read' needs to know the hidden type to do its job ('read' 
does not determine the type from the input form, but uses the type 
to determine what form.the input should have). 

a workaround is to try to read all possible types, then hide the type 
again once a match is found. the main disadvantage of this method 
is that we need a list of all the types that could possibly be hidden
in 'MyType' (or at least a list of all the types that we expect to
find hidden in 'MyType' when we read it).

we can, however, abstract out that list of types, and write a general
type-level recursion to try reading every type in such a list:

  class ReadAsAnyOf ts ex -- read an existential as any of hidden types ts
    where readAsAnyOf :: ts -> ReadPrec ex

  instance ReadAsAnyOf () ex
    where readAsAnyOf ~() = mzero

  instance (Read t, Show t, MyClass t, ReadAsAnyOf ts MyType) 
        => ReadAsAnyOf (t,ts) MyType
    where readAsAnyOf ~(t,ts) = r t `mplus` readAsAnyOf ts
            where r t = do { m <- readPrec; return (MT (m `asTypeOf` (t,0))) }

  -- a list of hidden types
  hidden = undefined :: (TipoA,(TipoB,()))

  readMT :: ReadPrec MyType
  readMT = prec 10 $ do
             Ident "MT" <- lexP
             parens $ readAsAnyOf hidden -- r T1a `mplus` r T1b

> Thanks for your kind attention.

you're welcome!-) reading existentials (or gadts, for that matter) 
is an interesting problem. sometimes too interesting..

claus



More information about the Haskell-Cafe mailing list