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

Bulat Ziganshin bulatz at HotPOP.com
Mon Dec 12 12:20:40 EST 2005


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:bulatz at HotPOP.com





More information about the Haskell-Cafe mailing list