Phantom type

From HaskellWiki
Revision as of 17:47, 31 July 2011 by Benmachine (talk | contribs) (re-mention empty types)
Jump to navigation Jump to search

A phantom type is a parametrised type whose parameters do not all appear on the right-hand side of its definition, e.g. from Control.Applicative:

newtype Const a b = Const { getConst :: a }

Here Const is a phantom type, because the b parameter doesn't appear after the = sign.

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 for encoding bounds checks in the type system.

Since the values of type parameters in a phantom type may be unused, they are often used in combination with empty types.

Simple examples

A phantom type will have a declaration that looks something like this:

data FormData a = FormData String

This looks strange since at first it seems the type parameter is unused and could be anything, without affecting the value inside. Indeed, one can write:

changeType :: FormData a -> FormData b
changeType (FormData str) = FormData str

to change it from any type to any other. However, if the constructor is not exported then users of the library that defined FormData can't define functions like the above, so the type parameter can only be set or changed by library functions. So we might do:

data Validated
data Unvalidated

-- since we don't export the constructor itself,
-- users with a String can only create Unvalidated values
formData :: String -> FormData Unvalidated
formData str = FormData str

-- Nothing if the data doesn't validate
validate :: FormData Unvalidated -> Maybe (FormData Validated)
validate (FormData str) = ...

-- can only be fed the result of a call to validate!
useData :: FormData Validated -> IO ()
useData (FormData str) = ...

The beauty of this is that we can define functions that work on all kinds of FormData, but still can't turn unvalidated data into validated data:

-- the library exports this
liftStringFn :: (String -> String) -> FormData a -> FormData a
liftStringFn fn (FormData str) = FormData (fn str)

-- the validation state is the *same* in the return type and the argument
dataToUpper :: FormData a -> FormData a
dataToUpper = liftStringFn (map toUpper)

With type classes, we can even choose different behaviours conditional on information that is nonexistent at runtime:

class Sanitise a where
  sanitise :: FormData a -> FormData Validated

-- do nothing to data that is already validated
instance Sanitise Validated where
  sanitise = id

-- sanitise untrusted data
instance Sanitise Unvalidated where
  sanitise (FormData str) = FormData (filter isAlpha str)

This technique is perfect for e.g. escaping user input to a web application. We can ensure with zero overhead that the data is escaped once and only once everywhere that it needs to be, or else we get a compile-time error.

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.