[Haskell] pattern matching on record fields and position

2005-11-02 Thread David Roundy
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
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] pattern matching on record fields and position

2005-11-02 Thread Malcolm Wallace
David Roundy [EMAIL PROTECTED] writes:

 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.

This sounds a bit like views, proposals for which have been around
for years, but never adopted.  There is a related language feature
(extension) called pattern guards which /is/ implemented in ghc,
and gives most of the power of views.

 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?

So, you could export just the field names, but not the constructors.
Instead of patterns, use pattern guards.

 I would like users (who import this module) to be able to write
 
 case fps of { PS { my_start = s } - print s }

This would become
  case fps of { _ | s - my_start fps   - print s }

It slightly abuses the pattern guard notation, because the pattern
is a degenerate one - just a variable name - so it always succeeds.
Thus, for a type with more than one constructor, like this:

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

the similar construct
  case foo of { _ | x - a foo   - print x
  | otherwise- putStrLn error }
would never reach the otherwise clause, even when given a B constructor.
Instead, it would crash the program.

One common style people use today to enable the later extension of a datatype
is empty-record patterns:

  case foo of { A{} - print (a foo)
  ; B{} - putStrLn error }

but as you no doubt have immediately realised, this forces the
constructors to be visible, and therefore does not prevent the
programmer from using explicit positional patterns.  It is just a
convention, not enforceable.

 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.

Probably you really want extensible records, with all the rho-typing
trickery that makes it possible to decide statically whether a
particular field exists when an accessor is applied to the record.
There are several competing proposals for this - the OOHaskell one
requires no extensions to Haskell'98.

Regards,
Malcolm
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] pattern matching on record fields and position

2005-11-02 Thread John Meacham
You might want to look at the 'get', 'set' and 'update' rules that DrIFT
can derive. i made them to addres a lot of the same issues you
mentioned.

I personally think it is a travesty that 

data Foo = Foo { a :: Int, b :: Char } | Bar { a :: Int }

let x = Bar { a = 4 }
y = x { b = 'x'} 

results in bottom rather than just leaving x unchanged.

well, travesty is too strong. but it bugs the heck out of me.

but yeah, the DrIFT code derives functions that pull out fields but
returns them in a possibly failing monad so you can properly handle a
data type with no appropriate field.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell