[Haskell] Re: (small) records proposal for Haskell '06

oleg at pobox.com oleg at pobox.com
Fri Jan 6 19:47:42 EST 2006


Joel Reymont wrote:
> How does pattern matching work with HList?
> I would like to pass a HList to a function and only match if a  
> certain field had a certain value.

The code below defines the function foo that accepts a record and
yields one value if the field PtX of the record has the value 0. If
the field has any other value, a different result is returned. The
function is written in a pattern-matching style. Also, the function is
record-polymorphic: it takes _any_ record (of any `record type') that
happens to have the field names PtX.

	*Test> :t foo
	foo :: (Num v, HasField (Proxy PtX) r v) => r -> [Char]

David Roundy wrote:
> I guess I meant to say that it hadn't been implemented for "real" records,
> and there doesn't seem to be a consensus that it's the best approach.

There had been no argument about what is best. As I understood it, the
question was about a specific proposed behavior in a hypothetical
record system. I merely wanted to point out that one does not need to
_guess_ how that feature might work in practice. One can try it right
now, and see for oneself if it works for the problem at hand or not.


{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}
{-# OPTIONS -fallow-overlapping-instances #-}

module Test where

import OOHaskell -- big overkill but convenient: it's only one line...

-- Labels
-- The more convenient labels need -fallow-overlapping-instances
-- The less convenient label representation needs fewer extensions.
-- We go for more convenient...

data PtX; px = proxy::Proxy PtX
data PtY; py = proxy::Proxy PtY

accessor r f = r # f

setter r f v = (f,v) .<. r 

point1 x = 
       px .=. x
   .*. emptyRecord

point2 x y = 
       px .=. x
   .*. py .=. (y + 10)
   .*. emptyRecord

-- Record-polymorphic function
foo p | 0 <- p # px = "X is zero"
foo _ = "something else"

test1  = foo (point1 0)
test1' = foo (point1 42)
test2 = foo (point2 10 20)
-- inline construction of the record
test3 = foo (py .=. False .*. px .=. 0 .*. emptyRecord)



More information about the Haskell mailing list