aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/documentation/lux/type/abstract.lux
blob: b1a945167662f67526a7ab51e30dc16e1329a368 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
(.module:
  [library
   [lux {"-" [and]}
    ["$" documentation {"+" [documentation:]}]
    [control
     ["<>" parser
      ["<[0]>" code]]]
    [data
     ["[0]" text {"+" [\n]}
      ["%" format {"+" [format]}]]]
    [macro
     ["[0]" template]]]]
  [\\library
   ["[0]" /]])

(documentation: /.Frame
  "Meta-data about an abstract/nominal type in a stack of them.")

(documentation: /.current
  "The currently-being-defined abstract/nominal type.")

(documentation: /.specific
  "A specific abstract/nominal type still being defined somewhere in the scope."
  [(specific name)])

(template [<name> <from> <to>]
  [(documentation: <name>
     "Type-casting macro for abstract/nominal types."
     [(|> value
          (: Representation)
          :abstraction
          (: Abstraction)
          :representation
          (: Representation))])]

  [/.:abstraction representation abstraction]
  [/.:representation abstraction representation]
  )

(documentation: /.abstract:
  (format "Define abstract/nominal types which hide their representation details."
          \n "You can convert between the abstraction and its representation selectively to access the value, while hiding it from others.")
  [(abstract: String
     Text

     [(def: (string value)
        (-> Text String)
        (:abstraction value))

      (def: (text value)
        (-> String Text)
        (:representation value))])]
  ["Type-parameters are optional."
   (abstract: (Duplicate a)
     [a a]

     [(def: (duplicate value)
        (All (_ a) (-> a (Duplicate a)))
        (:abstraction [value value]))])]
  ["Definitions can be nested."
   (abstract: (Single a)
     a

     [(def: (single value)
        (All (_ a) (-> a (Single a)))
        (:abstraction value))

      (abstract: (Double a)
        [a a]

        [(def: (double value)
           (All (_ a) (-> a (Double a)))
           (:abstraction [value value]))

         (def: (single' value)
           (All (_ a) (-> a (Single a)))
           (:abstraction Single [value value]))

         (let [value 0123]
           (same? value
                  (|> value
                      single'
                      (:representation Single)
                      double
                      :representation)))])])]
  ["Type-parameters do not necessarily have to be used in the representation type."
   "If they are not used, they become phantom types and can be used to customize types without changing the representation."
   (abstract: (JavaScript a)
     Text

     [(abstract: Expression Any [])
      (abstract: Statement Any [])

      (def: (+ x y)
        (-> (JavaScript Expression) (JavaScript Expression) (JavaScript Expression))
        (:abstraction
         (format "(" (:representation x) "+" (:representation y) ")")))

      (def: (while test body)
        (-> (JavaScript Expression) (JavaScript Statement) (JavaScript Statement))
        (:abstraction
         (format "while(" (:representation test) ") {"
                 (:representation body)
                 "}")))])])

(documentation: /.:transmutation
  "Transmutes an abstract/nominal type's phantom types."
  [(abstract: (JavaScript a)
     Text

     [(abstract: Expression Any [])
      (abstract: Statement Any [])

      (def: (statement expression)
        (-> (JavaScript Expression) (JavaScript Statement))
        (:transmutation expression))

      (def: (statement' expression)
        (-> (JavaScript Expression) (JavaScript Statement))
        (:transmutation JavaScript expression))])])

(documentation: /.^:representation
  "Pattern-matching macro to easily extract a representation."
  [(def: (computation abstraction)
     (All (_ a) (-> (Abstract a) ???))
     (let [(^:representation value) abstraction]
       (foo (bar (baz value)))))])

(.def: .public documentation
  (.List $.Module)
  ($.module /._
            ""
            [..Frame
             ..current
             ..specific
             ..:abstraction
             ..:representation
             ..abstract:
             ..:transmutation
             ..^:representation
             ($.default /.no_active_frames)]
            []))