control-dotdotdot-0.1.0.0: Haskell operator `g ... f = \x1 .. xn -> g (f x1 .. xn)`.

Safe HaskellSafe
LanguageHaskell2010

Control.DotDotDot

Description

Haskell operator g ... f = x1 .. xn -> g (f x1 .. xn). Compose functions such that all arguments are applied. Obviates (.).(.) and similar patterns in some cases.

Examples:

> ((+) ... (+) ... (+)) (1 :: Int) 2 3 4
10

Synopsis

Documentation

class b ~ IsFun f => DotDotDot f b where Source #

Class for defining ... recursively on function types.

Minimal complete definition

(...)

Associated Types

type Return (f :: *) (b :: Bool) :: * Source #

type Replace (f :: *) (r :: *) (b :: Bool) :: * Source #

Methods

(...) :: (Return f b -> r) -> f -> Replace f r b infixr 9 Source #

Instances

(~) Bool False (IsFun a) => DotDotDot a False Source # 

Associated Types

type Return a (False :: Bool) :: * Source #

type Replace a r (False :: Bool) :: * Source #

Methods

(...) :: (Return a False -> r) -> a -> Replace a r False Source #

DotDotDot b (IsFun b) => DotDotDot (a -> b) True Source # 

Associated Types

type Return (a -> b) (True :: Bool) :: * Source #

type Replace (a -> b) r (True :: Bool) :: * Source #

Methods

(...) :: (Return (a -> b) True -> r) -> (a -> b) -> Replace (a -> b) r True Source #

:: (b ~ IsFun f, DotDotDot f b) => (Return f b -> r) -> f -> Replace f r b infixr 9 Source #

Alias for ....

type family IsFun (a :: *) :: Bool where ... Source #

IsFun f is 'True if f has form _ -> _ and 'False otherwise.

Equations

IsFun (_ -> _) = True 
IsFun _ = False