On this page:
5.1 Syntax
lambda/  function
lambda/  f
λ/  f
define/  function
define/  f
lambda.
λ.
app
5.2 Representation
5.3 Utilities
apply/  steps
compose
conjoin
&&
disjoin
||
negate
!!
curry
curryr
uncurry
partial
partialr
partial/  template
unthunk
if-f
true.
false.
arg
flip
flip$
flip*
lift
call
pack
pack-map
map-values
filter-values
unwrap
5.4 Types
5.4.1 Interface
gen:  procedure
procedure?
keywords
arity
procedure-apply
5.4.2 Functions and Composition
function
base-composed-function
composed-function
power-function
monoid
function-cons
function-null
make-function
f
5.4.3 Function Application
gen:  application-scheme
application-scheme?
pass
flat-arguments
unwrap-application
curried-function
partial-function
template-function

5 Functional Primitives🔗

 (require relation/function) package: relation-lib

Elementary types and utilities to simplify the use and manipulation of functions.

This module provides general-purpose utilities to support programming in the functional style. As part of its operation, this module defines and provides a suite of "rich" function types that interoperate seamlessly with, and may be used as an alternative to, Racket’s built-in procedure type. These function types are usually no different from normal functions, but as higher-level entities, they provide greater visibility of the make-up of the function, allowing more flexibility in customizing the nature of composition, supporting natural semantics when used with standard sequence utilities, and more seamless use of currying and partial application.

    5.1 Syntax

    5.2 Representation

    5.3 Utilities

    5.4 Types

      5.4.1 Interface

      5.4.2 Functions and Composition

      5.4.3 Function Application

5.1 Syntax🔗

syntax

(lambda/function kw-formals body ...)

syntax

(lambda/f kw-formals body ...)

syntax

(λ/f kw-formals body ...)

Identical to lambda except that it produces a function rather than a primitive Racket function. lambda/f and λ/f are aliases for lambda/function.

syntax

(define/function (id kw-formals) body ...)

syntax

(define/f kw-formals body ...)

Identical to the function form of define except that it produces a function rather than a primitive Racket function. define/f is an alias for define/function.

syntax

(lambda. kw-formals ... -> body ...)

syntax

(λ. kw-formals ... -> body ...)

A lightweight way to define anonymous functions (lambdas) inspired by Haskell’s syntax for lambdas. Equivalent to lambda/f except that it does not support a rest argument, so it is best suited for simple cases like inline lambdas, rather than more complex cases such as a prop:procedure specification. In any case, if a rest argument is needed, use lambda/f directly.

Either -> or may be used as the syntactic separator between the arguments and the body of the function.

Examples:
> ((λ. x -> (sqr x)) 5)

25

> (map ((λ. x y -> (expt x y)) 2) (range 10))

'(1 2 4 8 16 32 64 128 256 512)

> ((λ. -> 10))

10

> ((λ. x y -> (+ x y)) 5 10)

15

> ((λ. x y #:key [key #f] -> (= #:key key x y)) 5 "5")

#f

> ((λ. x y #:key [key #f] -> (= #:key key x y)) #:key ->string 5 "5")

#t

syntax

(app fn template-args ...)

Syntactic sugar on the partial/template interface, inspired by and greatly resembling Fancy App: Scala-Style Magic Lambdas, this enables applying a function to arguments with reference to a template specified in advance. The template indicates the expected arguments and their positions or keywords.

Examples:
> (app + 2 _)

'(λ (2 _) #<procedure:+>)

> ((app + 2 _) 3)

5

> (map (app * 2 _) (list 1 2 3))

'(2 4 6)

> ((app string-append _ "-" _) "seam" "less")

"seam-less"

> (app = #:key string-upcase "apple" _)

'(λ ("apple" _ #:key #<procedure:string-upcase>) #<procedure:=>)

> ((app = #:key string-upcase _ "apple") "APPLE")

#t

> ((app = #:key _ "apple" _) "APPLE")

Missing keyword argument in template!

keyword: #:key

> ((app = #:key _ "apple" _) #:key string-upcase "APPLE")

#t

5.2 Representation🔗

The printed representation of a function has some features worthy of note. Let’s look at an example.

> (f add1 sqr)

'(λ (···) (.. #<procedure:sqr> #<procedure:add1>))

The first thing to note is that the printed representation is almost itself valid code to reproduce the function it represents. A prominent maxim of programming in the functional style is to write complex functions in terms of small, simple functions that can be composed together. The transparency of this representation is intended to support this habit, by enabling the makeup of such functions, whether simple or complex, to be easily scrutinized and manipulated. Specific clues encoded in the representation are as follows:
(λ (args ···) ...)
In general, the arguments portion of the representation indicates the application scheme. Here, it indicates that the function is left-curried (the default), while
(λ (··· args) ...)
indicates that it is right-curried (the ··· indicates where fresh arguments will be placed in relation to the existing arguments). If arguments have been supplied on both sides, either via currying or a template, the argument position(s) between the already-supplied arguments will be indicated by ··· (for curried functions), or _ (for templates), or _ (for partially applied, uncurried, functions).
(.. fn ...)
indicates that the method of composition is the usual one, i.e. compose,
(&& fn ...)
means the method of composition is conjoin,
(|| fn ...)
means disjoin, and
(?? fn ...)
indicates that the method of composition is not a standard one but a custom monoid. Note that in the case of composed functions, the order of composition is depicted left-to-right, i.e. the leftmost function is the leading one in the composition and is applied first, and the rightmost one is applied last.

More examples:
> (f add1 sqr)

'(λ (···) (.. #<procedure:sqr> #<procedure:add1>))

> ((f expt) 2)

'(λ (2 ···) #<procedure:expt>)

> (partial expt 2)

'(λ (2 __) #<procedure:expt>)

> (curry = #:key string-upcase "apple")

'(λ ("apple" ··· #:key #<procedure:string-upcase>) #<procedure:=>)

> (curryr member? (list 1 2 3))

'(λ (··· (1 2 3)) #<procedure:member?>)

> (curryr (curry string-append "ichi") "san")

'(λ ("ichi" ··· "san") #<procedure:string-append>)

> (app string-append "ichi" _ "san" _ "go")

'(λ ("ichi" _ "san" _ "go") #<procedure:string-append>)

> (&& positive? odd?)

'(λ (&& #<procedure:odd?> #<procedure:positive?>))

> (|| positive? odd?)

'(λ (|| #<procedure:odd?> #<procedure:positive?>))

> (f #:compose-with (monoid (λ (f g) g) values) add1 sub1)

'(λ (···) (?? #<procedure:sub1> #<procedure:add1>))

5.3 Utilities🔗

procedure

(apply/steps g v ... lst #:<kw> kw-arg ...)  sequence?

  g : function?
  v : any/c
  lst : list?
  kw-arg : any/c
Similar to apply, but yields a sequence corresponding to the values at each stage of application of the function g.

Examples:
> (->list (apply/steps (f add1 sub1 sqr) (list 3)))

'(9 8 9)

> (->list (apply/steps (f #:thread? #t ->number add1 ->string) (list "1")))

'(1 2 "2")

procedure

(compose g ...)  function?

  g : procedure?
Analogous to compose, but yields a function rather than a primitive Racket procedure.

In general, the composition is performed "naively" by simply wrapping the component functions with a new function. In the case where none of the component functions are wrapped with an application scheme, however, and where their composition methods are the same, the functions are composed "at the same level." Further study of the interaction between application schemes and composition may suggest some simplification rules here, but that is left for future consideration.

Examples:
> (compose ->string +)

'(λ (.. #<procedure:+> #<procedure:->string>))

> (compose ->string (f +))

'(λ (.. (λ (···) #<procedure:+>) #<procedure:->string>))

> (compose ->string (curry + 2))

'(λ (.. (λ (2 ···) #<procedure:+>) #<procedure:->string>))

procedure

(conjoin g ...)  function?

  g : procedure?

procedure

(&& g ...)  function?

  g : procedure?
Similar to compose and equivalent to conjoin, this yields a function whose composition method is conjoin rather than compose, that is, it composes predicates such that it evaluates to true when all components evaluate to true and not otherwise. && is provided as a convenient alias, following the convention in The Algebraic Racket Collection.

Examples:
> (&& positive? integer?)

'(λ (&& #<procedure:integer?> #<procedure:positive?>))

> ((&& positive? integer?) -5)

#f

> ((&& positive? integer?) 5.3)

#f

> ((&& positive? integer?) 5)

#t

procedure

(disjoin g ...)  function?

  g : procedure?

procedure

(|| g ...)  function?

  g : procedure?
Similar to compose and equivalent to disjoin, this yields a function whose composition method is disjoin rather than compose, that is, it composes predicates such that it evaluates to true when any component evaluates to true. || is provided as a convenient alias, following the convention in The Algebraic Racket Collection.

N.B.: It turns out that Racket considers the symbol || to be the empty symbol, because of the special handling of \| by the reader. This may cause problems in certain (perhaps rare) cases – for instance, if you do a symbol->string conversion, you may expect to find "||" but you would find "" instead. In cases where you are doing any kind of parsing or serialization of your code, or if you are using these in macros, it would be advisable to just use the written form of the function instead, i.e. disjoin rather than ||, to steer clear of possible issues here.

Examples:
> (|| positive? integer?)

'(λ (|| #<procedure:integer?> #<procedure:positive?>))

> ((|| positive? integer?) -5)

#t

> ((|| positive? integer?) 5.3)

#t

> ((|| positive? integer?) 5)

#t

> ((|| positive? integer?) -5.3)

#f

procedure

(negate g)  function?

  g : procedure?

procedure

(!! g)  function?

  g : procedure?
Analogous to negate, this yields a function whose result is the boolean negation of the result of applying g.

Examples:
> (!! positive?)

'(λ (.. #<procedure:positive?> #<procedure:not>))

> ((!! positive?) -5)

#t

> ((!! positive?) 5)

#f

procedure

(curry g v ...)  function?

  g : procedure?
  v : any/c

procedure

(curryr g v ...)  function?

  g : procedure?
  v : any/c
Analogous to curry and curryr, but these yield a function rather than a primitive Racket procedure. Since functions are curried by default, explicitly invoking curry is usually not necessary, but can be useful in cases where evaluation needs to be delayed until additional arguments are received. An explicit call to curry will not immediately evaluate to a result even if sufficient arguments have been provided for the invocation to produce a result.

Examples:
> (curry + 2)

'(λ (2 ···) #<procedure:+>)

> (curry + 2 3)

'(λ (2 3 ···) #<procedure:+>)

> ((curryr < 5) 3)

#t

> (curry (curryr (curry string-append "ichi") "san") "ni")

'(λ ("ichi" "ni" ··· "san") #<procedure:string-append>)

> ((curryr (curry string-append "ichi" "-") "-" "san") "ni")

"ichi-ni-san"

procedure

(uncurry g)  function?

  g : procedure?
Convert a curried function g accepting single arguments in succession to an equivalent one accepting an arbitrary number of arguments at once. This is typically not needed since both curry as well as Racket’s built-in currying interfaces support partial application with an arbitrary number of arguments, but it can be useful with naively curried functions not created using one of these interfaces.

Examples:
> (define (curried-add-3 x)
    (λ (y)
      (λ (z)
        (+ x y z))))
> (curried-add-3 1 4 7)

curried-add-3: arity mismatch;

 the expected number of arguments does not match the given

number

  expected: 1

  given: 3

> ((uncurry curried-add-3) 1 4 7)

12

procedure

(partial g v ...)  function?

  g : procedure?
  v : any/c

procedure

(partialr g v ...)  function?

  g : procedure?
  v : any/c
Partially apply the function g using the provided arguments. The result is a function with a flat set of these pre-supplied arguments which must be invoked with all of the remaining expected arguments when the time comes, i.e. it is not curried. partial supplies the arguments on the left, while partialr supplies them on the right.

Examples:
> (partial + 2)

'(λ (2 __) #<procedure:+>)

> ((partial + 2) 3 4)

9

> (partialr string-append "c")

'(λ (__ "c") #<procedure:string-append>)

> ((partialr string-append "c") "a" "b")

"abc"

procedure

(partial/template g v ...)  function?

  g : procedure?
  v : maybe/c
Partially apply the function g using the specified argument template. This template takes the form of a series of optional values, provided directly, either as positional or keyword arguments. The result is a function that expects precisely those arguments that are indicated as "missing" in the template. Note that this function is not curried. Typically this would be used via the convenient app syntax, rather than directly.

Examples:
> (partial/template = #:key (just string-upcase) (just "apple") nothing)

'(λ ("apple" _ #:key #<procedure:string-upcase>) #<procedure:=>)

> ((partial/template = #:key (just string-upcase) nothing (just "apple")) "APPLE")

#t

> ((partial/template = #:key nothing (just "apple") nothing) #:key string-upcase "APPLE")

#t

procedure

(unthunk g v ...)  procedure?

  g : procedure?
  v : any/c
Converts a procedure accepting no arguments to one accepting an arbitrary number of arguments (which are all ignored upon invocation). In other words, this converts a thunk into a thunk*.

Examples:
> (define gen (unthunk (sequence->generator '(1 2 3))))
> (gen "some")

1

> (gen 'ignored)

2

> (gen "arguments" 'a 'b 42)

3

procedure

(if-f pred f g)  procedure?

  pred : (-> any/c boolean?)
  f : procedure?
  g : procedure?
Analogous to if, checks the predicate pred against an input value and applies either f or g to it depending on the result.

Examples:
> ((if-f positive? add1 sub1) 3)

4

> (map (if-f positive? add1 sub1) (list 3 -3))

'(4 -4)

procedure

(true. v)  boolean?

  v : any

procedure

(false. v)  boolean?

  v : any
true. is an agreeable function that always returns #t, while false. is a contrarian that always returns #f. Both accept an arbitrary number of arguments (disregarding all of them).

Examples:
> (true.)

#t

> (true. 3 1 #:key 'hi)

#t

> (false.)

#f

> (false. 3 1 #:key 'hi)

#f

procedure

(arg n)  procedure?

  n : exact-nonnegative-integer?
Produces a function whose value is simply its nth argument.

Examples:
> ((arg 0) "hi" "there")

"hi"

> ((arg 2) "hi" "there" 'abc 'pqr)

'abc

> ((arg 3) -2 -1 0 1 2 3)

1

> (apply (arg 3) (range 10))

3

> (regexp-replace* #rx"\\[\\[(cat|dog)\\]\\]"
                   "The [[cat]] and the [[dog]] in the hat."
                   (arg 1))

"The cat and the dog in the hat."

procedure

(flip g)  procedure?

  g : procedure?

procedure

(flip$ g)  procedure?

  g : procedure?

procedure

(flip* g)  procedure?

  g : procedure?
flip yields a function identical to the one passed in, but with the first two argument positions swapped, flip$ passes the first argument in the last argument position (leaving other arguments in the original relative positions), while flip* reverses the entire list of arguments.

Examples:
> ((flip string-append) "my" "hello" "friend")

"hellomyfriend"

> ((flip$ string-append) "friend" "hello" "my")

"hellomyfriend"

> ((flip* string-append) "friend" "my" "hello")

"hellomyfriend"

procedure

(lift g)  procedure?

  g : procedure?
"Lifts" a function operating on ordinary values to a function operating on a functor (for instance, a list of such values) in the natural way. This is a thin wrapper around map, and may lend clarity in cases where you want to derive such a function but not necessarily apply it immediately.

Examples:
> (define list-add1 (lift add1))
> (->list (list-add1 (list 1 2 3)))

'(2 3 4)

> (->list ((lift ->string) (list 1 2 3)))

'("1" "2" "3")

> ((lift add1) (just 3))

(just 4)

procedure

(call g v ...)  procedure?

  g : procedure?
  v : any/c
Reprovided from call. This simply makes standard function invocation available as a function, for use in cases where we cannot directly (i.e. syntactically) invoke the function. This function is in some respects similar to the $ operator in Haskell.

Examples:
> (call + 1 2 3 4)

10

> (call = #:key string-upcase "Apple" "APPLE")

#t

> (map call (list add1 sqr) (list 2 3))

'(3 9)

procedure

(pack g v ...)  any/c

  g : procedure?
  v : any/c

procedure

(pack-map g v ...)  list?

  g : procedure?
  v : any/c
pack packs the provided arguments into a list and gives that list to g as an argument. pack-map packs the provided arguments into a list and maps them individually under g.

While apply allows a function operating on provided arguments to operate on such arguments provided as a list, pack enables the opposite, allowing a function expecting a list to operate on multiple arguments instead. While map allows a function operating on individual arguments to operate on such arguments provided as a list, pack-map analogously allows the function to operate on such arguments provided directly as multiple arguments.

Examples:
> (pack (curry apply +) 1 2 3 4)

10

> (pack length "apple" 23 'banana)

3

> (pack-map sqr 1 2 3 4)

'(1 4 9 16)

> (pack-map ->string 1 2 3)

'("1" "2" "3")

procedure

(map-values g v ...)  any

  g : procedure?
  v : any/c

procedure

(filter-values g v ...)  any

  g : procedure?
  v : any/c
Similar to map and filter but these accept and return multiple values instead of lists.

Examples:
> (map-values add1 3 5)

4

6

> (filter-values positive? 1 -2 3)

1

3

procedure

(unwrap v)  any

  v : list?
Unwrap the contents of a list, returning them as values.

Examples:
> (unwrap (list 3))

3

> (unwrap (list 1 2 3))

1

2

3

5.4 Types🔗

This module defines an interface, gen:procedure, to encode the idea of a function. Racket’s built-in procedures answer to this interface, as do the "rich" function types provided by this module. This rich type is usable as a drop-in alternative to built-in Racket functions, but in addition, provides various high-level conveniences.

5.4.1 Interface🔗

A generic interface that represents any object which behaves like a function. The built-in procedure type has an implementation for gen:procedure.

procedure

(procedure? v)  boolean?

  v : any/c
Predicate to check if a value is a procedure. This is in practice identical to Racket’s built-in procedure?.

Examples:
> (procedure? 3)

#f

> (procedure? add1)

#t

> (procedure? (f add1))

#t

To implement this interface for custom types, the following methods need to be implemented, unless the type already contains a prop:procedure specification (meaning it counts as a built-in procedure), and more specific handling is not needed.

procedure

(keywords proc)  
(listof keyword?)
(or/c (listof keyword?) #f)
  proc : procedure?
A generic version of procedure-keywords. This function takes a single argument and returns information about the keyword arguments accepted by the procedure. The return values should take the same form as those of procedure-keywords. The argument is expected to be an instance of the structure type to which the generic interface is associated (or a subtype of the structure type).

procedure

(arity proc)  normalized-arity?

  proc : procedure?
A generic version of procedure-arity. This function takes a single argument and returns information about the arity of the arguments accepted by the procedure. The return value should take the same form as that of procedure-arity. The argument is expected to be an instance of the structure type to which the generic interface is associated (or a subtype of the structure type).

procedure

(procedure-apply proc args)  any

  proc : procedure?
  args : arguments?
This function specifies the rule for application of the function. It is expected to actually invoke the function on the provided arguments and return the result.

This function takes two arguments. The first is expected to be an instance of the structure type to which the generic interface is associated (or a subtype of the structure type). The second will be an arguments structure representing the arguments provided to the function.

5.4.2 Functions and Composition🔗

struct

(struct function ())

An "abstract" base type that represents any function, whether atomic or composed. All of the rich function types provided by this module are subtypes of this type. It is curried by default, meaning that partially supplying arguments results in a new function parametrized by these already-provided arguments.

If you’d like to define a custom rich function type, it must implement gen:procedure as well as use function as its base type.

struct

(struct base-composed-function (composer))

  composer : monoid?
An "abstract" base type that represents a composed function. This is a subtype of function.
  • composer - The definition of composition for this function. By default (when constructed using make-function), this is the usual function composition, i.e. compose together with values as the identity.

struct

(struct composed-function (composer components))

  composer : monoid?
  components : list?
A type that represents a composed function. This is a subtype of base-composed-function and therefore includes a composer.

struct

(struct power-function (composer f n))

  composer : monoid?
  f : procedure?
  n : number?
A type that represents a function composed with itself a certain number of times, i.e. a "power" of the function under the indicated composition method. This is a subtype of base-composed-function and therefore includes a composer.

struct

(struct monoid (f id))

  f : (-> procedure? procedure? procedure?)
  id : procedure?
A composer of functions, generalizing "normal" function composition to support any definition of composition. Any suitable notion of function composition (and hence instances of this monoid type) must include:

procedure

(function-cons v w)  base-composed-function?

  v : procedure?
  w : base-composed-function?

procedure

(function-null [#:compose-with composer])  composed-function?

  composer : monoid? = (monoid compose values)
Constructors for the base-composed-function type analogous to cons and null for lists. function-null also serves as the identity value for composition.

Examples:
> (function-cons add1 (f sqr ->number))

'(λ (···) (.. #<procedure:add1> #<procedure:->number> #<procedure:sqr>))

> ((function-cons add1 (function-null)) 3)

4

procedure

(make-function [#:compose-with composer    
  #:thread? thread?]    
  g ...)  function?
  composer : monoid? = (monoid compose values)
  thread? : boolean? = #f
  g : procedure?

procedure

(f [#:compose-with composer    
  #:thread? thread?]    
  g ...)  function?
  composer : monoid? = (monoid compose values)
  thread? : boolean? = #f
  g : procedure?
A variadic constructor for creating functions from other functions. The argument thread? configures whether the resulting function composes right-to-left (the default) or left-to-right (like Threading Macros). In either case, the print representation of the resulting function always denotes the order of composition from left to right (i.e. corresponding to the threading direction). f is an alias for the more verbose make-function.

Examples:
> (f add1)

'(λ (···) #<procedure:add1>)

> (f add1 ->number)

'(λ (···) (.. #<procedure:->number> #<procedure:add1>))

> (f add1 add1 add1)

'(λ (···) (.. ^ 3 #<procedure:add1>))

> ((f ->string add1 ->number) "12")

"13"

> ((f #:thread? #t ->number add1 ->string) "12")

"13"

> (define (str-append x y z) (string-append x y z))
> ((f str-append) "hello")

'(λ ("hello" ···) #<procedure:str-append>)

> ((((f str-append) "hello") "there") "friend")

"hellotherefriend"

5.4.3 Function Application🔗

An application scheme is in essence simply a function that calls another function. It represents a definition of function application, entailing how arguments are to be ordered and compiled, what arguments are expected and whether they may be passed in incrementally, and what happens when the underlying function is actually invoked.

The default application scheme is curried partial application, meaning the function takes an arbitrary number of positional and keyword arguments at a time and evaluates to a result when sufficient arguments have been provided, or to a new function accepting more arguments otherwise. Other schemes provided include partial application without currying, and template-based partial application (resembling the scheme in Fancy App: Scala-Style Magic Lambdas). As application schemes are themselves functions, they implement gen:procedure as well, in order to gracefully "pass through" the rich functionality provided by function types to those underlying functions, which would otherwise be rendered opaque by the wrapping functions.

Application schemes compose naturally, so that, for example, a function could expect arguments to match a template, and could receive those arguments incrementally via curried partial application. The examples below illustrate this.

A generic interface representing an application scheme. Any application scheme must also implement gen:procedure.

Examples:
> ((partial + 1) 2)

3

> ((curry expt 2) 5)

32

> ((curryr expt 2) 5)

25

> (app string-append _ ", " _ ", " _ " " "and " _ ".")

'(λ (_ ", " _ ", " _ " " "and " _ ".") #<procedure:string-append>)

> ((app string-append _ ", " _ ", " _ " " "and " _ ".") "parsley" "sage")

Not enough arguments, expected: 4

> (curryr (app string-append _ ", " _ ", " _ " " "and " _ ".") "thyme")

'(λ (··· "thyme")

   (λ (_ ", " _ ", " _ " " "and " _ ".") #<procedure:string-append>))

> (curry (curryr (app string-append _ ", " _ ", " _ " " "and " _ ".") "thyme") "parsley" "sage")

'(λ ("parsley" "sage" ··· "thyme")

   (λ (_ ", " _ ", " _ " " "and " _ ".") #<procedure:string-append>))

> ((curry (curryr (app string-append _ ", " _ ", " _ " " "and " _ ".") "thyme") "parsley" "sage") "rosemary")

"parsley, sage, rosemary and thyme."

procedure

(application-scheme? v)  boolean?

  v : any/c
Predicate to check if a value is an application scheme.

Examples:
> (application-scheme? (curry append 'left (list 1 2 3) (list 4 5) (hash '#:key number->string)))

#t

> (application-scheme? (app string-append _ "-" _))

#t

To define custom application schemes, the following methods need to be implemented.

procedure

(pass application-scheme args)  application-scheme?

  application-scheme : application-scheme?
  args : arguments?
Incorporate fresh args into the application-scheme. This defines what happens when a function with the given application scheme is applied to fresh arguments. The result of this function is expected to be an updated application scheme.

procedure

(flat-arguments application-scheme)  arguments?

  application-scheme : application-scheme?
Produce a flat arguments structure representing the arguments that will be passed in a single invocation of the underlying function. The application scheme may compile the arguments in whatever manner it sees fit; the produced arguments structure represents the result of its operation.

Examples:
> (flat-arguments (curry + 1 2 3))

(arguments 1 2 3)

> (flat-arguments (curry = #:key string-upcase "apple"))

(arguments "apple" #:key #<procedure:string-upcase>)

> (flat-arguments (curry (curryr (curry string-append "hello") "friend") "there"))

(arguments "hello" "there" "friend")

> (flat-arguments (app + 3 _))

(arguments 3)

procedure

(unwrap-application application-scheme)  procedure?

  application-scheme : application-scheme?
Return the underlying function that is to be applied by the scheme.

struct

(struct curried-function (f chirality left right kw))

  f : procedure?
  chirality : (one-of/c 'left 'right)
  left : list?
  right : list?
  kw : hash?
An application scheme representing a curried function, including the arguments that parametrize (i.e. have already been supplied to) the function. This includes all arguments that have been supplied by either left- or right-currying. The chirality indicates whether the function is left- or right-curried.

struct

(struct partial-function (f chirality left right kw))

  f : procedure?
  chirality : (one-of/c 'left 'right)
  left : list?
  right : list?
  kw : hash?
An application scheme representing a partially applied function (not to be confused with the mathematical notion of partial function, which is a function defined on a subset of its domain), including the arguments that parametrize (i.e. have already been supplied to) the function. This includes all arguments that have been supplied by either left- or right-partial application. The chirality indicates the side on which fresh arguments will be incorporated.

struct

(struct template-function (f pos kw))

  f : procedure?
  pos : list?
  kw : hash?
An application scheme encoding a template expressing the expected arguments – whether positional or keyword – to a function. The values of positional or keyword arguments are expected to be optional values. Typically, template-based partial application would be used via the app macro, so that there is no need to muck about with optional values in normal usage.