aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/poly/lux/abstract/functor.lux
blob: d68d55af8f370ba7a5891825646f2ad83e48b4d9 (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
(.module:
  [library
   [lux #*
    [abstract
     [monad (#+ Monad do)]]
    [control
     ["p" parser
      ["<.>" type]
      ["s" code (#+ Parser)]]]
    [data
     ["." product]
     ["." text
      ["%" format (#+ format)]]
     [collection
      ["." list ("#\." monad monoid)]]]
    [macro
     [syntax (#+ syntax:)]
     ["." code]]
    [math
     [number
      ["n" nat]]]
    ["." type
     ["." poly (#+ poly:)]]]]
  [\\library
   ["." /]])

(poly: .public functor
  (do {! p.monad}
    [.let [type_funcC (code.local_identifier "____________type_funcC")
           funcC (code.local_identifier "____________funcC")
           inputC (code.local_identifier "____________inputC")]
     *env* <type>.env
     inputT <type>.next
     [polyC varsC non_functorT] (<type>.local (list inputT)
                                              (<type>.polymorphic <type>.any))
     .let [num_vars (list.size varsC)]
     .let [@Functor (: (-> Type Code)
                       (function (_ unwrappedT)
                         (if (n.= 1 num_vars)
                           (` ((~! /.Functor) (~ (poly.code *env* unwrappedT))))
                           (let [paramsC (|> num_vars -- list.indices (list\map (|>> %.nat code.local_identifier)))]
                             (` (All [(~+ paramsC)]
                                  ((~! /.Functor) ((~ (poly.code *env* unwrappedT)) (~+ paramsC)))))))))
           Arg<?> (: (-> Code (<type>.Parser Code))
                     (function (Arg<?> valueC)
                       ($_ p.either
                           ... Type-var
                           (do p.monad
                             [.let [varI (|> num_vars (n.* 2) --)]
                              _ (<type>.parameter! varI)]
                             (in (` ((~ funcC) (~ valueC)))))
                           ... Variants
                           (do !
                             [_ (in [])
                              membersC (<type>.variant (p.many (Arg<?> valueC)))
                              .let [last (-- (list.size membersC))]]
                             (in (` (case (~ valueC)
                                      (~+ (list\join (list\map (function (_ [tag memberC])
                                                                 (if (n.= last tag)
                                                                   (list (` ((~ (code.nat (-- tag))) #1 (~ valueC)))
                                                                         (` ((~ (code.nat (-- tag))) #1 (~ memberC))))
                                                                   (list (` ((~ (code.nat tag)) #0 (~ valueC)))
                                                                         (` ((~ (code.nat tag)) #0 (~ memberC))))))
                                                               (list.enumeration membersC))))))))
                           ... Tuples
                           (do p.monad
                             [pairsCC (: (<type>.Parser (List [Code Code]))
                                         (<type>.tuple (loop [idx 0
                                                              pairsCC (: (List [Code Code])
                                                                         (list))]
                                                         (p.either (let [slotC (|> idx %.nat (format "____________slot") code.local_identifier)]
                                                                     (do !
                                                                       [_ (in [])
                                                                        memberC (Arg<?> slotC)]
                                                                       (recur (++ idx)
                                                                              (list\compose pairsCC (list [slotC memberC])))))
                                                                   (in pairsCC)))))]
                             (in (` (case (~ valueC)
                                      [(~+ (list\map product.left pairsCC))]
                                      [(~+ (list\map product.right pairsCC))]))))
                           ... Functions
                           (do !
                             [_ (in [])
                              .let [g! (code.local_identifier "____________")
                                    outL (code.local_identifier "____________outL")]
                              [inT+ outC] (<type>.function (p.many <type>.any)
                                            (Arg<?> outL))
                              .let [inC+ (|> (list.size inT+)
                                             list.indices
                                             (list\map (|>> %.nat (format "____________inC") code.local_identifier)))]]
                             (in (` (function ((~ g!) (~+ inC+))
                                      (let [(~ outL) ((~ valueC) (~+ inC+))]
                                        (~ outC))))))
                           ... Recursion
                           (do p.monad
                             [_ <type>.recursive_call]
                             (in (` ((~' map) (~ funcC) (~ valueC)))))
                           ... Parameters
                           (do p.monad
                             [_ <type>.any]
                             (in valueC))
                           )))]
     [_ _ outputC] (: (<type>.Parser [Code (List Code) Code])
                      (p.either (<type>.polymorphic
                                 (Arg<?> inputC))
                                (p.failure (format "Cannot create Functor for: " (%.type inputT)))))]
    (in (` (: (~ (@Functor inputT))
              (implementation
               (def: ((~' map) (~ funcC) (~ inputC))
                 (~ outputC))))))))