module Data.Composition (
  (.:),
  (.*),
  (.**),
  (.***),
  (.****),
  (.*****),
  (.******),
  (.*******),
  (.********),
  compose2,
  compose3,
  compose4,
  compose5,
  compose6,
  compose7,
  compose8,
  compose9
) where

-- Not exported. This is defined here to remove the dependency on base
(.) :: (b -> c) -> (a -> b) -> a -> c
(f . g) x = f (g x)

-- | Compose two functions. @f .: g@ is similar to @f . g@
-- except that @g@ will be fed /two/ arguments instead of one
-- before handing its result to @f@.
-- 
-- This function is defined as
-- 
-- > (f .: g) x y = f (g x y)
-- 
-- Example usage:
-- 
-- > concatMap :: (a -> b) -> [a] -> [b]
-- > concatMap = concat .: map
-- 
-- Notice how /two/ arguments
-- (the function /and/ the list)
-- will be given to @map@ before the result
-- is passed to @concat@. This is equivalent to:
-- 
-- > concatMap f xs = concat (map f xs)
(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(f .: g) x y = f (g x y)

-- | Equivalent to '.:'
-- 
-- The pattern of appending asterisks is
-- more straightforward to extend to similar functions:
-- (compose2 = .*, compose3 = .**, etc).
-- However, @.:@ has been commonly adopted amongst Haskellers,
-- and the need for compose3 and beyond is rare in practice.
(.*) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(.*) = (.) . (.)

(.**) :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e
(.**) = (.) . (.*)

(.***) = (.) . (.**)
(.****) = (.) . (.***)
(.*****) = (.) . (.****)
(.******) = (.) . (.*****)
(.*******) = (.) . (.******)
(.********) = (.) . (.*******)


compose2 :: (c -> d) -> (a -> b -> c) -> a -> b -> d
compose2 = (.*)

compose3 :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e
compose3 = (.**)

compose4 = (.***)
compose5 = (.****)
compose6 = (.*****)
compose7 = (.******)
compose8 = (.*******)
compose9 = (.********)