[Haskell-cafe] Of phantom types and type extentions

Thomas M. DuBuisson thomas.dubuisson at gmail.com
Tue Oct 16 21:53:45 EDT 2007


All,

I've been casually developing a PacketBB (i.e. Generalized Manet Packet
Format) library in Haskell.  I think I have a need to pass state
information as a phantom type - I'll step through the issue now.

With the 'AddressBlock' (S5.2.1 packetBB draft 8), network addresses are
abbreviated as sets of bytes (potentially just one byte each, with a
head or tail identical with other addresses).  How many bytes are in the
set is determined, in part, by the type of address stored (ex: IPv4 or
IPv6).  Thus, when serializing, I need to provide this information.

Saying this again, but in (simplified) code:

data NetworkAddress a => AddressBlock a =
      AddrBlkWire {
        lenHd   :: Word8,
        hd      :: [Word8],
        lenTl   :: Word8,
        tl      :: [Word8],
        nrAddrs :: Word8,
        addrs   :: [Word8] }
    | AddrBlkAbstract [a]

data (NetworkAddress a) => SomeHigherLevelStruct a =
        SHLS (AddressBlock a) Word32 Word8

-- length (addrs x) == ("TotalAddressLength" - lenHd - lenTl) * nrAddrs

I can think of several ways to convert between AddrBlkWire and
ByteStrings:
1) Make separate instance of 'Binary' for each data type element of
NetworkAddress.
instance Binary (AddressBlock IPv4) where
        get = ...
        put = ...
instance Binary (AddressBlock IPv6) where
        get = ...
        put = ...

This solution immediately causes problems with every higher level
structure you wish to serialize.  For example, now you have to have
individual instance for SHLS, you can't do:

instance (NetworkAddress a) => Binary (SomeHigherLevelStruct a) where
        ...

2) You can pass another argument into a custom 'get' routine.  I see
this as a hack that makes me break a good naming convention.

getNetworkAddress :: Int        -- bytes per address
        -> Get NetworkAddress

3) If you don't worry about decoding, only encoding, then an extra field
in the data structure can fill the void of an extra argument.  Also a
hack.

I'm hoping someone here has a better solution.  Perhaps I am making a
mountain out of a mole hill, or perhaps this requires one of those type
system extensions I have yet to look hard at.  The solution I would want
looks like this:

class NetworkAddress a where
        addressByteSize :: a -> Int

instance (NetworkAddress a) => Binary (AddressBlock a) where
        get = do
                lenH <- get
                h    <- replicateM get (fromIntegral lenH)
                lenT <- get
                t    <- replicateM get (fromIntegral lenT)
                nr   <- get
                let addrSize = addressByteSize (undefined :: a)
                    bytes = (addrSize - lenH - lenT) * nr
                addrs <- replicateM get (fromIntegral bytes)
                return ...

The line 'addrSize = ' is what I don't know how to write.  How does one
call an instance of a type class without knowing the type at compile
time?

Thanks,
Tom

-- 
"The philosophy behind your actions should never change, on the other
hand, the practicality of them is never constant." - Thomas Main
DuBuisson



More information about the Haskell-Cafe mailing list