----------------------------------------------------------------------------- -- -- Module : Data.Function.Util -- Copyright : (c) 2014-16 Brian W Bush -- License : MIT -- -- Maintainer : Brian W Bush -- Stability : Stable -- Portability : Portable -- -- | Utilities related to "Data.Function". -- ----------------------------------------------------------------------------- {-# LANGUAGE Safe #-} module Data.Function.Util ( -- * Constant boolean functions always , never -- * Functions on second entries in pairs , sndNegater , sndCounter , sndSummer ) where import Control.Arrow (second) -- | Always true. always :: a -> Bool always = const True -- | Always false. never :: a -> Bool never = const False -- | Negate the second entry in a pair. sndNegater :: Num b => (a, b) -> (a, b) sndNegater = second negate -- | Measure the length of the second entry in a pair. sndCounter :: (a, [b]) -> (a, Int) sndCounter = second length -- | Sum the values of the second entry in a pair. sndSummer :: Num b => (a, [b]) -> (a, b) sndSummer = second sum