module Data.PopCulture.Emoticons where import Data.Function (・-・) :: a -> a (・-・) = id (・∀・) :: a -> b -> a (・∀・) = const (^◇^) :: (b -> c) -> (a -> b) -> a -> c (^◇^) = (.) -- | C combinator - cardinal - Haskell 'flip'. (★ ̄∀ ̄★) :: (a -> b -> c) -> b -> a -> c (★ ̄∀ ̄★) = flip -- | A combinator - apply / applicator - Haskell ('$'). -- -- This is also called @i-star@. (≧∀≦) :: (a -> b) -> a -> b (≧∀≦) = ($) -- 'fix' - which Y is Haskell\'s fix? (certainly it\'s the least -- fixed point) -- | Psi combinator - psi bird (?) - Haskell 'on'. (°∇°) :: (b -> b -> c) -> (a -> b) -> a -> a -> c (°∇°) = on -------------------------------------------------------------------------------- -- Other birds -- | B3 combinator - becard. (´∀`) :: (c -> d) -> (b -> c) -> (a -> b) -> a -> d (´∀`) f g h x = f (g (h x)) -- | B1 combinator - blackbird - specs 'oo'. (^∇^) :: (c -> d) -> (a -> b -> c) -> a -> b -> d (^∇^) f g x y = f (g x y) -- | B' combinator - bluebird prime. (^∀^) :: (a -> c -> d) -> a -> (b -> c) -> b -> d (^∀^) f x g y = f x (g y) -- | B2 combinator - bunting - specs 'ooo'. (・・) :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e (・・) f g x y z = f (g x y z) -- | C' combinator - no name. (^-^*) :: (c -> a -> d) -> (b -> c) -> a -> b -> d (^-^*) f g x y = f (g y) x -- | C* combinator - cardinal once removed. (^∇^**) :: (a -> c -> b -> d) -> a -> b -> c -> d (^∇^**) f x y z = f x z y -- | C** combinator - cardinal twice removed. (^∀^**) :: (a -> b -> d -> c -> e) -> a -> b -> c -> d -> e (^∀^**) f s t u v = f s t v u -- | D1 combinator - dickcissel. (・∇´) :: (a -> b -> d -> e) -> a -> b -> (c -> d) -> c -> e (・∇´) f x y g z = f x y (g z) -- | D combinator - dove. (・∀´) :: (a -> c -> d) -> a -> (b -> c) -> b -> d (・∀´) f x g y = f x (g y) -- | D2 combinator - dovekie. (^~^) :: (c -> d -> e) -> (a -> c) -> a -> (b -> d) -> b -> e (^~^) f g x h z = f (g x) (h z) -- | E combinator - eagle. (//∇//) :: (a -> d -> e) -> a -> (b -> c -> d) -> b -> c -> e (//∇//) f x g y z = f x (g y z) -- | E \^ - bald eagle. -- For alphabetical regularity it is somewhat misnamed here as -- eaglebald. (//・//) :: (e -> f -> g) -> (a -> b -> e) -> a -> b -> (c -> d -> f) -> c -> d -> g (//・//) f g s t h u v = f (g s t) (h u v) -- | F combinator - finch. (〃∇〃) :: a -> b -> (b -> a -> c) -> c (〃∇〃) x y f = f y x -- | F* combinator - finch once removed. (〃▽〃) :: (c -> b -> a -> d) -> a -> b -> c -> d (〃▽〃) f x y z = f z y x -- | F** combinator - finch twice removed. (〃・〃) :: (a -> d -> c -> b -> e) -> a -> b -> c -> d -> e (〃・〃) f s t u v = f s v u t -- | G combinator - goldfinch. (‐°‐) :: (b -> c -> d) -> (a -> c) -> a -> b -> d (‐°‐) f g x y = f y (g x) -- | H combinator - hummingbird. (°□°) :: (a -> b -> a -> c) -> a -> b -> c (°□°) f x y = f x y x -- | I* combinator - identity bird once removed -- Alias of 'applicator', Haskell\'s ('$'). (┬──┬) :: (a -> b) -> a -> b (┬──┬) f x = f x -- | I** combinator - identity bird twice removed (・.・) :: (a -> b -> c) -> a -> b -> c (・.・) f x y = f x y -- | Alternative J combinator - this is the J combintor of Joy, -- Rayward-Smith and Burton (see. Antoni Diller \'Compiling -- Functional Languages\' page 104). It is not the J - jay -- combinator of the literature. (・・?) :: (a -> c) -> a -> b -> c (・・?) f x _y = f x -- | J' combinator - from Joy, Rayward-Smith and Burton. -- See the comment to 'jalt'. (・・??) :: (a -> b -> d) -> a -> b -> c -> d (・・??) f x y _z = f x y -- | J combinator - jay. -- -- This is the usual J combinator. (・・???) :: (a -> b -> b) -> a -> b -> a -> b (・・???) f x y z = f x (f z y) -- | Ki - kite. -- Corresponds to the encoding of @false@ in the lambda calculus. (・~・) :: a -> b -> b (・~・) _x y = y -- | O combinator - owl. (--~) :: ((a -> b) -> a) -> (a -> b) -> b (--~) x y = y (x y) -- | (Big) Phi combinator - phoenix - Haskell 'liftM2'. -- -- This is the same function as 'Data.Aviary.Birds.starling''. -- (╯°□°) :: (b -> c -> d) -> (a -> b) -> (a -> c) -> a -> d (╯°□°) f g h x = f (g x) (h x) -- | Q4 combinator - quacky bird. ( ̄^ ̄) :: a -> (a -> b) -> (b -> c) -> c ( ̄^ ̄) x f g = g (f x) -- | Q combinator - queer bird. -- -- Haskell @(\#\#)@ in Peter Thiemann\'s Wash, reverse composition. (・﹏・) :: (a -> b) -> (b -> c) -> a -> c (・﹏・) f g x = g (f x) -- | Q3 combinator - quirky bird. (〃´∀`) :: (a -> b) -> a -> (b -> c) -> c (〃´∀`) f x g = g (f x) -- | Q1 combinator - quixotic bird. (〃..) :: (b -> c) -> a -> (a -> b) -> c (〃..) f x g = f (g x) -- | Q2 combinator - quizzical bird. (..) :: a -> (b -> c) -> (a -> b) -> c (..) x f g = f (g x) -- | R combinator - robin. (。・・。) :: a -> (b -> a -> c) -> b -> c (。・・。) x f y = f y x -- | R* combinator - robin once removed. (〃。・・。) :: (b -> c -> a -> d) -> a -> b -> c -> d (〃。・・。) f x y z = f y z x -- | R** combinator - robin twice removed. (*〃。・・。) :: (a -> c -> d -> b -> e) -> a -> b -> c -> d -> e (*〃。・・。) f s t u v = f s u v t -- | S combinator - starling. -- -- Haskell: Applicative\'s @(\<*\>)@ on functions. -- -- Substitution. (°-°*) :: (a -> b -> c) -> (a -> b) -> a -> c (°-°*) f g x = f x (g x) -- | S' combinator - starling prime - Turner\'s big phi. -- Haskell: Applicative\'s 'liftA2' on functions (and similarly -- Monad\'s 'liftM2'). -- -- This is the same function as 'Data.Aviary.Birds.phoenix'. -- (°-°〃) :: (b -> c -> d) -> (a -> b) -> (a -> c) -> a -> d (°-°〃) f g h x = f (g x) (h x) -- | T combinator - thrush. -- Haskell @(\#)@ in Peter Thiemann\'s Wash, reverse application. (╥﹏╥) :: a -> (a -> b) -> b (╥﹏╥) x f = f x -- | V combinator - vireo (pairing). (⋟﹏⋞) :: a -> b -> (a -> b -> c) -> c (⋟﹏⋞) x y f = f x y -- | V* combinator - vireo once removed. (⋟~⋞) :: (b -> a -> b -> d) -> a -> b -> b -> d (⋟~⋞) f x y z = f y x z -- | V** combinator - vireo twice removed. (╥~╥) :: (a -> c -> b -> c -> e) -> a -> b -> c -> c -> e (╥~╥) f s t u v = f s v t u -- | W combinator - warbler - elementary duplicator. (´・~・) :: (a -> a -> b) -> a -> b (´・~・) f x = f x x -- | W1 combinator - converse warbler. -- 'warbler' with the arguments reversed. (・・;) :: a -> (a -> a -> b) -> b (・・;) x f = f x x -- | W* combinator - warbler once removed. (●・・) :: (a -> b -> b -> c) -> a -> b -> c (●・・) f x y = f x y y -- | W** combinator - warbler twice removed. (◉・・) :: (a -> b -> c -> c -> d) -> a -> b -> c -> d (◉・・) f x y z = f x y z z