lambda-placeholders-0.0.0.0: A library to emulate laceholders similar to Scala.

Safe HaskellSafe-Inferred

Language.LambdaPlaceholders

Contents

Synopsis

Documentation

class CurryingApp a b e | b a -> e, e b -> a whereSource

Methods

(.$.) :: a -> b -> eSource

foo.$.arg curries foo the correct amount and composes it with arg. arg must be of the form a0 -> ... -> aN -> (z0,...,zN1, a0,z0,...zN1,a1,..., aN,z0,...,zNk) foo must be of the form (z0,...,zN1, a0,z0,...zN1,a1,..., aN,z0,...,zNk) -> r .$. has the same fixity as $.

Instances

CurryingApp a d e => CurryingApp a (b -> d) (b -> e) 
CurryingApp ((a, b) -> a0) (a, b) a0 
CurryingApp ((a, b, c) -> a0) (a, b, c) a0 
CurryingApp ((a, b, c, d) -> a0) (a, b, c, d) a0 
CurryingApp ((a, b, c, d, e) -> a0) (a, b, c, d, e) a0 
CurryingApp ((a, b, c, d, e, f) -> a0) (a, b, c, d, e, f) a0 
CurryingApp ((a, b, c, d, e, f, g) -> a0) (a, b, c, d, e, f, g) a0 
CurryingApp ((a, b, c, d, e, f, g, h) -> a0) (a, b, c, d, e, f, g, h) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i) -> a0) (a, b, c, d, e, f, g, h, i) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j) -> a0) (a, b, c, d, e, f, g, h, i, j) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k) -> a0) (a, b, c, d, e, f, g, h, i, j, k) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, n) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) a0 
CurryingApp ((a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) a0 

class UncurryingApp a b e | b a -> e, e b -> a whereSource

Methods

(.@.) :: a -> b -> eSource

foo.@.arg composes foo with arg. arg must be of the form a0 -> ... -> aN -> (z0,...,zN1, a0,z0,...zN1,a1,..., aN,z0,...,zNk) and foo must be of the form z0-> ...-> zN1 -> a0 -> ... -> aN -> z0 -> ... -> zNk -> r

Instances

UncurryingApp a d e => UncurryingApp a (b -> d) (b -> e) 
UncurryingApp (a -> b -> a0) (a, b) a0 
UncurryingApp (a -> b -> c -> a0) (a, b, c) a0 
UncurryingApp (a -> b -> c -> d -> a0) (a, b, c, d) a0 
UncurryingApp (a -> b -> c -> d -> e -> a0) (a, b, c, d, e) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> a0) (a, b, c, d, e, f) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> a0) (a, b, c, d, e, f, g) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> a0) (a, b, c, d, e, f, g, h) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> a0) (a, b, c, d, e, f, g, h, i) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> a0) (a, b, c, d, e, f, g, h, i, j) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> a0) (a, b, c, d, e, f, g, h, i, j, k) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> a0) (a, b, c, d, e, f, g, h, i, j, k, l) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> o -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, o) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> o -> p -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, o, p) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> o -> p -> q -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, o, p, q) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> o -> p -> q -> r -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, o, p, q, r) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> o -> p -> q -> r -> s -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, o, p, q, r, s) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> o -> p -> q -> r -> s -> t -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, o, p, q, r, s, t) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> o -> p -> q -> r -> s -> t -> u -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, o, p, q, r, s, t, u) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> o -> p -> q -> r -> s -> t -> u -> v -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, o, p, q, r, s, t, u, v) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> o -> p -> q -> r -> s -> t -> u -> v -> w -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, o, p, q, r, s, t, u, v, w) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> o -> p -> q -> r -> s -> t -> u -> v -> w -> x -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, o, p, q, r, s, t, u, v, w, x) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> o -> p -> q -> r -> s -> t -> u -> v -> w -> x -> y -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, o, p, q, r, s, t, u, v, w, x, y) a0 
UncurryingApp (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m -> o -> p -> q -> r -> s -> t -> u -> v -> w -> x -> y -> z -> a0) (a, b, c, d, e, f, g, h, i, j, k, l, m, o, p, q, r, s, t, u, v, w, x, y, z) a0 

Example Usage

-- LANGUAGE TupleSections
module Main where
import Language.LambdaPlaceholders

foo (a,b,c,d,e) = a + b + c + d * c + e

curried_foo = foo.$.(2, , 3 , , )

uncurried_foo = curried_foo.@.( , 3 , )

main = do
    putStrLn $ show $ curried_foo 4 5