Skip to content

Commit 3c5596f

Browse files
author
Alex Gryzlov
committed
WIP Maps
1 parent 9593c18 commit 3c5596f

File tree

1 file changed

+77
-82
lines changed

1 file changed

+77
-82
lines changed

src/Maps.lidr

Lines changed: 77 additions & 82 deletions
Original file line numberDiff line numberDiff line change
@@ -85,8 +85,8 @@ about strings:
8585
> bfro {x=MkId n1} {y=MkId n2} prf with (decEq n1 n2)
8686
> bfro _ | (Yes _) = Refl
8787
> bfro prf | (No contra) = absurd $ contra $ idInj prf
88-
> where
89-
> idInj : MkId x = MkId y -> x = y
88+
> where
89+
> idInj : MkId x = MkId y -> x = y
9090
> idInj Refl = Refl
9191

9292
> beq_id_true_iff : (beq_id x y = True) <-> x = y
@@ -107,9 +107,9 @@ Similarly:
107107
> beq_id_false_iff = (to, fro)
108108
> where
109109
> to : (beq_id x y = False) -> Not (x = y)
110-
> to beqf = not_true_and_false beqf . bfro
110+
> to beqf = not_true_and_false beqf . bfro
111111
> fro : (Not (x = y)) -> beq_id x y = False
112-
> fro noteq = not_true_is_false $ noteq . bto
112+
> fro noteq = not_true_is_false $ noteq . bto
113113

114114

115115
== Total Maps
@@ -128,7 +128,7 @@ simplifies proofs that use maps.
128128
We build partial maps in two steps. First, we define a type of _total maps_ that
129129
return a default value when we look up a key that is not present in the map.
130130

131-
> total_map : Type -> Type
131+
> total_map : Type -> Type
132132
> total_map a = Id -> a
133133

134134
Intuitively, a total map over an element type \idr{a} is just a function that
@@ -158,8 +158,8 @@ this:
158158
\todo[inline]{Seems like an inconsistency in the book here}
159159

160160
> examplemap : total_map Bool
161-
> examplemap = t_update (MkId "foo") False $
162-
> t_update (MkId "bar") True $
161+
> examplemap = t_update (MkId "foo") False $
162+
> t_update (MkId "bar") True $
163163
> t_empty False
164164

165165
This completes the definition of total maps. Note that we don't need to define a
@@ -195,132 +195,127 @@ $\square$
195195

196196
==== Exercise: 2 stars, optional (t_update_eq)
197197

198-
Next, if we update a map \idr{m} at a key \idr{x} with a new value v and then
199-
look up x in the map resulting from the update, we get back v:
198+
Next, if we update a map \idr{m} at a key \idr{x} with a new value \idr{v} and
199+
then look up \idr{x} in the map resulting from the \idr{update}, we get back
200+
\idr{v}:
201+
202+
> t_update_eq : (t_update x v m) x = v
203+
> t_update_eq = ?t_update_eq_rhs
200204

201-
Lemma t_update_eq : ∀A (m: total_map A) x v,
202-
(t_update m x v) x = v.
203-
Proof.
204-
(* FILL IN HERE *) Admitted.
205205
$\square$
206206

207207

208208
==== Exercise: 2 stars, optional (t_update_neq)
209209

210-
On the other hand, if we update a map m at a key x1 and then look up a different
211-
key x2 in the resulting map, we get the same result that m would have given:
210+
On the other hand, if we update a map \idr{m} at a key \idr{x1} and then look up
211+
a different key \idr{x2} in the resulting map, we get the same result that
212+
\idr{m} would have given:
213+
214+
> t_update_neq : Not (x1 = x2) -> (t_update x1 v m) x2 = m x2
215+
> t_update_neq x = ?t_update_neq_rhs
212216

213-
Theorem t_update_neq : ∀(X:Type) v x1 x2
214-
(m : total_map X),
215-
x1 ≠ x2 →
216-
(t_update m x1 v) x2 = m x2.
217-
Proof.
218-
(* FILL IN HERE *) Admitted.
219217
$\square$
220218

221219

222220
==== Exercise: 2 stars, optional (t_update_shadow)
223221

224-
If we update a map m at a key x with a value v1 and then update again with the
225-
same key x and another value v2, the resulting map behaves the same (gives the
226-
same result when applied to any key) as the simpler map obtained by performing
227-
just the second update on m:
222+
If we update a map \idr{m} at a key \idr{x} with a value \idr{v1} and then
223+
update again with the same key \idr{x} and another value \idr{v2}, the resulting
224+
map behaves the same (gives the same result when applied to any key) as the
225+
simpler map obtained by performing just the second \idr{update} on \idr{m}:
228226

229-
Lemma t_update_shadow : ∀A (m: total_map A) v1 v2 x,
230-
t_update (t_update m x v1) x v2
231-
= t_update m x v2.
232-
Proof.
233-
(* FILL IN HERE *) Admitted.
227+
> t_update_shadow : t_update x v2 $ t_update x v1 m = t_update x v2 m
228+
> t_update_shadow = ?t_update_shadow_rhs
234229

235230
$\square$
236231

237232
For the final two lemmas about total maps, it's convenient to use the reflection
238-
idioms introduced in chapter IndProp. We begin by proving a fundamental
239-
reflection lemma relating the equality proposition on ids with the boolean
240-
function beq_id.
233+
idioms introduced in chapter `IndProp`. We begin by proving a fundamental
234+
_reflection lemma_ relating the equality proposition on \idr{Id}s with the
235+
boolean function \idr{beq_id}.
241236

242237

243238
==== Exercise: 2 stars, optional (beq_idP)
244239

245-
Use the proof of beq_natP in chapter IndProp as a template to prove the following:
240+
Use the proof of \idr{beq_natP} in chapter `IndProp` as a template to prove the
241+
following:
242+
243+
> data Reflect : Type -> Bool -> Type where
244+
> ReflectT : (p : Type) -> Reflect p True
245+
> ReflectF : (p : Type) -> (Not p) -> Reflect p False
246246

247-
Lemma beq_idP : ∀x y, reflect (x = y) (beq_id x y).
248-
Proof.
249-
(* FILL IN HERE *) Admitted.
247+
> beq_idP : Reflect (x = y) (beq_id x y)
248+
> beq_idP = ?beq_idP_rhs
250249

251250
$\square$
252251

253-
Now, given ids x1 and x2, we can use the destruct (beq_idP x1 x2) to
254-
simultaneously perform case analysis on the result of beq_id x1 x2 and generate
255-
hypotheses about the equality (in the sense of =) of x1 and x2.
252+
Now, given \idr{Id}s \idr{x1} and \idr{x2}, we can use \idr{with (beq_idP x1
253+
x2)} to simultaneously perform case analysis on the result of \idr{beq_id x1 x2}
254+
and generate hypotheses about the equality (in the sense of \idr{=}) of \idr{x1}
255+
and \idr{x2}.
256256

257257

258258
==== Exercise: 2 stars (t_update_same)
259259

260-
With the example in chapter IndProp as a template, use beq_idP to prove the
261-
following theorem, which states that if we update a map to assign key x the same
262-
value as it already has in m, then the result is equal to m:
260+
With the example in chapter `IndProp` as a template, use \idr{beq_idP} to prove
261+
the following theorem, which states that if we update a map to assign key
262+
\idr{x} the same value as it already has in \idr{m}, then the result is equal to
263+
\idr{m}:
263264

264-
Theorem t_update_same : ∀X x (m : total_map X),
265-
t_update m x (m x) = m.
266-
Proof.
267-
(* FILL IN HERE *) Admitted.
265+
> t_update_same : t_update x (m x) m = m
266+
> t_update_same = ?t_update_same_rhs
268267

269268
$\square$
270269

271270

272271
==== Exercise: 3 stars, recommended (t_update_permute)
273272

274-
Use beq_idP to prove one final property of the update function: If we update a
275-
map m at two distinct keys, it doesn't matter in which order we do the updates.
273+
Use \idr{beq_idP} to prove one final property of the \idr{update} function: If
274+
we update a map \idr{m} at two distinct keys, it doesn't matter in which order
275+
we do the updates.
276276

277-
Theorem t_update_permute : ∀(X:Type) v1 v2 x1 x2
278-
(m : total_map X),
279-
x2 ≠ x1 →
280-
(t_update (t_update m x2 v2) x1 v1)
281-
= (t_update (t_update m x1 v1) x2 v2).
282-
Proof.
283-
(* FILL IN HERE *) Admitted.
277+
> t_update_permute : Not (x2 = x1) -> t_update x1 v1 $ t_update x2 v2 m
278+
> = t_update x2 v2 $ t_update x1 v1 m
279+
> t_update_permute x = ?t_update_permute_rhs
284280

285281
$\square$
286282

283+
287284
== Partial maps
288285

289-
Finally, we define partial maps on top of total maps. A partial map with
290-
elements of type A is simply a total map with elements of type option A and
291-
default element None.
286+
Finally, we define _partial maps_ on top of total maps. A partial map with
287+
elements of type \idr{a} is simply a total map with elements of type \idr{Maybe
288+
a} and default element \idr{Nothing}.
292289

293-
Definition partial_map (A:Type) := total_map (option A).
290+
> partial_map : Type -> Type
291+
> partial_map a = total_map (Maybe a)
294292

295-
Definition empty {A:Type} : partial_map A :=
296-
t_empty None.
293+
> empty : partial_map a
294+
> empty = t_empty Nothing
297295

298-
Definition update {A:Type} (m : partial_map A)
299-
(x : id) (v : A) :=
300-
t_update m x (Some v).
296+
> update : (x : Id) -> (v : a) -> (m : partial_map a) -> partial_map a
297+
> update x v m = t_update x (Just v) m
301298

302299
We now straightforwardly lift all of the basic lemmas about total maps to
303300
partial maps.
304301

305-
Lemma apply_empty : ∀A x, @empty A x = None.
302+
> apply_empty : empty {a} x = Nothing {a}
303+
> apply_empty = Refl
304+
305+
\todo[inline]{Finish}
306306

307-
Lemma update_eq : ∀A (m: partial_map A) x v,
308-
(update m x v) x = Some v.
307+
> update_eq : (update x v m) x = Just v
308+
> update_eq = ?update_eq_rhs
309309

310-
Theorem update_neq : ∀(X:Type) v x1 x2
311-
(m : partial_map X),
312-
x2 ≠ x1 →
313-
(update m x2 v) x1 = m x1.
310+
> update_neq : Not (x2 = x1) -> (update x2 v m) x1 = m x1
311+
> update_neq x = ?update_neq_rhs
314312

315-
Lemma update_shadow : ∀A (m: partial_map A) v1 v2 x,
316-
update (update m x v1) x v2 = update m x v2.
313+
> update_shadow : update x v2 $ update x v1 m = update x v2 m
314+
> update_shadow = ?update_shadow_rhs
317315

318-
Theorem update_same : ∀X v x (m : partial_map X),
319-
m x = Some v →
320-
update m x v = m.
316+
> update_same : m x = Just v -> update x v m = m
317+
> update_same prf = ?update_same_rhs
321318

322-
Theorem update_permute : ∀(X:Type) v1 v2 x1 x2
323-
(m : partial_map X),
324-
x2 ≠ x1 →
325-
(update (update m x2 v2) x1 v1)
326-
= (update (update m x1 v1) x2 v2).
319+
> update_permute : Not (x2 = x1) -> update x1 v1 $ update x2 v2 m
320+
> = update x2 v2 $ update x1 v1 m
321+
> update_permute x = ?update_permute_rhs

0 commit comments

Comments
 (0)