[Haskell-cafe] Re: [Haskell] TypeCasting in Haskell

Robert Dockins robdockins at fastmail.fm
Wed May 24 10:55:53 EDT 2006


On May 24, 2006, at 7:30 AM, Christophe Poucet wrote:
> Dear all,
>
> I typically use indirect composite for making AST's. It allows me  
> to easily make new types with other annotations without having to  
> duplicate all elements but only those that actually change. It also  
> allows a whole amalgam of other possibilities. Recently I have  
> observed a type error which seems to be fixable only by doing a  
> "typecast". What do I call a typecast, you may ask? Basically a  
> noop that changes the type. Here attached you will find the code  
> that demonstrates this.

Is there a specific question in here?

>> module TypeCast where
>>
>> data FooBar foo bar = --- Indirect composite
>> Foo { unFoo :: foo}
>> | Bar { unBar :: bar}

BTW, this is pretty much just the Either type from the prelude.  I'm  
not familiar with the term 'indirect composite' (it sounds like a GoF- 
ism...), but this construction is often called 'disjoint union' in  
the papers I've read.

>> --- Assume some PFoobar (parsed)
>> data PFooBar = PF {unPF :: FooBar String String}
>> --- Assume some TFoobar (typed)
>> data TFooBar = TF {unTF :: FooBar Int String }
>>
>> -- Merrily we write our conversion, using binding to optimize  
>> slightly
>> typer :: PFooBar -> TFooBar
>> typer pFooBar =
>> case unPF pFooBar of
>> f at Foo { unFoo = foo} -> -- We only need to change foo
>> TF $ f{unFoo = 1}
>> b at Bar { unBar = bar} -> -- We don't need to change this string
>> TF $ b -- So we just return b

>> --- Nice little main to make this a full module:
>> main :: IO ()
>> main = do
>> print . typer . PF . Foo $ "Hello"
>>
>> --- Type error:
>> -- TypeCast.hs:19:11:
>> -- Couldn't match `Int' against `String'
>> -- Expected type: FooBar Int String
>> -- Inferred type: FooBar String String
>> -- In the second argument of `($)', namely `b'
>> -- In a case alternative: (b at Bar {unBar = bar}) -> TF $ b
>>
>> --- what is the fix? Basically do a noop on b
>> --- b at Bar {unBar = bar} ->
>> --- TF $ b{unBar = bar}

As you noted, the correct way to do this is to destruct the value and  
reconstruct.  It's a little irritating, and it often happens in code  
using Either and similar constructs.

If you rewrite as using Either, and remove a few 'data' wrappers, you  
get:

typer:: Either String String -> Either Int String
typer = either (const (Left 1)) Right

Or:

typer (Left _) = Left 1
typer (Right x) = Right x


Where you can clearly see the destruction/construction pair.  You can  
wrap this up in helper functions, but I don't think there's any real  
way to remove it altogether.  (well, there's always unsafeCoerce#,  
but I can't really recommend you play around with that).  Obviously  
this can become a pretty big pain if you've got more than just a few  
constructors and/or deeply nested datatypes.

If the boilerplate becomes a serious problem, you can investigate one  
of the systems for generic programming in Haskell.  Scrap Your  
Boilerplate, Strafunski and, the GHC -fgenerics option are the ones I  
know of.


> Cheers,
> Christophe


Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
           -- TMBG



More information about the Haskell-Cafe mailing list