On this page:
make-contract
make-chaperone-contract
make-flat-contract
build-compound-type-name
coerce-contract
coerce-contracts
coerce-chaperone-contract
coerce-chaperone-contracts
coerce-flat-contract
coerce-flat-contracts
coerce-contract/  f
skip-projection-wrapper?
with-contract-continuation-mark
contract-pos/  neg-doubling
8.7.1 Blame Objects
blame?
raise-blame-error
blame-add-context
blame-context
blame-positive
blame-negative
blame-contract
blame-value
blame-source
blame-swap
blame-original?
blame-swapped?
blame-replace-negative
blame-replaced-negative?
blame-update
blame-missing-party?
blame-add-missing-party
exn:  fail:  contract:  blame
current-blame-format
8.7.2 Contracts as structs
prop:  contract
prop:  chaperone-contract
prop:  flat-contract
prop:  contracted
impersonator-prop:  contracted
prop:  blame
impersonator-prop:  blame
build-flat-contract-property
build-chaperone-contract-property
build-contract-property
contract-property?
chaperone-contract-property?
flat-contract-property?
8.7.3 Obligation Information in Check Syntax
define/  final-prop
define/  subexpression-pos-prop
8.7.4 Utilities for Building New Combinators
contract-stronger?
contract-equivalent?
contract-first-order-passes?
contract-first-order

8.7 Building New Contract Combinators🔗ℹ

 (require racket/contract/combinator) package: base

procedure

(make-contract 
  [#:name name 
  #:first-order first-order 
  #:late-neg-projection late-neg-proj 
  #:collapsible-late-neg-projection collapsible-late-neg-proj 
  #:val-first-projection val-first-proj 
  #:projection proj 
  #:stronger stronger 
  #:equivalent equivalent 
  #:list-contract? is-list-contract?]) 
  contract?
  name : any/c = 'anonymous-contract
  first-order : (-> any/c any/c) = (λ (x) #t)
  late-neg-proj : (or/c #f (-> blame? (-> any/c any/c any/c)))
   = #f
  collapsible-late-neg-proj : (or/c #f (-> blame? (values (-> any/c any/c any/c) collapsible-contract?)))
   = #f
  val-first-proj : (or/c #f (-> blame? (-> any/c (-> any/c any/c))))
   = #f
  proj : (-> blame? (-> any/c any/c))
   = 
(λ (b)
  (λ (x)
    (if (first-order x)
      x
      (raise-blame-error
       b x
       '(expected: "~a" given: "~e")
       name x))))
  stronger : (or/c #f (-> contract? contract? boolean?)) = #f
  equivalent : (or/c #f (-> contract? contract? boolean?)) = #f
  is-list-contract? : boolean? = #f

procedure

(make-chaperone-contract 
  [#:name name 
  #:first-order first-order 
  #:late-neg-projection late-neg-proj 
  #:collapsible-late-neg-projection collapsible-late-neg-proj 
  #:val-first-projection val-first-proj 
  #:projection proj 
  #:stronger stronger 
  #:equivalent equivalent 
  #:list-contract? is-list-contract?]) 
  chaperone-contract?
  name : any/c = 'anonymous-chaperone-contract
  first-order : (-> any/c any/c) = (λ (x) #t)
  late-neg-proj : (or/c #f (-> blame? (-> any/c any/c any/c)))
   = #f
  collapsible-late-neg-proj : (or/c #f (-> blame? (values (-> any/c any/c any/c) collapsible-contract?)))
   = #f
  val-first-proj : (or/c #f (-> blame? (-> any/c (-> any/c any/c))))
   = #f
  proj : (-> blame? (-> any/c any/c))
   = 
(λ (b)
  (λ (x)
    (if (first-order x)
      x
      (raise-blame-error
       b x
       '(expected: "~a" given: "~e")
       name x))))
  stronger : (or/c #f (-> contract? contract? boolean?)) = #f
  equivalent : (or/c #f (-> contract? contract? boolean?)) = #f
  is-list-contract? : boolean? = #f

procedure

(make-flat-contract 
  [#:name name 
  #:first-order first-order 
  #:late-neg-projection late-neg-proj 
  #:collapsible-late-neg-projection collapsible-late-neg-proj 
  #:val-first-projection val-first-proj 
  #:projection proj 
  #:stronger stronger 
  #:equivalent equivalent 
  #:list-contract? is-list-contract?]) 
  flat-contract?
  name : any/c = 'anonymous-flat-contract
  first-order : (-> any/c any/c) = (λ (x) #t)
  late-neg-proj : (or/c #f (-> blame? (-> any/c any/c any/c)))
   = #f
  collapsible-late-neg-proj : (or/c #f (-> blame? (values (-> any/c any/c any/c) collapsible-contract?)))
   = #f
  val-first-proj : (or/c #f (-> blame? (-> any/c (-> any/c any/c))))
   = #f
  proj : (-> blame? (-> any/c any/c))
   = 
(λ (b)
  (λ (x)
    (if (first-order x)
      x
      (raise-blame-error
       b x
       '(expected: "~a" given: "~e")
       name x))))
  stronger : (or/c #f (-> contract? contract? boolean?)) = #f
  equivalent : (or/c #f (-> contract? contract? boolean?)) = #f
  is-list-contract? : boolean? = #f
These functions build simple higher-order contracts, chaperone contracts, and flat contracts, respectively. They all take the same set of three optional arguments: a name, a first-order predicate, and a blame-tracking projection. For make-flat-contract, see also flat-contract-with-explanation.

The name argument is any value to be rendered using display to describe the contract when a violation occurs. The default name for simple higher-order contracts is anonymous-contract, for chaperone contracts is anonymous-chaperone-contract, and for flat contracts is anonymous-flat-contract.

The first-order predicate first-order is used to determine which values the contract applies to. This test is used by contract-first-order-passes?, and indirectly by or/c and first-or/c to determine which higher-order contract to wrap a value with when there are multiple higher-order contracts to choose from. The default value accepts any value, but it must match the behavior of the projection argument (see below for how). The predicate should be influenced by the value of (contract-first-order-okay-to-give-up?) (see it’s documentation for more explanation).

The late-neg-proj argument defines the behavior of applying the contract via a late neg projection. If it is supplied, this argument accepts a blame object that is missing one party (see also blame-missing-party?). Then it must return a function that accepts both the value that is getting the contract and the name of the missing blame party, in that order. The result must either be the value (perhaps suitably wrapped with a chaperone or impersonator to enforce the contract), or signal a contract violation using raise-blame-error. The default is #f.

The collapsible-late-neg-proj argument takes the place of the late-neg-proj argument for contracts that support collapsing. If it is supplied, this argument accepts a blame object that is missing one party. It must return two values. The first value must be a function that accepts both the value that is getting the contract and the name of the missing blame party, in that order. The second value should be a collapsible representation of the contract.

The projection proj and val-first-proj are older mechanisms for defining the behavior of applying the contract. The proj argument is a curried function of two arguments: the first application accepts a blame object, and the second accepts a value to protect with the contract. The projection must either produce the value, suitably wrapped to enforce any higher-order aspects of the contract, or signal a contract violation using raise-blame-error. The default projection produces an error when the first-order test fails, and produces the value unchanged otherwise. The val-first-proj is like late-neg-proj, except with an extra layer of currying.

At least one of the late-neg-proj, proj, val-first-proj, or first-order must be non-#f.

The projection arguments (late-neg-proj, proj, and val-first-proj) must be in sync with the first-order argument. In particular, if the first-order argument returns #f for some value, then the projections must raise a blame error for that value and if the first-order argument returns #t for some value, then the projection must not signal any blame for this value, unless there are higher-order interactions later. In other words, for flat contracts, the first-order and projection arguments must check the same predicate. For convenience, the the default projection uses the first-order argument, signalling an error when it returns #f and never signalling one otherwise.

Projections for chaperone contracts must produce a value that passes chaperone-of? when compared with the original, uncontracted value. Projections for flat contracts must fail precisely when first-order does, and must produce the input value unchanged otherwise. Applying a flat contract may result in either an application of the predicate, or the projection, or both; therefore, the two must be consistent. The existence of a separate projection only serves to provide more specific error messages. Most flat contracts do not need to supply an explicit projection.

The stronger argument is used to implement contract-stronger?. The first argument is always the contract itself and the second argument is whatever was passed as the second argument to contract-stronger?. If no stronger argument is supplied, then a default that compares its arguments with equal? is used for flat contracts and chaperone contracts. For impersonator contracts constructed with make-contract that do not supply the stronger argument, contract-stronger? returns #f.

Similarly, the equivalent argument is used to implement contract-equivalent?. If it isn’t supplied or #false is supplied, then equal? is used for chaperone and flat contracts, and (λ (x y) #f) is used otherwise.

The is-list-contract? argument is used by the list-contract? predicate to determine if this is a contract that accepts only list? values.

Examples:
> (define int/c
    (make-flat-contract #:name 'int/c #:first-order integer?))
> (contract int/c 1 'positive 'negative)

1

> (contract int/c "not one" 'positive 'negative)

eval:4:0: broke its own contract

  promised: int/c

  produced: "not one"

  in: int/c

  contract from: positive

  blaming: positive

   (assuming the contract is correct)

> (int/c 1)

#t

> (int/c "not one")

#f

> (define int->int/c
    (make-contract
     #:name 'int->int/c
     #:first-order
     (λ (x) (and (procedure? x) (procedure-arity-includes? x 1)))
     #:projection
     (λ (b)
       (let ([domain ((contract-projection int/c) (blame-swap b))]
             [range ((contract-projection int/c) b)])
         (λ (f)
           (if (and (procedure? f) (procedure-arity-includes? f 1))
             (λ (x) (range (f (domain x))))
             (raise-blame-error
              b f
              '(expected "a function of one argument" given: "~e")
              f)))))))
> (contract int->int/c "not fun" 'positive 'negative)

eval:8:0: broke its own contract;

 promised a function of one argument

  produced: "not fun"

  in: int->int/c

  contract from: positive

  blaming: positive

   (assuming the contract is correct)

> (define halve
    (contract int->int/c (λ (x) (/ x 2)) 'positive 'negative))
> (halve 2)

1

> (halve 1/2)

halve: contract violation

  expected: int/c

  given: 1/2

  in: int->int/c

  contract from: positive

  blaming: negative

   (assuming the contract is correct)

> (halve 1)

halve: broke its own contract

  promised: int/c

  produced: 1/2

  in: int->int/c

  contract from: positive

  blaming: positive

   (assuming the contract is correct)

Changed in version 6.0.1.13 of package base: Added the #:list-contract? argument.
Changed in version 6.90.0.30: Added the #:equivalent argument.
Changed in version 7.1.0.10: Added the #:collapsible-late-neg-projection argument.

procedure

(build-compound-type-name c/s ...)  any

  c/s : any/c
Produces an S-expression to be used as a name for a contract. The arguments should be either contracts or symbols. It wraps parentheses around its arguments and extracts the names from any contracts it is supplied with.

procedure

(coerce-contract id v)  contract?

  id : symbol?
  v : any/c
Converts a regular Racket value into an instance of a contract struct, converting it according to the description of contracts.

If v is not one of the coercible values, coerce-contract signals an error, using the first argument in the error message.

procedure

(coerce-contracts id vs)  (listof contract?)

  id : symbol?
  vs : (listof any/c)
Coerces all of the arguments in vs into contracts (via coerce-contract/f) and signals an error if any of them are not contracts. The error messages assume that the function named by id got vs as its entire argument list.

procedure

(coerce-chaperone-contract id v)  chaperone-contract?

  id : symbol?
  v : any/c
Like coerce-contract, but requires the result to be a chaperone contract, not an arbitrary contract.

procedure

(coerce-chaperone-contracts id vs)

  (listof chaperone-contract?)
  id : symbol?
  vs : (listof any/c)
Like coerce-contracts, but requires the results to be chaperone contracts, not arbitrary contracts.

procedure

(coerce-flat-contract id v)  flat-contract?

  id : symbol?
  v : any/c
Like coerce-contract, but requires the result to be a flat contract, not an arbitrary contract.

procedure

(coerce-flat-contracts id v)  (listof flat-contract?)

  id : symbol?
  v : (listof any/c)
Like coerce-contracts, but requires the results to be flat contracts, not arbitrary contracts.

procedure

(coerce-contract/f v)  (or/c contract? #f)

  v : any/c
Like coerce-contract, but returns #f if the value cannot be coerced to a contract.

parameter

(skip-projection-wrapper?)  boolean?

(skip-projection-wrapper? wrap?)  void?
  wrap? : boolean?
 = #f
The functions make-chaperone-contract and build-chaperone-contract-property wrap their arguments to ensure that the result of the projections are chaperones of the input. This layer of wrapping can, in some cases, introduce unwanted overhead into contract checking. If this parameter’s value is #t during the dynamic extent of the call to either of those functions, the wrapping (and thus the checks) are skipped.

syntax

(with-contract-continuation-mark blame body ...)

(with-contract-continuation-mark blame+neg-party body ...)
Inserts a continuation mark that informs the contract profiler (see the contract profiling documentation) that contract checking is happening. For the costs from checking your new combinator to be included, you should wrap any deferred, higher-order checks with this form. First-order checks are recognized automatically and do not require this form.

If your combinator’s projections operate on complete blame objects (i.e., no missing blame parties), the blame object should be the first argument to this form. Otherwise (e.g., in the case of late-neg projections), a pair of the blame object and the missing party should be used instead.

Added in version 6.4.0.4 of package base.

Some contract combinators need to build projections for subcontracts with both regular and blame-swaped versions of the blame that they are given in order to check both access and mutations (e.g., vector/c and vectorof). In the case that such combinators are nested deeply inside each other, there is a potential for an exponential explosion of nested projections being built.

To avoid that explosion, wrap each of the calls to the blame-accepting portion of the combinator in contract-pos/neg-doubling. It returns three values. The first is a boolean, indicating how to interpret the other two results. If the boolean is #t, then the other two results are the values of e1 and e2 and we are not too deep in the nesting. If the boolean is #f, then we have passed a threshold and it is not safe to evaluate e1 and e2 yet, as we are in danger of running into the exponential slowdown. In that case, the last two results are thunks that, when invoked, compute the values of e1 and e2.

As an example, vectorof uses contract-pos/neg-doubling wrapping its two calls to the blame-accepting part of the projection for its subcontract. When it receives a #f as that first boolean, it does not invoke the thunks right away, but waits until the interposition procedure that it attaches to the chaperoned vector is called. Then it invokes them (and caches the result). This delays the construction of the projections until they are actually needed, avoiding the exponential blowup.

Added in version 6.90.0.27 of package base.

8.7.1 Blame Objects🔗ℹ

This section describes blame objects and operations on them.

procedure

(blame? v)  boolean?

  v : any/c
This predicate recognizes blame objects.

procedure

(raise-blame-error b    
  #:missing-party missing-party    
  v    
  fmt    
  v-fmt ...)  none/c
  b : blame?
  missing-party : #f
  v : any/c
  fmt : 
(or/c string?
      (listof (or/c string?
                    'given 'given:
                    'expected 'expected:)))
  v-fmt : any/c
Signals a contract violation. The first argument, b, records the current blame information, including positive and negative parties, the name of the contract, the name of the value, and the source location of the contract application. The #:missing-party argument supplies one of the blame parties. It should be non-#f when the b object was created without supplying a negative party. See blame-add-missing-party and the description of the late-neg-proj argument of make-contract.

The second positional argument, v, is the value that failed to satisfy the contract.

The remaining arguments are a format string, fmt, and its arguments, v-fmt ..., specifying an error message specific to the precise violation.

If fmt is a list, then the elements are concatenated together (with spaces added, unless there are already spaces at the ends of the strings), after first replacing symbols with either their string counterparts, or replacing 'given with "produced" and 'expected with "promised", depending on whether or not the b argument has been swapped or not (see blame-swap).

If fmt contains the symbols 'given: or 'expected:, they are replaced like 'given and 'expected are, but the replacements are prefixed with the string "\n  " to conform to the error message guidelines in Error Message Conventions.

procedure

(blame-add-context blame    
  context    
  [#:important important    
  #:swap? swap?])  blame?
  blame : blame?
  context : (or/c string? #f)
  important : (or/c string? #f) = #f
  swap? : boolean? = #f
Adds some context information to blame error messages that explicates which portion of the contract failed (and that gets rendered by raise-blame-error).

The context argument describes one layer of the portion of the contract, typically of the form "the 1st argument of" (in the case of a function contract) or "a conjunct of" (in the case of an and/c contract).

For example, consider this contract violation:
> (define/contract f
    (list/c (-> integer? integer?))
    (list (λ (x) x)))
> ((car f) #f)

f: contract violation

  expected: integer?

  given: #f

  in: the 1st argument of

      the 1st element of

      (list/c (-> integer? integer?))

  contract from: (definition f)

  blaming: top-level

   (assuming the contract is correct)

  at: eval:2:0

It shows that the portion of the contract being violated is the first occurrence of integer?, because the -> and the list/c combinators each internally called blame-add-context to add the two lines following “in” in the error message.

The important argument is used to build the beginning part of the contract violation. The last important argument that gets added to a blame object is used. The class/c contract adds an important argument, as does the -> contract (when -> knows the name of the function getting the contract).

The swap? argument has the effect of calling blame-swap while adding the layer of context, but without creating an extra blame object.

Passing #f as the context string argument is no longer relevant. For backwards compatibility, blame-add-context returns b when context is #f.

Changed in version 6.90.0.29 of package base: The context argument being #f is no longer relevant.

procedure

(blame-context blame)  (listof string?)

  blame : blame?
Returns the context information that would be supplied in an error message, if blame is passed to raise-blame-error.

procedure

(blame-positive b)  any/c

  b : blame?

procedure

(blame-negative b)  any/c

  b : blame?
These functions produce printable descriptions of the current positive and negative parties of a blame object.

procedure

(blame-contract b)  any/c

  b : blame?
This function produces a description of the contract associated with a blame object (the result of contract-name).

procedure

(blame-value b)  any/c

  b : blame?
This function produces the name of the value to which the contract was applied, or #f if no name was provided.

procedure

(blame-source b)  srcloc?

  b : blame?
This function produces the source location associated with a contract. If no source location was provided, all fields of the structure will contain #f.

procedure

(blame-swap b)  blame?

  b : blame?
This function swaps the positive and negative parties of a blame object. (See also blame-add-context.)

procedure

(blame-original? b)  boolean?

  b : blame?

procedure

(blame-swapped? b)  boolean?

  b : blame?
These functions report whether the current blame of a given blame object is the same as in the original contract invocation (possibly of a compound contract containing the current one), or swapped, respectively. Each is the negation of the other; both are provided for convenience and clarity.

procedure

(blame-replace-negative b neg)  blame?

  b : blame?
  neg : any/c
Produces a blame? object just like b except that it uses neg instead of the negative position b has.

procedure

(blame-replaced-negative? b)  boolean?

  b : blame?
Returns #t if b is the result of calling blame-replace-negative (or the result of some other function whose input was the result of blame-replace-negative).

procedure

(blame-update b pos neg)  blame?

  b : blame?
  pos : any/c
  neg : any/c
Produces a blame? object just like b except that it adds pos and neg to the positive and negative parties of b respectively.

procedure

(blame-missing-party? b)  boolean?

  b : blame?
Returns #t when b does not have both parties.

procedure

(blame-add-missing-party b missing-party)

  (and/c blame? (not/c blame-missing-party?))
  b : (and/c blame? blame-missing-party?)
  missing-party : any/c
Produces a new blame object like b, except that the missing party is replaced with missing-party.

struct

(struct exn:fail:contract:blame exn:fail:contract (object)
    #:extra-constructor-name make-exn:fail:contract:blame)
  object : blame?
This exception is raised to signal a contract error. The object field contains a blame object associated with a contract violation.

parameter

(current-blame-format)  (-> blame? any/c string? string?)

(current-blame-format proc)  void?
  proc : (-> blame? any/c string? string?)
A parameter that is used when constructing a contract violation error. Its value is procedure that accepts three arguments:
  • the blame object for the violation,

  • the value that the contract applies to, and

  • a message indicating the kind of violation.

The procedure then returns a string that is put into the contract error message. Note that the value is often already included in the message that indicates the violation.

Examples:
> (define (show-blame-error blame value message)
    (string-append
     "Contract Violation!\n"
     (format "Guilty Party: ~a\n" (blame-positive blame))
     (format "Innocent Party: ~a\n" (blame-negative blame))
     (format "Contracted Value Name: ~a\n" (blame-value blame))
     (format "Contract Location: ~s\n" (blame-source blame))
     (format "Contract Name: ~a\n" (blame-contract blame))
     (format "Offending Value: ~s\n" value)
     (format "Offense: ~a\n" message)))
> (current-blame-format show-blame-error)
> (define/contract (f x)
    (-> integer? integer?)
    (/ x 2))
> (f 2)

1

> (f 1)

Contract Violation!

Guilty Party: (function f)

Innocent Party: top-level

Contracted Value Name: f

Contract Location: #(struct:srcloc eval 4 0 4 1)

Contract Name: (-> integer? integer?)

Offending Value: 1/2

Offense: promised: integer?

  produced: 1/2

> (f 1/2)

Contract Violation!

Guilty Party: top-level

Innocent Party: (function f)

Contracted Value Name: f

Contract Location: #(struct:srcloc eval 4 0 4 1)

Contract Name: (-> integer? integer?)

Offending Value: 1/2

Offense: expected: integer?

  given: 1/2

8.7.2 Contracts as structs🔗ℹ

The property prop:contract allows arbitrary structures to act as contracts. The property prop:chaperone-contract allows arbitrary structures to act as chaperone contracts; prop:chaperone-contract inherits prop:contract, so chaperone contract structures may also act as general contracts. The property prop:flat-contract allows arbitrary structures to act as flat contracts; prop:flat-contract inherits both prop:chaperone-contract and prop:procedure, so flat contract structures may also act as chaperone contracts, as general contracts, and as predicate procedures.

These properties declare structures to be contracts or flat contracts, respectively. The value for prop:contract must be a contract property constructed by build-contract-property; likewise, the value for prop:chaperone-contract must be a chaperone contract property constructed by build-chaperone-contract-property and the value for prop:flat-contract must be a flat contract property constructed by build-flat-contract-property.

These properties attach a contract value to the protected structure, chaperone, or impersonator value. The function has-contract? returns #t for values that have one of these properties, and value-contract extracts the value from the property (which is expected to be the contract on the value).

These properties attach a blame information to the protected structure, chaperone, or impersonator value. The function has-blame? returns #t for values that have one of these properties, and value-blame extracts the value from the property.

The value is expected to be the blame record for the contract on the value or a cons-pair of a blame record with a missing party and the missing party. The value-blame function reassembles the arguments of the pair into a complete blame record using blame-add-missing-party. If the value has one of the properties, but the value is not a blame object or a pair whose car position is a blame object, then has-blame? returns #f but value-blame returns #f.

procedure

(build-flat-contract-property 
  [#:name get-name 
  #:first-order get-first-order 
  #:late-neg-projection late-neg-proj 
  #:collapsible-late-neg-projection collapsible-late-neg-proj 
  #:val-first-projection val-first-proj 
  #:projection get-projection 
  #:stronger stronger 
  #:equivalent equivalent 
  #:generate generate 
  #:list-contract? is-list-contract?]) 
  flat-contract-property?
  get-name : (-> contract? any/c)
   = (λ (c) 'anonymous-flat-contract)
  get-first-order : (-> contract? (-> any/c boolean?))
   = (λ (c) (λ (x) #t))
  late-neg-proj : (or/c #f (-> contract? (-> blame? (-> any/c any/c any/c))))
   = #f
  collapsible-late-neg-proj : (or/c #f (-> contract? (-> blame? (values (-> any/c any/c any/c) collapsible-contract?))))
   = #f
  val-first-proj : (or/c #f (-> contract? blame? (-> any/c (-> any/c any/c))))
   = #f
  get-projection : (-> contract? (-> blame? (-> any/c any/c)))
   = 
(λ (c)
  (λ (b)
    (λ (x)
      (if ((get-first-order c) x)
          x
          (raise-blame-error
           b x '(expected: "~a" given: "~e")
           (get-name c) x)))))
  stronger : (or/c (-> contract? contract? boolean?) #f) = #f
  equivalent : (or/c #f (-> contract? contract? boolean?)) = #f
  generate : 
(->i ([c contract?])
     [generator
      (c)
      (-> exact-nonnegative-integer?
          (or/c (-> (or/c contract-random-generate-fail? c))
                #f))])
   = (λ (c) (λ (fuel) #f))
  is-list-contract? : (-> contract? boolean?) = (λ (c) #f)

procedure

(build-chaperone-contract-property 
  [#:name get-name 
  #:first-order get-first-order 
  #:late-neg-projection late-neg-proj 
  #:collapsible-late-neg-projection collapsible-late-neg-proj 
  #:val-first-projection val-first-proj 
  #:projection get-projection 
  #:stronger stronger 
  #:equivalent equivalent 
  #:generate generate 
  #:exercise exercise 
  #:list-contract? is-list-contract?]) 
  chaperone-contract-property?
  get-name : (-> contract? any/c)
   = (λ (c) 'anonymous-chaperone-contract)
  get-first-order : (-> contract? (-> any/c boolean?))
   = (λ (c) (λ (x) #t))
  late-neg-proj : (or/c #f (-> contract? (-> blame? (-> any/c any/c any/c))))
   = #f
  collapsible-late-neg-proj : (or/c #f (-> contract? (-> blame? (values (-> any/c any/c any/c) collapsible-contract?))))
   = #f
  val-first-proj : (or/c #f (-> contract? blame? (-> any/c (-> any/c any/c))))
   = #f
  get-projection : (-> contract? (-> blame? (-> any/c any/c)))
   = 
(λ (c)
  (λ (b)
    (λ (x)
      (if ((get-first-order c) x)
          x
          (raise-blame-error
           b x '(expected: "~a" given: "~e")
           (get-name c) x)))))
  stronger : (or/c (-> contract? contract? boolean?) #f) = #f
  equivalent : (or/c #f (-> contract? contract? boolean?)) = #f
  generate : 
(->i ([c contract?])
     [generator
      (c)
      (-> exact-nonnegative-integer?
          (or/c (-> (or/c contract-random-generate-fail? c))
                #f))])
   = (λ (c) (λ (fuel) #f))
  exercise : 
(->i ([c contract?])
     [result
      (c)
      (-> exact-nonnegative-integer?
          (values
           (-> c void?)
           (listof contract?)))])
   = (λ (c) (λ (fuel) (values void '())))
  is-list-contract? : (-> contract? boolean?) = (λ (c) #f)

procedure

(build-contract-property 
  [#:name get-name 
  #:first-order get-first-order 
  #:late-neg-projection late-neg-proj 
  #:collapsible-late-neg-projection collapsible-late-neg-proj 
  #:val-first-projection val-first-proj 
  #:projection get-projection 
  #:stronger stronger 
  #:equivalent equivalent 
  #:generate generate 
  #:exercise exercise 
  #:list-contract? is-list-contract?]) 
  contract-property?
  get-name : (-> contract? any/c) = (λ (c) 'anonymous-contract)
  get-first-order : (-> contract? (-> any/c boolean?))
   = (λ (c) (λ (x) #t))
  late-neg-proj : (or/c #f (-> contract? (-> blame? (-> any/c any/c any/c))))
   = #f
  collapsible-late-neg-proj : (or/c #f (-> contract? (-> blame? (values (-> any/c any/c any/c) collapsible-contract?))))
   = #f
  val-first-proj : (or/c #f (-> contract? blame? (-> any/c (-> any/c any/c))))
   = #f
  get-projection : (-> contract? (-> blame? (-> any/c any/c)))
   = 
(λ (c)
  (λ (b)
    (λ (x)
      (if ((get-first-order c) x)
          x
          (raise-blame-error
           b x '(expected: "~a" given: "~e")
           (get-name c) x)))))
  stronger : (or/c (-> contract? contract? boolean?) #f) = #f
  equivalent : (or/c #f (-> contract? contract? boolean?)) = #f
  generate : 
(->i ([c contract?])
     [generator
      (c)
      (-> exact-nonnegative-integer?
          (or/c (-> (or/c contract-random-generate-fail? c))
                #f))])
   = (λ (c) (λ (fuel) #f))
  exercise : 
(->i ([c contract?])
     [result
      (c)
      (-> exact-nonnegative-integer?
          (values
           (-> c void?)
           (listof contract?)))])
   = (λ (c) (λ (fuel) (values void '())))
  is-list-contract? : (-> contract? boolean?) = (λ (c) #f)
These functions build the arguments for prop:contract, prop:chaperone-contract, and prop:flat-contract, respectively.

A contract property specifies the behavior of a structure when used as a contract. It is specified in terms of seven properties:
  • get-name which produces a description to write as part of a contract violation;

  • get-first-order, which produces a first-order predicate to be used by contract-first-order-passes?;

  • late-neg-proj, which produces a blame-tracking projection defining the behavior of the contract (The get-projection and val-first-proj arguments also specify the projection, but using a different signature. They are here for backwards compatibility.);

  • collapsible-late-neg-proj, similar to late-neg-proj which produces a blame-tracking projection defining the behavior of the contract, this function additionally specifies the collapsible behavior of the contract;

  • stronger, a predicate that determines whether this contract (passed in the first argument) is stronger than some other contract (passed in the second argument) and whose default always returns #f;

  • equivalent, a predicate that determines whether this contract (passed in the first argument) is equivalent to some other contract (passed in the second argument); the default for flat and chaperone contracts is equal? and for impersonator contracts returns #f;

  • generate, which returns a thunk that generates random values matching the contract (using contract-random-generate-fail) to indicate failure) or #f to indicate that random generation for this contract isn’t supported;

  • exercise, which returns a function that exercises values matching the contract (e.g., if it is a function contract, it may call the function) and a list of contracts whose values will be generated by this process;

  • and is-list-contract?, which is used by flat-contract? to determine if this contract accepts only list?s.

At least one of the late-neg-proj, collapsible-late-neg-proj, get-projection, val-first-proj, or get-first-order must be non-#f.

These accessors are passed as (optional) keyword arguments to build-contract-property, and are applied to instances of the appropriate structure type by the contract system. Their results are used analogously to the arguments of make-contract.

A chaperone contract property specifies the behavior of a structure when used as a chaperone contract. It is specified using build-chaperone-contract-property, and accepts exactly the same set of arguments as build-contract-property. The only difference is that the projection accessor must return a value that passes chaperone-of? when compared with the original, uncontracted value.

A flat contract property specifies the behavior of a structure when used as a flat contract. It is specified using build-flat-contract-property, and accepts similar arguments as build-contract-property. The differences are:
  • the projection accessor is expected not to wrap its argument in a higher-order fashion, analogous to the constraint on projections in make-flat-contract;

  • the #:exercise keyword argument is omitted because it is not relevant for flat contracts.

Changed in version 6.0.1.13 of package base: Added the #:list-contract? argument.
Changed in version 6.1.1.4: Allow generate to return contract-random-generate-fail.
Changed in version 6.90.0.30: Added the #:equivalent argument.
Changed in version 7.1.0.10: Added the #:collapsible-late-neg-projection argument.

procedure

(contract-property? v)  boolean?

  v : any/c

procedure

(chaperone-contract-property? v)  boolean?

  v : any/c

procedure

(flat-contract-property? v)  boolean?

  v : any/c
These predicates detect whether a value is a contract property, chaperone contract property, or a flat contract property, respectively.

8.7.3 Obligation Information in Check Syntax🔗ℹ

Check Syntax in DrRacket shows obligation information for contracts according to syntax-propertys that the contract combinators leave in the expanded form of the program. These properties indicate where contracts appear in the source and where the positive and negative positions of the contracts appear.

To make Check Syntax show obligation information for your new contract combinators, use the following properties (some helper macros and functions are below):

syntax

(define/final-prop header body ...)

 
header = main-id
  | (main-id id ...)
  | (main-id id ... . id)
The same as (define header body ...), except that uses of main-id in the header are annotated with the 'racket/contract:contract property (as above).

syntax

(define/subexpression-pos-prop header body ...)

 
header = main-id
  | (main-id id ...)
  | (main-id id ... . id)
The same as (define header body ...), except that uses of main-id in the header are annotated with the 'racket/contract:contract property (as above) and arguments are annotated with the 'racket/contract:positive-position property.

8.7.4 Utilities for Building New Combinators🔗ℹ

procedure

(contract-stronger? c1 c2)  boolean?

  c1 : contract?
  c2 : contract?
Returns #t if the contract c1 accepts either fewer or the same set of values that c2 does.

Chaperone contracts and flat contracts that are the same (i.e., where c1 is equal? to c2) are considered to always be stronger than each other.

This function is conservative, so it may return #f when c1 does, in fact, accept fewer values.

Examples:
> (contract-stronger? integer? integer?)

#t

> (contract-stronger? (between/c 25 75) (between/c 0 100))

#t

> (contract-stronger? (between/c 0 100) (between/c 25 75))

#f

> (contract-stronger? (between/c -10 0) (between/c 0 10))

#f

> (contract-stronger? (λ (x) (and (real? x) (<= x 0)))
                      (λ (x) (and (real? x) (<= x 100))))

#f

procedure

(contract-equivalent? c1 c2)  boolean?

  c1 : contract?
  c2 : contract?
Returns #t if the contract c1 accepts the same set of values that c2 does.

Chaperone contracts and flat contracts that are the same (i.e., where c1 is equal? to c2) are considered to always be equivalent to each other.

This function is conservative, so it may return #f when c1 does, in fact, accept the same set of values that c2 does.

Examples:
> (contract-equivalent? integer? integer?)

#t

> (contract-equivalent? (non-empty-listof integer?)
                        (cons/c integer? (listof integer?)))

#t

> (contract-equivalent? (λ (x) (and (real? x) (and (number? x) (>= (sqr x) 0))))
                        (λ (x) (and (real? x) (real? x))))

#f

Added in version 6.90.0.30 of package base.

procedure

(contract-first-order-passes? contract v)  boolean?

  contract : contract?
  v : any/c
Returns a boolean indicating whether the first-order tests of contract pass for v.

If it returns #f, the contract is guaranteed not to hold for that value; if it returns #t, the contract may or may not hold. If the contract is a first-order contract, a result of #t guarantees that the contract holds.

See also contract-first-order-okay-to-give-up? and contract-first-order-try-less-hard.

procedure

(contract-first-order c)  (-> any/c boolean?)

  c : contract?
Produces the first-order test used by or/c to match values to higher-order contracts.