On Tue, 2007-05-29 at 21:28 +0100, Andrew Coppin wrote:

> > phantom types:
> >  the types of ghost values (in other words, we are only interested in
> >  the type, not in any value of that type).

> Mmm... Still not seeing a great amount of use for this one.

The point is to 'tag' something with a type (at compile time) without
actually having any value of that type around at run time.

For instance, you could use this to keep track of the encodings for
strings of 8-bit characters.

Say you have a data type for your strings, like so:

        data FPS enc = FPS [Word8] deriving Show

'enc' is now a phantom type, it has no bearing on the actual value,
which is always a list of Word8s, right?

You can then define a set of encoding data types, and class for them:

        data Latin1
        data KOI8R

        class Encoding e where
           w2c :: e -> Word8 -> Char
           c2w :: e -> Char  -> Word8

The Latin1 instance is easy:

        instance Encoding Latin1 where
           w2c _ = chr . fromIntegral
           c2w _ = fromIntegral . ord

KOI8 is a bit more involved, so I omit that.  Now we can define
functions for converting to/from [Char]:

        pack :: forall e . Encoding e => String -> FPS e
        pack = FPS . map (c2w (undefined :: e))

        unpack :: forall e . Encoding e => FPS e -> String 
        unpack (FPS s) = map (w2c (undefined :: e)) s

Loading this in GHCi (requires -fglasgow-exts), you can do:

        *Main> pack "foobar"  :: FPS Latin1
        FPS [102,111,111,98,97,114]

i.e. ord 'f' to ord 'r'.

        *Main> pack "foobar"  :: FPS KOI8R
        FPS [202,211,211,198,197,214]

This is a fake KOI8R instance, but demonstrates the point: by requiring
a different type, a different result is achieved.  Note that the
resulting FPS retains the type, so that when I do:

        *Main> unpack it
        "foobar"

...I get back the original string.

Disclaimers: There are more elaborate and elegant examples of phantom
types out there, look for e.g. Oleg's posts on the subject.  The above
does not constitute legal advice.  Slippery when wet, do not cover,
batteries not included, and your mileage may vary.

-k




_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to