[Haskell] pattern matching on record fields and position

David Roundy droundy at darcs.net
Wed Nov 2 09:07:41 EST 2005


Hello fellow haskellers,

I have a couple of related (almost conjugate) proposals/questions.
Basically, I've been thinking about how to make code more robust with
respect to changes in the data types.

Pattern matching based on positions is very fragile (I don't think this is
a surprise to anyone).  When you add a new field to a data type, you have
to modify every bit of code that uses positional pattern matching, such as

lengthPS (PS _ _ l) = l

I'd like to be able export a data type with constructors in such a way that
positional pattern matching isn't possible--but field-based pattern
matching *is* possible.  One could just use a coding policy, but I like the
compiler enforcing things like this for me.  Perhaps there's already a
trick to do this?

In particular, this would be relevant if I had the following data type:

data FPS = PS { fp :: ForeignPtr Word8, my_start :: Int, my_length :: Int }

I would like to be able to export this data constructor (in actual
FastPackedString, the constructor isn't exported at all--and shouldn't
be--but I'm taking this as a simple hypothetical example).

I would like users (who import this module) to be able to write

case fps of { PS { my_start = s } -> print s }

but not to write

case fps of { PS _ s _ -> print s }

If I could enforce this, then I could change the definition of FPS to

data FPS = PS { fp :: ForeignPtr Word8, my_start :: Int, my_length :: Int,
                extra_argument :: String }

or

data FPS = PS { fp :: ForeignPtr Word8, my_length :: Int, my_start :: Int }

and have a guarantee that no code that imports the module will be broken.
In the first example, all positional-matching code would fail to compile.
The second is even more insidious, since code would continue to compile,
but would be wrong!


The second feature I'd like (and even better if it's something that already
exists, although I've been told that it isn't) would be to be able to have
record field names that are exported so as to not allow them to be used as
accessor functions if those functions might lead to failure.  For example:

data Foo = AB { a :: String, b :: Int } | B { b :: Int }

I would like "a" to be useable for pattern matching, but not as the
function "a :: Foo -> String", which is dangerous, in that it really ought
(in my opinion) to have the type Foo -> Maybe String.

Actually, a compiler warning when using dangerous functions of this sort
(as we can get when we use non-comprehensive pattern-matching) would
satisfy me, although I'd really prefer to be able to have these accessor
functions not be generated, or at least have an option to not export them.

As you can probably tell, I've been thinking about how one can export
constructors and yet still maintain flexibility in the implementation of
data structures.  Pattern matching is very nice, and often one wouldn't
want to give it up, but it seems to completely tie down the implementation
of data type, which is annoying, and seems to be a tradeoff that we could
avoid by a combination of using field descriptors for pattern matching
constructors.  The catch being that for data types with multiple
constructors, field descriptors always introduce "unsafe" functions that
I'd really prefer didn't exist.
-- 
David Roundy
http://www.darcs.net


More information about the Haskell mailing list