[Haskell-cafe] trick to easily generate Eq/Ord instances
Henning Thielemann
lemming at henning-thielemann.de
Tue Dec 13 10:12:41 EST 2005
On Mon, 12 Dec 2005, Bulat Ziganshin wrote:
> Hello
>
> sometimes, Eq/Ord classes can't be derived automatically because we
> need to comare only part of fields. in such situations i use the
> following trick to easify generation of class instances:
>
> data ArchiveBlock = ArchiveBlock {
> blArchive :: Archive
> , blType :: BlockType
> , blCompressor :: Compressor
> , blPos :: Integer
> , blOrigSize :: Integer
> , blCompSize :: Integer
> , blCRC :: CRC
> , blFiles :: Int
> }
>
> instance Eq ArchiveBlock where
> (==) = map2eq $ map3 (blArchive,blPos,blCRC)
>
> instance Ord ArchiveBlock where
> compare = map2cmp $ map2 (blArchive,blPos)
>
> {-
> instance Ord ArchiveBlock where
> compare = map2cmp blPos -- for comparision on just one field
> -}
I solved that problem with two generic functions:
Compare the same item of two records.
> compareField :: Ord b => (a -> b) -> a -> a -> Ordering
> compareField f x y = compare (f x) (f y)
Lexicographically compare a list of attributes of two records.
> compareRecord :: [a -> a -> Ordering] -> a -> a -> Ordering
> compareRecord cs x y =
> head (dropWhile (EQ==) (map (\c -> c x y) cs) ++ [EQ])
Use it this way:
> instance Ord ArchiveBlock where
> compare =
> compareRecord
> [compareField blArchive,
> compareField blPos,
> compareField blCRC]
More information about the Haskell-Cafe
mailing list