[Haskell-cafe] Help me understand this pattern

Justin Bailey jgbailey at gmail.com
Thu Mar 20 18:57:50 EDT 2008


All,

Yesterday I wrote some code I thought was very clever (even though I
stole most of it) and I wonder what the pattern is. I have seen it in
at least one other place, and I suspect it's well known to long-time
Haskellers.

The problem I wanted to solved was creating a combinator that could be
defined to take any number of differently typed arguments and convert
them to a more fundamental representation. To be concrete, I have a
data type Expr:

  data Expr a = ...

where a is a phantom type. I wanted users of the library (haskelldb)
to be able to define functions[1] such as:

  -- Trim whitespace from the expression given.
  trim :: Expr a -> Expr String
  -- Pad the expression given to the correct length with the given
string, if one is given.
  rpad :: Expr a -> Expr Int -> Maybe String -> Expr String

I wanted them to be able to do this using one combinator from the
library and I did not want to expose the guts of the library so they
could define the functions directly in the untyped, primitive
representation. That is, I did NOT want to define my combinator as:

  func :: String -> [PrimExpr] -> Expr a

Using ideas already in haskelldb, I came up with this:

  data ExprNil = ExprNil
  data ExprCons h tl = ExprCons h tl

  func :: String -> (ExprNil -> ExprCons (Expr e) tl) -> Expr o
  arg :: (Expr a) -> (tl -> ExprCons (Expr a) tl)

Using these two functions, I could define trim and rpad via
composition and I did not have to expose a primitive representation or
use an existentially quantified data type[2]:

  trim str = func "trim" $ arg str

  rpad str len (Just pad_str) = func "rpad" $ arg str . arg len . arg
(toExpr pad_str)
    where
      toExpr :: String -> Expr String

  rpad str len Nothing = func "rpad" $ arg str . arg len

Notice how in the second case of 'rpad', the function defined only has
two arguments since no padding character was provided.

With that background, I'm hoping others can tell me what this
generalizes too. It's pretty clear I'm working with type-level lists,
but I'm sure there is more. Is this encoding existentials? Is the
(ExprCons hd tl) type really a continuation? I'm positive this is a
well-known pattern and I'd really like to learn more about it
(history, other uses, libraries that depend on it, etc.).

Thanks in advance!

Justin

[1] These functions are used to generate SQL code and do not actually
do the operations given. For example, trim causes the "trim" function
to be applied to the column given when the SQL is actually generated.
[2] Just a note that these functions are NOT in haskelldb right now -
this is my own experimentation.


More information about the Haskell-Cafe mailing list