[Haskell-cafe] Of phantom types and type extentions

Bertram Felgenhauer bertram.felgenhauer at googlemail.com
Tue Oct 16 02:38:32 EDT 2007


Thomas M. DuBuisson wrote:
> 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 following works in Haskell 98:

     get = let
        result = do
            lenH <- get
            h    <- replicateM get (fromIntegral lenH)
            lenT <- get
            t    <- replicateM get (fromIntegral lenT)
            nr   <- get
            let addrSize = addressByteSize (getAddressType result)
                bytes = (addrSize - lenH - lenT) * nr
            addrs <- replicateM get (fromIntegral bytes)
            return ...

        getAddressType :: Get (AddressBlock a) -> a
        getAddressType _ = undefined
      in
        result

The trick is to use an auxillary function (getAddressType) to
extract a value of the desired type from the result type of get.

This is one of the few places where the monomorphism actually helps;
without it, 'result' would get a polymorphic type and the right
instance of NetworkAddress would remain undetermined.

There's probably a solution using pattern signatures [1] but I couldn't
get it to work in my first attempt. I didn't try scoped type variables [2].

[1] http://tinyurl.com/2533oc
(http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#pattern-type-sigs)
[2] http://tinyurl.com/2ypmvx
(http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#scoped-type-variables)

HTH,

Bertram


More information about the Haskell-Cafe mailing list