> -----Original Message-----
> From: Frank Atanassow [mailto:[EMAIL PROTECTED]]
> Sent: 18 September 2000 10:24
> To: Chris Angus
> Cc: [EMAIL PROTECTED]
> Subject: RE: Patterns Catalog
> 
> 
> [changed cc: to haskell-cafe]
> 
> Chris Angus writes:
>  > I have thought of a few "functional patterns"
>  > ...
>  > *) Phantom types

>  > [..]
>  > *) Decoration [transform one structure into another]
>  >            (possibly use polymorphism to make strcutures 
> the same but
>  > parameterised)

Consider Typechecking a lambda expression

data Expr = App Expr Expr
            | Var String
            | Lambda String Expr
            | Let String Expr Expr

if we apply type inference to this we would typically store intermediate
results i.e. we would convert a type Expr into a TExpr

data TExpr = TApp Type TExpr TExpr
             | TVar Type String
             | TLambda Type String TExpr
             | TLet Type String TExpr TExpr

(Forgive bugs in this example please)
So rather than simply giving a true/false
answer we can preserve intermediate results which oculd be useful later
We could parameterize this interms of types and type checking could 
be thought of as 

check :: Expr -> Maybe TExpr

data PExpr a = PApp a PExpr PExpr
               | PVar a String
               | PLambda a String PExpr
               | PLet a String PExpr PExpr

and initially populate this with () say so
type checking could be typed

check :: PExpr () -> Maybe (PExpr Type)

I'm probably not explaining this well but this sort of pattern gives
you not only the answer to a problem but also the series of steps
that you took to get there.

here we have added information but it is trivial to still view the 
structure as before. (as you can tell I need to think about examples / 
language / terms of reference yet)



> 
> What are these two? "Phantom types" = existential types?
>

Nope. Not existential types but instead the use of a type system
to guarentee well-formedness.

We create a Parameterized type in which the parameter does not appear
on the rhs (shameless cutting and pasting from Daan Leijen and Erik Meijer)

data Expr a = Expr PrimExpr 

  constant :: Show a => a -> Expr a
  (.+.)  :: Expr Int -> Expr Int -> Expr Int
  (.==.) :: Eq a=> Expr a-> Expr a-> Expr Bool
  (.AND.):: Expr Bool -> Expr Bool-> Expr Bool

  data PrimExpr
    = BinExpr   BinOp PrimExpr PrimExpr
    | UnExpr    UnOp PrimExpr
    | ConstExpr String

  data BinOp
    = OpEq | OpAnd | OpPlus | ...


i.e. the datatype is such that we could get garbage such as

BinExpr OpEq (ConstExpr "1") (ConstExpr "\"foo\")

but since we only expose the functions our attempts
to create this expression via

constant 1 .==. constant "foo" would fail to typecheck

I believe this technique is used when tryiong to interface
with a language that would cause a runtime exception if the types
were wrong but would have a go at running  the expression first 
(They use it in the context of SQL but I have also seen it in the
context of FLI work)

 
> -- 
> Frank Atanassow, Dept. of Computer Science, Utrecht University
> Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
> Tel +31 (030) 253-1012, Fax +31 (030) 251-3791
> 

Reply via email to