{-# LANGUAGE ScopedTypeVariables, Rank2Types #-} -- .$Header: c:/Source/Haskell/Wrapper/Data/Flex/RCS/Utils.hs,v 1.5 2011/09/20 23:38:55 dosuser Exp dosuser $ module Data.Flex.Utils ( -- * Various utility functions for handling wrappers -- ** Wrapper/unwrapper composition inCompose, inCompose2, -- ** Constructing @'Monad'@ bind (@'>>='@) for wrapped values bindWrapper, -- ** Another popular composition combinator on -- ** Semantic editor combinators -- () , result, argument ) where -- | Place (by composition) two functions round another function circumpose :: (c -> d) -> (a -> b) -> (b -> c) -> (a -> d) circumpose left right = (left .) . (. right) -- | Bracket (by composition) a function by two other functions. -- (\'In' as in infix.) -- Sometimes more convenient than @'circumpose'@ inCompose :: (a -> b) -> (c -> d) -> (b -> c) -> (a -> d) inCompose = flip circumpose -- | A generalisation of @'inCompose'@ to two-argument functions inCompose2 :: (forall a. f a -> a) -> (d -> e) -> (b -> c -> d) -> (f b -> f c -> e) inCompose2 unwrap wrap = inCompose unwrap $ inCompose unwrap wrap -- | Change the result of a function result :: (b -> c) -> (a -> b) -> (a -> c) result = (.) -- | Change the argument of a function argument :: (a -> b) -> (b -> c) -> (a -> c) argument = flip (.) -- | Handy utility function infixl 8 `on` on :: (b -> b -> c) -> (a -> b) -> (a -> a -> c) (op `on` f) x y = f x `op` f y -- | Utility function to construct @'>>='@ for a target monad @t@ from -- the @'>>='@ from an implementation monad @i@ bindWrapper :: (forall q. t q -> i q) -- ^ wrap: function from target monad to implementation monad -> (d -> e) -- ^ unwrap: vice versa (@i q -> t q@) -> (i a -> (c -> i b) -> d) -- ^ @'>>='@ in the implementation monad -> t a -> (c -> t b) -> e bindWrapper wrap unwrap = inCompose wrap $ inCompose (result wrap) unwrap -- vim: expandtab:tabstop=4:shiftwidth=4