{-# LANGUAGE ViewPatterns #-} -- | This module includes several minor combinators and some rewrite rules for their efficient application. module Data.RangeMin.Internal.Combinators where import Control.Monad(join, liftM2) {-# RULES "on/id" forall f . f `on` id = f; "liftM2/app" forall f g h x . liftM2 f g h x = f (g x) (h x); "on/on" forall f g h . (f `on` g) `on` h = f `on` (g . h); "onPair/onPair" forall f g x . onPair f (onPair g x) = onPair (f . g) x; ".:/on" forall f g h . (f .: g) `on` h = f .: (g `on` h) #-} infixr 9 .: infixl 8 `on` {-# INLINE [1] on #-} -- | @(f `on` g) x y@ is equivalent to @f (g x) (g y)@. on :: (a -> a -> b) -> (c -> a) -> c -> c -> b f `on` g = \ (g -> x) (g -> y) -> f x y {-# INLINE [1] onPair #-} -- | @onPair f (x, y)@ is equivalent to @(f x, f y)@. onPair :: (a -> b) -> (a, a) -> (b, b) onPair f (f -> x', f -> y') = (x', y') {-# INLINE (.:) #-} -- | @(f .: g) x y@ is equivalent to @f (g x y)@. (.:) :: (a -> b) -> (c -> d -> a) -> c -> d -> b f .: g = \x y -> f (g x y) {-# INLINE switch #-} -- | @switch x y p@ is equivalent to @if p then x else y@. switch :: a -> a -> Bool -> a switch x y p = if p then x else y {-# INLINE both #-} both :: (a -> b) -> (a -> c) -> a -> (b, c) both f g = \ x -> (f x, g x)