aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/data/collection/dictionary/plist.lux
blob: 5417fca5d5d9e6937a6a2b1e0969dc83c9c829d1 (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
(.using
 [library
  [lux {"-" has revised}
   [abstract
    [equivalence {"+" Equivalence}]
    [monoid {"+" Monoid}]]
   [control
    ["[0]" maybe ("[1]#[0]" functor)]]
   [data
    ["[0]" product]
    ["[0]" text ("[1]#[0]" equivalence)]
    [collection
     ["[0]" list ("[1]#[0]" functor mix)]]]
   [math
    [number
     ["n" nat]]]]])

... https://en.wikipedia.org/wiki/Property_list
(type: .public (PList a)
  (List [Text a]))

(def: .public empty
  PList
  {.#End})

(def: .public size
  (All (_ a) (-> (PList a) Nat))
  list.size)

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

(def: .public (value key properties)
  (All (_ a) (-> Text (PList a) (Maybe a)))
  (case properties
    {.#End}
    {.#None}

    {.#Item [k' v'] properties'}
    (if (text#= key k')
      {.#Some v'}
      (value key properties'))))

(template [<name> <type> <access>]
  [(def: .public <name>
     (All (_ a) (-> (PList a) (List <type>)))
     (list#each <access>))]

  [keys   Text product.left]
  [values a    product.right]
  )

(def: .public (contains? key properties)
  (All (_ a) (-> Text (PList a) Bit))
  (case (..value key properties)
    {.#Some _}
    true

    {.#None}
    false))

(def: .public (has key val properties)
  (All (_ a) (-> Text a (PList a) (PList a)))
  (case properties
    {.#End}
    (list [key val])

    {.#Item [k' v'] properties'}
    (if (text#= key k')
      {.#Item [key val]
              properties'}
      {.#Item [k' v']
              (has key val properties')})))

(def: .public (revised key f properties)
  (All (_ a) (-> Text (-> a a) (PList a) (PList a)))
  (case properties
    {.#End}
    {.#End}

    {.#Item [k' v'] properties'}
    (if (text#= key k')
      {.#Item [k' (f v')] properties'}
      {.#Item [k' v'] (revised key f properties')})))

(def: .public (lacks key properties)
  (All (_ a) (-> Text (PList a) (PList a)))
  (case properties
    {.#End}
    properties

    {.#Item [k' v'] properties'}
    (if (text#= key k')
      properties'
      {.#Item [k' v']
              (lacks key properties')})))

(implementation: .public (equivalence (^open "/#[0]"))
  (All (_ a) (-> (Equivalence a) (Equivalence (PList a))))

  (def: (= reference subject)
    (and (n.= (list.size reference)
              (list.size subject))
         (list.every? (function (_ [key val])
                        (|> reference
                            (..value key)
                            (maybe#each (/#= val))
                            (maybe.else false)))
                      subject))))

(implementation: .public monoid
  (All (_ a) (Monoid (PList a)))

  (def: identity
    ..empty)

  (def: (composite left right)
    (list#mix (function (_ [key val] it)
                (..has key val it))
              right
              left)))