aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/data/collection/set/multi.lux
blob: b325c793a35c1f3525decd09207bc3543c59f75c (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
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
... https://en.wikipedia.org/wiki/Multiset
(.module:
  [library
   [lux {"-" [list]}
    [abstract
     [equivalence {"+" [Equivalence]}]
     [hash {"+" [Hash]}]]
    [control
     ["[0]" function]
     ["[0]" maybe]]
    [math
     [number
      ["n" nat]]]
    [type
     [abstract {"+" [abstract: :abstraction :representation ^:representation]}]]]]
  ["[0]" //
   [//
    ["[0]" list ("[1]\[0]" mix monoid)]
    ["[0]" dictionary {"+" [Dictionary]}]]])

(abstract: .public (Set a)
  (Dictionary a Nat)

  (def: .public empty
    (All (_ a) (-> (Hash a) (Set a)))
    (|>> dictionary.empty :abstraction))

  (def: .public size
    (All (_ a) (-> (Set a) Nat))
    (|>> :representation dictionary.values (list\mix n.+ 0)))

  (def: .public (has multiplicity elem set)
    (All (_ a) (-> Nat a (Set a) (Set a)))
    (case multiplicity
      0 set
      _ (|> set
            :representation
            (dictionary.revised' elem 0 (n.+ multiplicity))
            :abstraction)))

  (def: .public (lacks multiplicity elem set)
    (All (_ a) (-> Nat a (Set a) (Set a)))
    (case multiplicity
      0 set
      _ (case (dictionary.value elem (:representation set))
          {.#Some current}
          (:abstraction
           (if (n.> multiplicity current)
             (dictionary.revised elem (n.- multiplicity) (:representation set))
             (dictionary.lacks elem (:representation set))))
          
          {.#None}
          set)))

  (def: .public (multiplicity set elem)
    (All (_ a) (-> (Set a) a Nat))
    (|> set :representation (dictionary.value elem) (maybe.else 0)))

  (def: .public list
    (All (_ a) (-> (Set a) (List a)))
    (|>> :representation
         dictionary.entries
         (list\mix (function (_ [elem multiplicity] output)
                     (list\composite (list.repeated multiplicity elem) output))
                   {.#End})))

  (template [<name> <composite>]
    [(def: .public (<name> parameter subject)
       (All (_ a) (-> (Set a) (Set a) (Set a)))
       (:abstraction (dictionary.merged_with <composite> (:representation parameter) (:representation subject))))]

    [union n.max]
    [sum n.+]
    )

  (def: .public (intersection parameter (^:representation subject))
    (All (_ a) (-> (Set a) (Set a) (Set a)))
    (list\mix (function (_ [elem multiplicity] output)
                (..has (n.min (..multiplicity parameter elem)
                              multiplicity)
                       elem
                       output))
              (..empty (dictionary.key_hash subject))
              (dictionary.entries subject)))

  (def: .public (difference parameter subject)
    (All (_ a) (-> (Set a) (Set a) (Set a)))
    (|> parameter
        :representation
        dictionary.entries
        (list\mix (function (_ [elem multiplicity] output)
                    (..lacks multiplicity elem output))
                  subject)))

  (def: .public (sub? reference subject)
    (All (_ a) (-> (Set a) (Set a) Bit))
    (|> subject
        :representation
        dictionary.entries
        (list.every? (function (_ [elem multiplicity])
                       (|> elem
                           (..multiplicity reference)
                           (n.>= multiplicity))))))

  (def: .public (support set)
    (All (_ a) (-> (Set a) (//.Set a)))
    (let [(^@ set [hash _]) (:representation set)]
      (|> set
          dictionary.keys
          (//.of_list hash))))

  (implementation: .public equivalence
    (All (_ a) (Equivalence (Set a)))
    
    (def: (= (^:representation reference) sample)
      (and (n.= (dictionary.size reference)
                (dictionary.size (:representation sample)))
           (|> reference
               dictionary.entries
               (list.every? (function (_ [elem multiplicity])
                              (|> elem
                                  (..multiplicity sample)
                                  (n.= multiplicity))))))))

  (implementation: .public hash
    (All (_ a) (Hash (Set a)))
    
    (def: &equivalence ..equivalence)
    
    (def: (hash (^:representation set))
      (let [[hash _] set]
        (list\mix (function (_ [elem multiplicity] acc)
                    (|> elem (\ hash hash) (n.* multiplicity) (n.+ acc)))
                  0
                  (dictionary.entries set)))))
  )

(def: .public (member? set elem)
  (All (_ a) (-> (Set a) a Bit))
  (|> elem (..multiplicity set) (n.> 0)))

(def: .public empty?
  (All (_ a) (-> (Set a) Bit))
  (|>> ..size (n.= 0)))

(def: .public (of_list hash subject)
  (All (_ a) (-> (Hash a) (List a) (Set a)))
  (list\mix (..has 1) (..empty hash) subject))

(def: .public (of_set subject)
  (All (_ a) (-> (//.Set a) (Set a)))
  (..of_list (//.member_hash subject)
             (//.list subject)))

(def: .public super?
  (All (_ a) (-> (Set a) (Set a) Bit))
  (function.flipped sub?))