www

Unnamed repository; edit this file 'description' to name the repository.
Log | Files | Refs | README

phc-adt-constructor.scrbl (13924B)


      1 #lang scribble/manual
      2 
      3 @(require racket/require
      4           (for-label (except-in (subtract-in typed/racket/base type-expander)
      5                                 values)
      6                      type-expander
      7                      phc-adt
      8                      xlist
      9                      (lib "phc-adt/tagged.hl.rkt")
     10                      (lib "phc-adt/structure.hl.rkt")
     11                      (lib "phc-adt/constructor.hl.rkt")
     12                      (lib "phc-adt/variant.hl.rkt")
     13                      (lib "phc-adt/tagged-supertype.hl.rkt"))
     14           scribble-enhanced/doc
     15           scribble-math
     16           (subtract-in scribble/struct scribble-enhanced/doc)
     17           scribble/decode)
     18 @doc-lib-setup
     19 
     20 @title{Constructors}
     21 
     22 @deftech{Constructors} are implemented as tagged structures, using a
     23 single special field: @racket[values]. The @racket[constructor] identifier and
     24 its derivatives therefore call @racket[tagged], using that single field. The
     25 identifiers described within this section provide some syntactic sugar,
     26 allowing constructors to contain more than one value. These values are wrapped
     27 in a (possibly improper) list which is stored within the tagged structure's
     28 @racket[values] field.
     29 
     30 
     31 @defform*[#:kind "type-expander"
     32           [(constructor tag-name maybe-∀ τᵢ ...)
     33            (constructor tag-name maybe-∀ τᵢ ... . dotted-τ-rest)
     34            (constructor tag-name maybe-∀ τᵢ ... #:rest τ-rest)]
     35           #:grammar
     36           [(tag-name Identifier)
     37            (maybe-∀ (code:line)
     38                     (code:line #:∀ (tvarⱼ ...)))
     39            (τᵢ xlist-type-or-repeated-type)
     40            (τ-rest xlist-type-or-repeated-type)
     41            (dotted-τ-rest #,"like τ-rest, but must not be a syntax pair")]]{
     42 
     43  Expands to the type for a constructor with the given tag name and type of
     44  contents. The @racket[(τᵢ ...)], @racket[(τᵢ ... . dotted-τ-rest)] or
     45  @racket[(τᵢ ... #:rest τ-rest)] sequence is passed unmodified to
     46  @racket[xlist]. Therefore, depending on the syntax used, the expanded type is
     47  equivalent to one of the following types:
     48 
     49  @racketblock[
     50  (tagged tag-name maybe-∀ [values (xlist τᵢ ...)])
     51  (tagged tag-name maybe-∀ [values (xlist τᵢ ... . dotted-τ-rest)])
     52  (tagged tag-name maybe-∀ [values (xlist τᵢ ... #:rest τ-rest)])]
     53 
     54  The elements may appear in any order, as long as the tag name appears before
     55  any element type, and as long as the element types form a contiguous
     56  sequence.}
     57 
     58 @defform*[#:kind "syntax"
     59           #:link-target? #f
     60           #:literals (* : ! ::)
     61           [(constructor maybe-∀ tag-name *)
     62            (constructor maybe-∀ tag-name : typeᵢ ...)
     63            (constructor maybe-∀ tag-name ! . xlist-types)
     64            (constructor maybe-∀ tag-name :: . xlist-types)]
     65           #:grammar
     66           [(maybe-∀ (code:line)
     67                     (code:line #:∀ (tvarⱼ ...)))
     68            (tag-name Identifier)
     69            (xlist-types (τᵢ ...)
     70                         (τᵢ ... . dotted-τ-rest)
     71                         (τᵢ ... #:rest τ-rest))
     72            (τᵢ xlist-type-or-repeated-type)
     73            (typeᵢ Type)]]{
     74  Expands to a builder function for a constructor with the given tag name and
     75  type of contents.
     76 
     77  The first syntax, using @racket[*] and no types, produces a polymorphic
     78  builder function which accepts any number of arguments, infers their types,
     79  and uses the whole list of arguments as the constructor's value.
     80 
     81  In the following three cases, when @racket[#:∀ (tvarⱼ ...)] is specified, a
     82  polymorphic builder with the @racket[tvarⱼ] type variables is produced.
     83 
     84  The second syntax, using @racket[:] followed by a sequence of regular types,
     85  produces a builder function with one argument per type. The builder function
     86  aggregates all its arguments in a list, and uses that list as the
     87  constructor's value.
     88 
     89  The second syntax, using @racket[!] followed by a sequence of types valid for
     90  @racket[xlist], produces a builder function which accepts a variable number of
     91  arguments. The builder function @racket[cast]s the whole list of arguments to
     92  the type @racket[(xlist . xlist-types)], which must therefore be a suitable
     93  argument to @racket[make-predicate]. The cast list is used as the
     94  constructor's value.
     95 
     96  The third syntax, using @racket[::] followed by a sequence of types valid for
     97  @racket[xlist], produces a builder function which accepts a single value of
     98  type @racket[(xlist . xlist-typed)], and uses that value as the constructor's
     99  value.
    100 
    101  Usually, the value stored within a constructor will be a list (i.e. a tuple
    102  in other languages), but it is possible to store a single value using
    103  @racket[xlist]'s rest syntax:
    104 
    105  @racketblock[
    106  ((constructor #:∀ (A) tag-name :: . A) 123)
    107  ((constructor tag-name :: . Number) 123)
    108  ((constructor tag-name :: #:rest (Vector Number String)) #(123 "abc"))]
    109 
    110  The elements may appear in any order, as long as the tag name appears before
    111  any element type, and as long as the element types form a contiguous
    112  sequence.}
    113 
    114 @defform*[#:kind "syntax"
    115           #:link-target? #f
    116           #:literals (:)
    117           [(constructor maybe-∀ tag-name value-maybe-typeᵢ)
    118            (constructor maybe-∀ tag-name value-maybe-typeᵢ . dotted-rest)
    119            (constructor maybe-∀ tag-name value-maybe-typeᵢ #:rest rest)]
    120           #:grammar
    121           [(maybe-∀ (code:line)
    122                     (code:line #:∀ (tvarⱼ ...)))
    123            (tag-name Identifier)
    124            (value-maybe-typeᵢ valueᵢ
    125                               [valueᵢ : typeᵢ]
    126                               [: typeᵢ valueᵢ])
    127            (rest value-maybe-typeᵢ)
    128            (dotted-rest #,"like rest, but must not be a syntax pair")]]{
    129 
    130  Expands to an instance of a constructor containing the given values, grouped
    131  inside a list.
    132 
    133  When a @racket[typeᵢ] is specified, it is used to annotate the value, and is
    134  used as the type for that element in the resulting constructor type.
    135 
    136  When @racket[#:∀ (tvarⱼ ...)] is specified, the type of values annotated with
    137  @racket[tvarⱼ] is inferred, and an instance of a polymorphic constructor is
    138  produced. A @racket[tvarⱼ] can be used within a more complex type, in which
    139  case only that part of the type is inferred.
    140 
    141  The elements may appear in any order, as long as the tag name appears before
    142  any value, and as long as the values form a contiguous sequence, including the
    143  @racket[#:rest rest] which must appear immediately after the sequence of
    144  values, if specified. The @racket[dotted-rest], on the other hand, can be
    145  separated from the other values, so
    146  @racket[(constructor foo 1 [2 : A] 3 #:∀ (A) . 4)] is a valid (but awkward)
    147  use of @racket[constructor].
    148 
    149  The type of the @racket[dotted-rest] can still be specified using
    150  @racket[typed/racket]'s reader abbreviation for @racket[ann], namely
    151  @racket[#{dotted-rest :: type}].}
    152 
    153 @defform*[#:kind "match expander"
    154           #:link-target? #f
    155           #:literals (* : ! ::)
    156           [(constructor tag-name . xlist-pats)]
    157           #:grammar
    158           [(tag-name Identifier)
    159            (xlist-pats (patᵢ ...)
    160                        (patᵢ ... . dotted-pat-rest)
    161                        (patᵢ ... #:rest pat-rest))
    162            (patᵢ XList-Match-Pattern)]]{
    163                                         
    164  Expands to a match pattern which checks whether the value is a constructor
    165  with the given tag name, and then matches the constructor's value against the
    166  match pattern @racket[(xlist . xlist-pats)]. The @racket[xlist] match expander
    167  in turn matches each element of a (possibly improper) list against the given
    168  patterns, and supports various means of specifying fixed-length, bounded and
    169  unbounded repetitions like "must appear between three and five times". See the
    170  documentation for the @racket[xlist] match expander for more details.}
    171 
    172 @defform[#:kind "syntax"
    173          #:literals (* : ! ::)
    174          (constructor? tag-name . xlist-types)
    175          #:grammar
    176          [(tag-name Identifier)
    177           (xlist-types (τᵢ ...)
    178                        (τᵢ ... . dotted-τ-rest)
    179                        (τᵢ ... #:rest τ-rest))
    180           (τᵢ xlist-type-or-repeated-type)
    181           (τ-rest xlist-type-or-repeated-type)
    182           (dotted-τ-rest #,"like τ-rest, but must not be a syntax pair")]]{
    183  Expands to a predicate which returns true if and only if the following
    184  conditions are met:
    185  @itemlist[
    186  @item{The value is a constructor with the given tag name (i.e. a tagged
    187    structure with the given tag name and a single field named @racket[values],
    188    so nodes and untagged structures with a single field named @racket[values]
    189    are accepted too)}
    190  @item{The constructor's value (i.e. the contents of its @racket[values]
    191    field) is accepted by @racket[(make-predicate (xList . xlist-types))]}]}
    192 
    193 @defform[(define-constructor name maybe-tag maybe-pred? maybe-∀ . type-spec)
    194          #:grammar
    195          [(name Identifier)
    196           (maybe-∀ (code:line)
    197                    (code:line #:∀ (tvarⱼ ...)))
    198           (maybe-tag (code:line)
    199                           (code:line #:tag tag-name))
    200           (tag-name Identifier)
    201           (maybe-pred? (code:line)
    202                             (code:line #:? predicate-name?))
    203           (predicate-name? Identifier)
    204           (types-spec (: typeᵢ ...)
    205                       (! . xlist-types)
    206                       (:: . xlist-types))
    207           (xlist-types (τᵢ ...)
    208                        (τᵢ ... . dotted-τ-rest)
    209                        (τᵢ ... #:rest τ-rest))
    210           (τᵢ xlist-type-or-repeated-type)
    211           (τ-rest xlist-type-or-repeated-type)
    212           (dotted-τ-rest #,"like τ-rest, but must not be a syntax pair")
    213           (typeᵢ Type)]]{
    214  Defines @racket[name] as a shorthand for the type expander, match expander,
    215  builder function and predicate for a constructor with given
    216  @racket[tag-name] and content types.
    217 
    218  When @racket[#:tag tag-name] is omitted, it defaults to @racket[name].
    219 
    220  The predicate is bound to @racket[predicate-name?]; When
    221  @racket[#:? predicate-name?] is omitted, it defaults to @racket[_name?], which
    222  is an identifier with the same lexical context as @racket[name], with a
    223  @racket["?"] appended at the end.
    224 
    225  The @racket[_name] and @racket[_predicate?] identifiers behave as follows:
    226 
    227  @(make-blockquote
    228    "leftindent"
    229    (flow-paragraphs
    230     (decode-flow
    231      (splice-run
    232       @defidform[#:kind "type expander"
    233                  #:link-target? #f
    234                  _name]{
    235   Expands to the same type as @racket[(constructor tag-name typeᵢ ...)] or
    236   @racket[(constructor tag-name . xlist-types)] would.}))))
    237 
    238  @(make-blockquote
    239    "leftindent"
    240    (flow-paragraphs
    241     (decode-flow
    242      (splice-run
    243       @defidform[#:link-target? #f _name]{
    244   Expands to the same builder function as
    245   @racket[(constructor tag-name types-spec)] would. The use of @racket[:],
    246   @racket[!] or @racket[::] before the sequence of types therefore specifies
    247   whether the builder function accepts a simple fixed number of arguments, a
    248   variable number of arguments (performing a cast), or a single argument used as
    249   the whole value for the constructor.}))))
    250 
    251  @(make-blockquote
    252    "leftindent"
    253    (flow-paragraphs
    254     (decode-flow
    255      (splice-run
    256       @defform[#:kind "match expander"
    257                #:link-target? #f
    258                (_name patᵢ ...)]{
    259                                  
    260   When using the @racket[: typeᵢ ...] form of @racket[define-constructor], the
    261   defined match expander expects one pattern @racket[patᵢ] per type. The
    262   resulting match pattern verifies that the value is a constructor with the
    263   given @racket[tag-name] containing a list with the correct number of elements,
    264   and matches each element against the corresponding @racket[patᵢ].
    265 
    266   When using the @racket[(! . xlist-types)] or @racket[(:: . xlist-types)]
    267   forms of @racket[define-constructor], the defined match expander expects one
    268   pattern per (possibly repeated) xlist type. The resulting match pattern
    269   verifies that the value is a constructor with the given @racket[tag-name]
    270   containing a value accepted by
    271   @racket[(make-predicate (xlist . xlist-types))]. It then uses the
    272   @racket[split-xlist] match expander, which splits the list into one sublist
    273   per repeated xlist type (and a single item for each non-repeated xlist type),
    274   and matches each sublist or single item against the corresponding
    275   @racket[patᵢ]. See the documentation for @racket[split-xlist] for more details
    276   about this process. The resulting match pattern is therefore equivalent to:
    277 
    278   @racketblock[(and (tagged? tag-name values)
    279                     (? (make-predicate (xlist . xlist-types)))
    280                     (split-xlist [patᵢ ...] . xlist-types))]}))))
    281 
    282  @(make-blockquote
    283    "leftindent"
    284    (flow-paragraphs
    285     (decode-flow
    286      (splice-run
    287       @defidform[#:link-target? #f _predicate?]{
    288   Expands to the same predicate as
    289   
    290   @racketblock[(constructor? tag-name (xlist τᵢ … . τ-rest))]
    291 
    292   would, where all occurrences of @racket[tvarⱼ] type variables are replaced
    293   with @racket[Any].}))))
    294 
    295  The elements of the grammar for @racket[define-tagged] may appear in any
    296  order, as long as the tag name appears before any field descriptor, and as
    297  long as the field descriptors form a contiguous sequence.}
    298 
    299 @defidform[#:kind "type"
    300            ConstructorTop]{ The supertype of all @tech{constructors},
    301  including @tech{tagged structures}, @tech{untagged structures} and @tech{
    302   nodes} which only contain a single @racket[values] field.}
    303 
    304 @defproc[(ConstructorTop? [v Any]) Boolean]{
    305  A predicate for @racket[ConstructorTop]. It accepts all @tech{constructors},
    306  including @tech{tagged structures}, @tech{untagged structures} and @tech{
    307   nodes} which contain a single @racket[values] field, and rejects any other
    308  value.}
    309 
    310 @defproc[(constructor-values [v ConstructorTop]) T]{
    311  Returns the value stored within the constructor.}