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.
module TypeCast where
data FooBar foo bar = --- Indirect composite
Foo { unFoo :: foo}
| Bar { unBar :: bar}
--- 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
[EMAIL PROTECTED] { unFoo = foo} -> -- We only need to change foo
TF $ f{unFoo = 1}
[EMAIL PROTECTED] { 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: ([EMAIL PROTECTED] {unBar = bar}) -> TF $ b
--- what is the fix? Basically do a noop on b
--- [EMAIL PROTECTED] {unBar = bar} ->
--- TF $ b{unBar = bar}
Cheers,
Christophe
--
Christophe Poucet
Ph.D. Student
Phone:+32 16 28 87 20
E-mail: Christophe (dot) Poucet (at) imec (dot) be
Website: http://notvincenz.com/
IMEC vzw – Register of Legal Entities Leuven VAT BE 0425.260.668 – Kapeldreef 75, B-3001 Leuven, Belgium – www.imec.be
*****DISCLAIMER*****
This e-mail and/or its attachments may contain confidential information. It is
intended solely for the intended addressee(s).
Any use of the information contained herein by other persons is prohibited.
IMEC vzw does not accept any liability for the contents of this e-mail and/or
its attachments.
**********
_______________________________________________
Haskell mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell