Num instances for Sum and Product

Dan Burton danburton.email at gmail.com
Wed Feb 22 20:19:07 CET 2012


Data.Monoid in the base package specifies newtypes Sum and Product. It
would be convenient if these newtypes had appropriate Num instances, which
are trivial to write in plain Haskell:

import Data.Monoid
liftTy2 wrap unwrap op x y = wrap $ unwrap x `op` unwrap yliftTy wrap
unwrap f = wrap . f . unwrap
liftSum = liftTy Sum getSumliftSum2 = liftTy2 Sum getSum
instance (Num a) => Num (Sum a) where
  (+) = liftSum2 (+)
  (-) = liftSum2 (-)
  (*) = liftSum2 (*)
  abs = liftSum abs
  negate = liftSum negate
  signum = liftSum signum
  fromInteger = Sum . fromInteger
liftProd = liftTy Product getProductliftProd2 = liftTy2 Product getProduct
instance (Num a) => Num (Product a) where
  (+) = liftProd2 (+)
  (-) = liftProd2 (-)
  (*) = liftProd2 (*)
  abs = liftProd abs
  negate = liftProd negate
  signum = liftProd signum
  fromInteger = Product . fromInteger


Or with a few extensions (as noted by Daniel Wagner):

{-# LANGUAGE StandaloneDeriving, GeneralizedNewtypeDeriving #-}
import Data.Monoid
deriving instance Num a => Num (Sum a)deriving instance Num a => Num (Product a)


--
Dan Burton
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20120222/54e2db67/attachment.htm>


More information about the Libraries mailing list