Re: [Haskell-cafe] trick to easily generate Eq/Ord instances

2005-12-13 Thread Henning Thielemann


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]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] trick to easily generate Eq/Ord instances

2005-12-13 Thread Bulat Ziganshin
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
-}



-- Utility functions
map2   (f,g) a  =  (f a, g a)
map3 (f,g,h) a  =  (f a, g a, h a)
keyval  f x=  (f x, x)-- |Return pair containing computed 
key and original value
map2cmp f x y  =  (f x) `compare` (f y)   -- |Converts "key_func" to 
"compare_func"
map2eq  f x y  =  (f x) == (f y)  -- |Converts "key_func" to "eq_func"
  



-- 
Best regards,
 Bulat  mailto:[EMAIL PROTECTED]



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe