Phantom type

From HaskellWiki
Revision as of 03:55, 22 December 2010 by Benmachine (talk | contribs) (include notes about more mundane uses; snip out outdated links)
Jump to navigation Jump to search

A phantom type is a type used only to construct other types; its values are never used. Phantom types are useful in a variety of contexts: in the standard Data.Fixed module they are used with type classes to encode the precision being used, with smart constructors or GADTs they can encode information about how and where a value can be used, or with more exotic extensions they can be used in type arithmetic or for encoding bounds checks in the type system.

An extension to Haskell 98 supported by GHC allows you to define datatypes without any constructors (and therefore no values other than bottom):

data MyType

This lets the compiler (and programmer!) recognize phantom types and ensure they aren't used improperly.

The use of a type system to guarantee 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
(.&&.) :: 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 trying 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.)

-- ChrisAngus

A foundation for embedded languages provides some formal background for embedding typed languages in Haskell, and also its references give a fairly comprehensive survey of uses of phantom types and related techniques.