On this page:
3.1 Defining low-level mutators
define-mutator
define-dependent-mutator
3.2 Low-level mutation interface
maybe-mutate
mutated
mutated/  c
mutated-do
mutated-do-single
mmap
mbind
mtest
mutation-index?
counter?
3.3 Mutator combinators
mutator/  c
dependent-mutator/  c
compose-mutators
apply-mutators
make-guarded-mutator
make-stream-mutator
mutator-type
mutate-in-sequence
rearrange-in-sequence
compound-expr?
no-mutation
3.4 Expression and program mutators:   syntax traversal
3.4.1 Expression mutators
make-expr-mutator
mutation-guard
mutation-guarded?
expression-selector/  c
select-any-expr
3.4.2 Program mutators
make-program-mutator
without-counter
syntax-only
program-mutator->module-mutator
program-mutator->stream-builder
mutated-program
top-level-selector/  c
select-all
select-define-body
select-define/  contract-body
select-any-define-named-form-body
3.5 Logging:   recovering the mutation type that causes a mutation
mutate-logger

3 Low-level mutator tools🔗ℹ

 (require mutate/low-level) package: mutate-lib

This section of the library offers a low-level interface to defining mutators. This interface requires you (the mutator designer) to handle an extra piece of information to keep track of mutation points during traversal:

Internally, this library uses a counter (called a mutation counter) to keep track of the mutation points found as it traverses a program. Every mutator consumes a counter and produces an updated counter along with its possibly-mutated result syntax. The counter (along with the mutation index) provides the mechanism to decide whether a particular mutation point should be used or not: if a mutator is applied with a counter that is smaller than the mutation index, then that mutator’s mutation point should be skipped and the counter incremented to record that a mutation point has been passed; when the counter is equal to the mutation index, then the mutation point has been selected and the mutation should be performed as well as incrementing the counter. Thus the counter must be threaded through the program traversal and mutator applications.

With the mutation counter, we have all the pieces to fully define what consistutes a mutator concretely. A mutator is a function of three arguments: a piece of syntax, a mutation index, and the current mutation counter, and it returns two things: the possibly-mutated syntax, and the updated mutation counter. Technically, the two results are wrapped in a mutated struct. See mutator/c for all the technical details to the definition, but this is the core idea.

Important: it is your responsibility as the designer of a mutator using low-level mutator tools to thread the current counter value. Tools like mutated-do are provided to lessen this burden: use them. Failing to thread the counter properly will result in unpredictable selection of mutants by mutation index.

The low level mutator api also offers more control over how mutators come together to build a mutation engine:

With one or more simple mutators in hand, you can combine them all together (with compose-mutators) and uses the resulting mutator to create an expression mutator (with make-expr-mutator). The expression mutator traverses the syntax it receives, searching for mutation points for the simple mutator(s) it was created with. In other words, make-expr-mutator lifts a simple mutator from mutating single expressions to mutating expressions including all of their sub-expressions.

Finally, you can use an expression mutator to create a program mutator (with make-program-mutator). The program mutator traverses a whole program / module based on a notion of top level forms, deciding which top level forms to consider for mutation, and communicating to its caller additional information about which top level form is selected for mutation by a given mutation index – or raising an error if the index exceeds the maximum possible for a program. The default program mutator probably returns more information than you need, so you can use the transformers starting with without-counter to simplify its results.

3.1 Defining low-level mutators🔗ℹ

syntax

(define-mutator (id stx-id mutation-index-id counter-id) #:type type-expr
  body ...)
Defines a general-purpose mutator accepting first the syntax to mutate, then the mutation index, and finally the current mutation counter.

Unlike the simpler mutator definition forms above, the body of the mutator should produce a mutated value rather than plain syntax. The result should be a mutated version of the syntax received, produced with the low-level mutator tools in Low-level mutation interface.

Usually this form is only necessary for complex mutators, and even then most of the time you will be better off building such a mutator out of simpler pieces defined with the above forms and combined together with compose-mutators.

Examples:
> (define-mutator (rearrange-positional-exprs stx mutation-index counter)
    #:type "position-swap"
    (syntax-parse stx
      [(head e ...)
       (mutated-do-single [rearranged-e-stxs (rearrange-in-sequence (attribute e)
                                                                    mutation-index
                                                                    counter)]
                          #:return (quasisyntax/loc stx
                                     (head #,@rearranged-e-stxs)))]
      [else
       (no-mutation stx mutation-index counter)]))
> (rearrange-positional-exprs #'(f 1 2 x y) 0)

(mutated #<syntax:eval:2:0 (f 2 1 x y)> 1)

> (rearrange-positional-exprs #'(f 1 2 x y) 1)

(mutated #<syntax:eval:3:0 (f 1 2 y x)> 2)

syntax

(define-dependent-mutator (id formal ...) #:type type-expr
  body ...)
Defines a dependent mutator, which is roughly a function of any arguments that produces a mutator.

This form is useful for defining mutators for which the mutation depends on something other than the immediate syntax of an expression to be mutated. For example, a mutator might depend on the contents of the whole module; in that case, this form can define a dependent mutator that expects the module syntax, and analyzes that syntax to produce a mutator. The easiest way to produce a mutator is by using one of the above mutator definition forms and then returning it.

3.2 Low-level mutation interface🔗ℹ

procedure

(maybe-mutate original    
  new    
  mutation-index    
  counter    
  [#:equivalent? equivalent?])  mutated?
  original : syntax?
  new : syntax?
  mutation-index : mutation-index?
  counter : counter?
  equivalent? : (syntax? syntax? . -> . boolean?)
   = syntax-equal?
The primitive mutation operation. All mutators boil down to applications of maybe-mutate.

Decides whether to swap original with new based on whether mutation-index and counter are equal.

Regardless of whether the swap is performed or not, the resulting mutated? object accounts for the fact that a mutation point has been reached. Hence, all accounting of mutation indexes and mutation counters is managed by maybe-mutate.

The equivalent? argument determines if original and new are equivalent, in which case the swap does not count as a mutation point.

Examples:
> (maybe-mutate #'x #'y 0 0)

(mutated #<syntax:eval:1:0 y> 1)

> (maybe-mutate #'x #'x 0 0) ; no mutation point recorded because original and new are the same

(mutated #<syntax:eval:2:0 x> 0)

> (maybe-mutate #'x #'y 1 0) ; no mutation because counter != index

(mutated #<syntax:eval:3:0 x> 1)

> (maybe-mutate #'x #'y 0 1) ; no mutation because counter != index

(mutated #<syntax:eval:4:0 x> 2)

struct

(struct mutated (stx new-counter)
    #:transparent)
  stx : syntax?
  new-counter : counter?
The struct that wraps a possibly-mutated piece of syntax with an updated mutation counter.

procedure

(mutated/c inner-ctc)  contract?

  inner-ctc : contract?
The contract combinator for making contracts that recognize mutated structs.

syntax

(mutated-do #:count-with [counter-id counter-value-expr]
  action-clause ...
  terminating-clause)
 
action-clause = [pat mutated-expr]
  | #:let [pat expr]
     
terminating-clause = #:return expr
  | #:in mutated-expr
A syntactic shorthand for sequencing a series of mutator applications, threading the counter through the applications. mutated-do implicitly unpacks the result of each application to extract the new syntax (binding it with pat like match-define), and the new counter (binding it to counter-id). Hence, the form is analagous to match-let*, where every clause always has the most-up-to-date counter bound to counter-id.

The #:return clause terminates the sequence with an expression for the resulting piece of syntax; mutated-do implicitly wraps that resulting syntax with the current value of the counter.

Examples:
> (define-mutator (to-a/b/c! stx mutation-index counter) #:type "to-a/b/c!"
    (mutated-do #:count-with [current-counter counter]
      [after-a     (maybe-mutate stx       #'a! mutation-index current-counter)]
      ; `current-counter` is now counter + 1
      [after-a+b   (maybe-mutate after-a   #'b! mutation-index current-counter)]
      ; `current-counter` is now counter + 2
      [after-a+b+c (maybe-mutate after-a+b #'c! mutation-index current-counter)]
      ; `current-counter` is now counter + 3, which will be wrapped with the returned result
      #:return after-a+b+c))
> (to-a/b/c! #'original 0 0)

(mutated #<syntax:eval:1:0 a!> 3)

> (to-a/b/c! #'original 1 0)

(mutated #<syntax:eval:1:0 b!> 3)

> (to-a/b/c! #'original 2 0)

(mutated #<syntax:eval:1:0 c!> 3)

The #:let action-clause inserts a let-like binding of a normal value inside a sequence; i.e. the expr of such a clause is not expected to be a mutated value and is not implicitly unwrapped.

Examples:
> (define-mutator (add-length stx mutation-index counter) #:type "add-length"
    (mutated-do #:count-with [current-counter counter]
      [maybe-a/b/c!    (to-a/b/c! stx mutation-index current-counter)]
      #:let [stx-parts (syntax->list maybe-a/b/c!)]
      #:let [len       (if stx-parts (length stx-parts) -1)]
      [with-len        (maybe-mutate maybe-a/b/c!
                                     #`(#,maybe-a/b/c! #,len)
                                     mutation-index
                                     current-counter)]
      #:return with-len))
> (add-length #'(+ 1 2) 0 0)

(mutated #<syntax:eval:1:0 a!> 4)

; mutation indices 1 and 2 trigger `to-a/b/c!`...
> (add-length #'(+ 1 2) 3 0)

(mutated #<syntax:eval:5:0 ((+ 1 2) 3)> 4)

> (add-length #'0 3 0)

(mutated #<syntax:eval:5:0 (0 -1)> 4)

The #:in terminating clause terminates the sequence, but the expected result of the mutated-expr should be a mutated value, which is the result of the overall sequence as-is (no implicit wrapping).

For example, to-a/b/c! could have terminated the sequence directly with the final application of maybe-mutate:
> (define-mutator (to-a/b/c!-2 stx mutation-index counter) #:type "to-a/b/c!"
    (mutated-do #:count-with [current-counter counter]
      [after-a     (maybe-mutate stx       #'a! mutation-index current-counter)]
      [after-a+b   (maybe-mutate after-a   #'b! mutation-index current-counter)]
      #:in (maybe-mutate after-a+b #'c! mutation-index current-counter)))
> (to-a/b/c!-2 #'original 0 0)

(mutated #<syntax:eval:9:0 a!> 3)

> (to-a/b/c!-2 #'original 1 0)

(mutated #<syntax:eval:9:0 b!> 3)

> (to-a/b/c!-2 #'original 2 0)

(mutated #<syntax:eval:9:0 c!> 3)

syntax

(mutated-do-single clause #:return result)

Shorthand for mutated-do with a single action clause followed by a return.

This shorthand is provided because it is a common pattern, and in this case there’s no point specifying a counter identifier because the counter is only threaded directly from the result of clause to the wrapper of result.

procedure

(mmap f m)  (mutated/c syntax?)

  f : (syntax? . -> . syntax?)
  m : (mutated/c syntax?)
Maps f over the syntax in m, producing a new mutated struct with the resulting syntax and the same counter as m.

procedure

(mbind f m)  (mutated/c syntax?)

  f : (syntax? counter? . -> . (mutated/c syntax?))
  m : (mutated/c syntax?)
Applies f with the contents of m.

procedure

(mtest pred m)  boolean?

  pred : (syntax? . -> . boolean?)
  m : (mutated/c syntax?)
Applies pred to the syntax in m.

Predicates for mutation indexes and mutation counters. Since they’re both just natural numbers, the value of these predicates is purely for documentation.

3.3 Mutator combinators🔗ℹ

The following procedures provide an api for creating mutators in a different way from the definition forms above, as well as manipulating mutators.

contract

mutator/c : contract?

The contract for mutators.

In fact, plain functions can be used as mutators too, if they have the right interface. Roughly, this contract corresponds to either:

procedure

(dependent-mutator/c dom-ctc ...)  contract?

  dom-ctc : contract?
Creates a contract for a dependent mutator with domain specified by dom-ctcs and which produces a mutator/c.

procedure

(compose-mutators mutator ...)  mutator/c

  mutator : mutator/c
Composes multiple mutators together into a single one, which applies each of the mutators in the given order.

Given zero mutators, returns no-mutation.

Examples:
> (define-constant-mutator (increment-integer-consts v)
    [(? integer?) #:-> (add1 v)])
> (define-constant-mutator (negate-integer-consts v)
    [(? integer?) #:-> (- v)])
> (define inc-or-negate-ints (compose-mutators increment-integer-consts negate-integer-consts))
> (inc-or-negate-ints #'5 0 0)

(mutated #<syntax:eval:4:0 6> 1)

> (inc-or-negate-ints #'5 1 0)

(mutated #<syntax:eval:5:0 -5> 2)

procedure

(apply-mutators stx    
  mutators    
  mutation-index    
  counter)  (mutated/c syntax?)
  stx : syntax?
  mutators : (listof mutator/c)
  mutation-index : mutation-index?
  counter : counter?
Applies a sequence of mutators in order.

Examples:
> (apply-mutators #'5 (list increment-integer-consts negate-integer-consts) 0 0)

(mutated #<syntax:eval:6:0 6> 1)

> (apply-mutators #'5 (list increment-integer-consts negate-integer-consts) 1 0)

(mutated #<syntax:eval:7:0 -5> 2)

procedure

(make-guarded-mutator guard    
  transformer    
  [#:type type])  mutator/c
  guard : (syntax? . -> . boolean?)
  transformer : (syntax? . -> . syntax?)
  type : string? = #f
Creates a mutator which performs the transformation transformer on syntax only if guard produces #t.

This is a more flexible, if often more verbose, version of define-simple-mutator.

If not provided, type defaults to the type of the mutator in which make-guarded-mutator is applied.

Examples:
> (define if-swap2
    (make-guarded-mutator (syntax-parser [({~datum if} c t e) #t]
                                         [else #f])
                          (syntax-parser [({~datum if} c t e) #'(if c e t)])))
> (if-swap2 #'(if (< x 0) 0 (f x)) 0 0)

(mutated #<syntax:eval:1:0 (if (< x 0) (f x) 0)> 1)

> (if-swap2 #'(not-an-if 42 (+ 2 3)) 0 0)

(mutated #<syntax:eval:3:0 (not-an-if 42 (+ 2 3))> 0)

procedure

(make-stream-mutator make-stream    
  [#:type type])  mutator/c
  make-stream : (syntax? . -> . (stream/c syntax?))
  type : string? = #f
Creates a mutator that draws syntax transformations from a stream of such transformations produced by make-stream. The resulting mutator maps the sequence of mutations produced by transformer to distinct mutation points on the same piece of syntax.

If not provided, type defaults to the type of the mutator in which make-stream-mutator is applied.

Examples:
> (require racket/stream)
> (define (permutation-stream stx)
    (for/stream ([p (in-permutations (syntax->list stx))])
      (datum->syntax stx p)))
> (define rearrange (make-stream-mutator permutation-stream))
> (rearrange #'(a b c) 0 0)

(mutated #<syntax (b a c)> 1)

> (rearrange #'(a b c) 1 0)

(mutated #<syntax (a c b)> 2)

> (rearrange #'(a b c) 2 0)

(mutated #<syntax (c a b)> 3)

> (rearrange #'(a b c) 3 0)

(mutated #<syntax (b c a)> 4)

> (rearrange #'(a b c) 4 0)

(mutated #<syntax (c b a)> 5)

> (rearrange #'(a b c) 5 0)

(mutated #<syntax:eval:9:0 (a b c)> 5)

procedure

(mutator-type mutator [default])  string?

  mutator : mutator/c
  default : string? = "<?>"
Tries to extract the mutator type of a mutator. For mutators defined by the mutator definition forms and created by make-guarded-mutator and make-stream-mutator, this produces the string provided at definition/creation.

If the type can’t be extracted (e.g. because the mutator is a plain function), default is returned.

Example:
> (mutator-type increment-integer-consts)

"increment-integer-consts"

procedure

(mutate-in-sequence stxs    
  mutation-index    
  counter    
  mutator)  (mutated/c syntax?)
  stxs : (listof syntax?)
  mutation-index : mutation-index?
  counter : counter?
  mutator : mutator/c
Maps mutator over each element the given list in sequence, threading the counter across the applications and wrapping the resulting list with the final counter value.

Examples:
> (mutate-in-sequence (list #'5 #'#f #'7 #'(+ 2 2)) 0 0 increment-integer-consts)

(mutated

 '(#<syntax:eval:9:0 6>

   #<syntax:eval:9:0 #f>

   #<syntax:eval:9:0 7>

   #<syntax:eval:9:0 (+ 2 2)>)

 1)

> (mutate-in-sequence (list #'5 #'#f #'7 #'(+ 2 2)) 1 0 increment-integer-consts)

(mutated

 '(#<syntax:eval:10:0 5>

   #<syntax:eval:10:0 #f>

   #<syntax:eval:10:0 8>

   #<syntax:eval:10:0 (+ 2 2)>)

 2)

procedure

(rearrange-in-sequence stxs    
  mutation-index    
  counter)  (mutated/c syntax?)
  stxs : (listof syntax?)
  mutation-index : mutation-index?
  counter : counter?
A (sort-of) mutation that swaps elements of stxs pairwise.

Examples:
> (rearrange-in-sequence (list #'1 #'2 #'3 #'4 #'5) 0 0)

(mutated

 '(#<syntax:eval:1:0 2>

   #<syntax:eval:1:0 1>

   #<syntax:eval:1:0 3>

   #<syntax:eval:1:0 4>

   #<syntax:eval:1:0 5>)

 1)

> (rearrange-in-sequence (list #'1 #'2 #'3 #'4 #'5) 1 0)

(mutated

 '(#<syntax:eval:2:0 1>

   #<syntax:eval:2:0 2>

   #<syntax:eval:2:0 4>

   #<syntax:eval:2:0 3>

   #<syntax:eval:2:0 5>)

 2)

> (rearrange-in-sequence (list #'1 #'2 #'3 #'4 #'5) 2 0)

(mutated

 '(#<syntax:eval:3:0 1>

   #<syntax:eval:3:0 2>

   #<syntax:eval:3:0 3>

   #<syntax:eval:3:0 4>

   #<syntax:eval:3:0 5>)

 2)

procedure

(compound-expr? stx)  boolean?

  stx : syntax?
Returns true for syntax starting with parentheses.

A mutator that does nothing to its argument.

Example:
> (no-mutation #'x 0 0)

(mutated #<syntax:eval:1:0 x> 0)

3.4 Expression and program mutators: syntax traversal🔗ℹ

 (require mutate/traversal) package: mutate-lib

3.4.1 Expression mutators🔗ℹ

procedure

(make-expr-mutator mutator    
  [#:select select-expr])  mutator/c
  mutator : mutator/c
  select-expr : expression-selector/c = select-any-expr
Creates an expression mutator out of a mutator by considering not only the top level of a piece of syntax for mutation, but also traversing into the syntax to consider sub-expressions for mutation.

select-expr selects which expressions to traverse into for discovering mutation points; see expression-selector/c. The default selects everything.

Examples:
> (define-constant-mutator (increment-integer-consts v)
    [(? integer?) #:-> (add1 v)])
; Simple mutators only consider the top level shape of the syntax.
> (increment-integer-consts #'5 0 0) ; so this mutates

(mutated #<syntax:eval:2:0 6> 1)

> (increment-integer-consts #'(list 5 10) 0 0) ; but this doesn't

(mutated #<syntax:eval:3:0 (list 5 10)> 0)

> (define increment-integer-consts/expr (make-expr-mutator increment-integer-consts))
> (increment-integer-consts/expr #'(list 5 10) 0 0) ; now the traversal finds the 5 to mutate

(mutated #<syntax:eval:5:0 (list 6 10)> 1)

> (increment-integer-consts/expr #'(list 5 10) 1 0) ; and then the 10

(mutated #<syntax:eval:6:0 (list 5 11)> 2)

procedure

(mutation-guard stx)  syntax?

  stx : syntax?
Guards the given piece of syntax from being traversed any further by mutate-expr. This effectively hides any mutation points in subexpressions of stx from mutate-expr’s traversal.

This is useful for ensuring that only certain mutations can happen to a form, like in the example below.

Examples:
> (define-mutator (negate-if-cond-only stx mutation-index counter) #:type "negate-if-cond-only"
    (syntax-parse stx
      [({~datum if} cond t e)
       ; Guard below marks conditions so that sub-parts don't get considered for mutation.
       ; This avoids some obvious equivalent mutants, but may miss interesting ones
       ; (e.g. involving side effects in conditions).
       ; Example:
       ; (if (not #t) a b) could be mutated by this mutator to (if (not (not #t)) a b),
       ; and by a constant swap mutator to (if (not #f) a b).
       ; The mutation guard prevents the second mutation.
       (mutated-do-single [negated-cond (maybe-mutate #'cond #'(not cond) mutation-index counter)]
                          #:return (mutation-guard #`(if #,negated-cond t e)))]
      [else (no-mutation stx mutation-index counter)]))
> (define-constant-mutator (bool-constant-swap v)
    [(? boolean?) #:-> (not v)])
> (define expr-mutator
    (make-expr-mutator (compose-mutators negate-if-cond-only bool-constant-swap)))
> (expr-mutator #'(if (not #f) 1 2) 0 0)

(mutated #<syntax:eval:1:0 (if (not (not #f)) 1 2)> 1)

> (expr-mutator #'(if (not #f) 1 2) 1 0)

(mutated #<syntax:eval:1:0 (if (not #f) 1 2)> 1)

procedure

(mutation-guarded? stx)  boolean?

  stx : syntax?
A predicate recognizing mutation-guarded syntax.

Examples:
> (mutation-guarded? #'hello)

#f

> (mutation-guarded? (mutation-guard #'hello))

#t

contract

expression-selector/c : contract?

 = 
(syntax?
 . -> .
 (or/c #f
       (list/c syntax?
               (syntax? . -> . syntax?)
               (listof (cons/c parameter? any/c)))))
The contract for expression selectors provided to make-expr-mutator or build-mutation-engine.

An expression selector is a function that controls which expressions are traversed to find mutation points. Specifically, it is a function that, provided the syntax of an expression, returns either
  • false, to indicate that the expression should not be considered for mutation or traversal, or

  • a list of three things:
    • The syntax to be considered for mutation and traversal. This is typically the expression given as input, but not necessarily so: the selector may extract a just sub-part of the expression to be considered.

    • A function to reconstruct the whole expression corresponding to the input, given a mutated version of the first item of the list.

    • An association list of parameters and values to set while considering the first item of the list for mutation and traversal.

Examples:
> (define ignore-begin-effect-exprs
    (syntax-parser
      [({~datum begin} non-result-e ... result-e)
       (list #'result-e
             (λ (new-result-e) #`(begin non-result-e ... #,new-result-e))
             empty)]
      [other-e
       (list #'other-e
             (λ (x) x)
             empty)]))
> (define iic/except-in-begin-effect-exprs
    (make-expr-mutator increment-integer-consts #:select ignore-begin-effect-exprs))
; The 5 in (displayln 5) will not be considered.
> (iic/except-in-begin-effect-exprs #'(if (= 5 x) (begin (displayln 5) (+ y 5)) 0) 0 0)

(mutated #<syntax:eval:9:0 (if (= 6 x) (begin (displayln 5) (+ y 5)) 0)> 1)

> (iic/except-in-begin-effect-exprs #'(if (= 5 x) (begin (displayln 5) (+ y 5)) 0) 1 0)

(mutated #<syntax:eval:10:0 (if (= 5 x) (begin (displayln 5) (+ y 6)) 0)> 2)

> (iic/except-in-begin-effect-exprs #'(if (= 5 x) (begin (displayln 5) (+ y 5)) 0) 2 0)

(mutated #<syntax:eval:11:0 (if (= 5 x) (begin (displayln 5) (+ y 5)) 1)> 3)

The expression selector that selects everything.

3.4.2 Program mutators🔗ℹ

procedure

(make-program-mutator mutator 
  [#:select select]) 
  
({syntax? mutation-index?} {counter?} . ->* . (or/c (mutated/c mutated-program?)
                                                    #f))
  mutator : mutator/c
  select : top-level-selector/c = select-all
Creates a full program mutator out of a mutator (which is usually an expression mutator produced by make-expr-mutator).

Similar to make-expr-mutator, select selects top level expressions to consider for mutation and traversal.

The resulting program mutator expects a syntax-list of top level forms of the program; i.e. a program with the shape #'[top-level-form ...]. (But see program-mutator->module-mutator.) It returns a mutated-program, which contains the syntax of the mutated program and an identifier for the top level form which was mutated (as produced by select, see top-level-selector/c for details).

If the program mutator is called with a mutation index that is larger than the total number of mutation points, it returns #f.

Examples:
> (define mutate-program
    (make-program-mutator (make-expr-mutator increment-integer-consts)))
> (mutate-program #'[(provide x y)
                     (displayln 0)
                     (define x 5)
                     (define y (+ x 1))]
                  0)

(mutated

 (mutated-program

  #<syntax:eval:13:0 ((provide x y) (displayln 1) (define x 5) (define y (+ x 1)))>

  'displayln)

 1)

> (mutate-program #'[(provide x y)
                     (displayln 0)
                     (define x 5)
                     (define y (+ x 1))]
                  1)

(mutated

 (mutated-program

  #<syntax:eval:14:0 ((provide x y) (displayln 0) (define x 6) (define y (+ x 1)))>

  'define)

 2)

> (mutate-program #'[(provide x y)
                     (displayln 0)
                     (define x 5)
                     (define y (+ x 1))]
                  2)

(mutated

 (mutated-program

  #<syntax:eval:15:0 ((provide x y) (displayln 0) (define x 5) (define y (+ x 2)))>

  'define)

 3)

> (mutate-program #'[(provide x y)
                     (displayln 0)
                     (define x 5)
                     (define y (+ x 1))]
                  3)

#f

; with selector
> (define mutate-program-defines
    (make-program-mutator (make-expr-mutator increment-integer-consts)
                          #:select select-define-body))
> (mutate-program-defines #'[(provide x y)
                             (displayln 0)
                             (define x 5)
                             (define y (+ x 1))]
                          0)

(mutated

 (mutated-program

  #<syntax:eval:18:0 ((provide x y) (displayln 0) (define x 6) (define y (+ x 1)))>

  'x)

 1)

procedure

(without-counter program-mutator)

  ({syntax? mutation-index?} {counter?} . ->* . mutated-program?)
  program-mutator : 
({syntax? mutation-index?}
 {counter?}
 . ->* .
 (mutated/c mutated-program?))
Transforms a program mutator returned by make-program-mutator to strip the mutated wrapper from its results.

Examples:
> (define mutate-program/no-counter
    (without-counter (make-program-mutator (make-expr-mutator increment-integer-consts))))
> (mutate-program/no-counter #'[(provide x y)
                                (define x 5)
                                (define y (+ x 1))]
                             0)

(mutated-program

 #<syntax:eval:20:0 ((provide x y) (define x 6) (define y (+ x 1)))>

 'define)

> (mutate-program/no-counter #'[(provide x y)
                                (define x 5)
                                (define y (+ x 1))]
                             1)

(mutated-program

 #<syntax:eval:21:0 ((provide x y) (define x 5) (define y (+ x 2)))>

 'define)

procedure

(syntax-only program-mutator)

  ({syntax? mutation-index?} {counter?} . ->* . syntax?)
  program-mutator : 
({syntax? mutation-index?}
 {counter?}
 . ->* .
 (mutated/c mutated-program?))
Similar to without-counter, transforms a program mutator returned by make-program-mutator to strip both the mutated and mutated-program wrappers from its results, so that it produces only syntax.

procedure

(program-mutator->module-mutator program-mutator)

  ({syntax? mutation-index?} {counter?} . ->* . any/c)
  program-mutator : 
({syntax? mutation-index?}
 {counter?}
 . ->* .
 any/c)
Transforms a program mutator to mutate top level forms inside of a ‘module‘ form, rather than expecting the "program" to be directly a sequence of top level forms.

procedure

(program-mutator->stream-builder program-mutator)

  (syntax? . ->* . (stream/c any/c))
  program-mutator : 
({syntax? mutation-index?}
 {counter?}
 . ->* .
 any/c)
Transforms a program mutator to produce a stream of all possible mutants, ordered by mutation point, instead of returning a single mutant selected by a mutation index.

struct

(struct mutated-program (stx mutated-id)
    #:transparent)
  stx : syntax?
  mutated-id : any/c
The wrapper of mutated program syntax, returned by program mutators, which carries the identifier of the top level form mutated alongside the mutated program syntax.

contract

top-level-selector/c

 : 
(syntax? . -> . (or/c #f
                      (list/c (listof syntax?)
                              any/c
                              ((listof syntax?) . -> . syntax?))))
The contract for top-level selectors provided to make-program-mutator or build-mutation-engine.

A top-level selector is a function that controls which parts of top level forms are considered for mutation. Specifically, it is a function that, provided the syntax of a top level form, returns either
  • False, to indicate that the form should not be considered for mutation or traversal, or

  • A list of three things:
    • A listof of syntaxes to be considered for mutation and traversal. This may just be the whole top level form, or it may be sub-parts of it.

    • An identifier for this top level form.

    • A function to reconstruct the whole top level form corresponding to the input, given mutated versions of the syntaxes returned in the first value.

Examples:
> (require syntax/parse/lib/function-header)
> (define (select-define-body-only stx)
    (syntax-parse stx
      [({~datum define} {~or* plain-name:id sig:function-header} body ...)
       (list (attribute body)
             (or (attribute plain-name) (attribute sig.name))
             (λ (mutated-body-stxs) #`(define {~? plain-name sig} #,@mutated-body-stxs)))]
      [_ #f]))
> (define mutate-program
    (make-program-mutator (make-expr-mutator increment-integer-consts)
                          #:select select-define-body-only))
; 0 will not be considered because it is not in the body of a define
> (mutate-program #'[(provide x y)
                     (displayln 0)
                     (define x 5)
                     (define y (+ x 1))]
                  0)

(mutated

 (mutated-program

  #<syntax:eval:25:0 ((provide x y) (displayln 0) (define x 6) (define y (+ x 1)))>

  #<syntax:eval:25:0 x>)

 1)

> (mutate-program #'[(provide x y)
                     (displayln 0)
                     (define x 5)
                     (define y (+ x 1))]
                  1)

(mutated

 (mutated-program

  #<syntax:eval:26:0 ((provide x y) (displayln 0) (define x 5) (define y (+ x 2)))>

  #<syntax:eval:26:0 y>)

 2)

> (mutate-program #'[(provide x y)
                     (displayln 0)
                     (define x 5)
                     (define y (+ x 1))]
                  2)

#f

Some top level selectors for common cases.

select-all simply selects the entirety of all top level forms.

select-define-body selects the body of defines. In the case of the function shorthand, this selector makes the implicit begin explicitly visible in the body expression it returns (and then removes it again during reconstruction).

select-define/contract-body is like select-define-body but for define/contract.

select-any-define-named-form-body selects any top level form that starts with an identifier spelled with "define".

Examples:
> (select-define-body #'(define (f x) (do-something!) 42))

'((#<syntax:eval:1:0 (begin (do-something!) 42)>)

  f

  #<procedure:reconstruct-definition>)

> (select-any-define-named-form-body #'(my-fancy-define (f x) (do-something!) 42))

'((#<syntax:eval:2:0 (do-something!)> #<syntax:eval:2:0 42>)

  f

  #<procedure:reconstruct-definition>)

> (select-any-define-named-form-body #'(def (f x) (do-something!) 42))

#f

3.5 Logging: recovering the mutation type that causes a mutation🔗ℹ

 (require mutate/logger) package: mutate-lib

maybe-mutate logs a mutation message when it executes a mutation on the mutate-logger (topic mutate) at level info. The message has a data payload which is a list of three elements:
  • the mutator type of the mutator that caused the mutation

  • the original syntax

  • the mutated syntax

Since all mutators boil down to applications of maybe-mutate, the mutate-logger provides a channel to recover which mutator is used to mutate a program.

logger

mutate-logger : logger?