aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--.gitignore9
-rw-r--r--B.agda11
-rw-r--r--Prelude/Bool.agda18
-rw-r--r--Prelude/BooleanAlgebra.agda9
-rw-r--r--Prelude/Char.agda12
-rw-r--r--Prelude/Eq.agda40
-rw-r--r--Prelude/Maybe.agda12
-rw-r--r--Prelude/Product.agda9
-rw-r--r--Prelude/String.agda12
-rw-r--r--Prelude/Sum.agda12
10 files changed, 144 insertions, 0 deletions
diff --git a/.gitignore b/.gitignore
new file mode 100644
index 0000000..1c5bf9e
--- /dev/null
+++ b/.gitignore
@@ -0,0 +1,9 @@
+# -*- conf -*-
+
+# Editor backup files
+*~
+\#*
+.\#*
+
+# Agda
+*.agdai \ No newline at end of file
diff --git a/B.agda b/B.agda
new file mode 100644
index 0000000..c2a7b5b
--- /dev/null
+++ b/B.agda
@@ -0,0 +1,11 @@
+module B where
+
+open import B.Prelude.Bool public
+open import B.Prelude.BooleanAlgebra public
+open import B.Prelude.Char public
+open import B.Prelude.Maybe public
+open import B.Prelude.Product public
+open import B.Prelude.String public
+open import B.Prelude.Sum public
+
+open import B.Prelude.Eq public
diff --git a/Prelude/Bool.agda b/Prelude/Bool.agda
new file mode 100644
index 0000000..9d82c50
--- /dev/null
+++ b/Prelude/Bool.agda
@@ -0,0 +1,18 @@
+module B.Prelude.Bool where
+
+open import B.Prelude.BooleanAlgebra using (BooleanAlgebra)
+import Data.Bool
+import Data.Bool.Properties
+
+open Data.Bool
+ using (Bool; if_then_else_; T)
+ public
+
+instance
+ BooleanAlgebra-Bool : BooleanAlgebra _ _
+ BooleanAlgebra-Bool = Data.Bool.Properties.booleanAlgebra
+
+module Bool where
+ open Data.Bool
+ using (_xor_)
+ public
diff --git a/Prelude/BooleanAlgebra.agda b/Prelude/BooleanAlgebra.agda
new file mode 100644
index 0000000..df22109
--- /dev/null
+++ b/Prelude/BooleanAlgebra.agda
@@ -0,0 +1,9 @@
+module B.Prelude.BooleanAlgebra where
+
+import Algebra
+open Algebra
+ using (BooleanAlgebra)
+ public
+open Algebra.BooleanAlgebra ⦃...⦄
+ using (_∧_; _∨_; ¬_; ⊤; ⊥)
+ public
diff --git a/Prelude/Char.agda b/Prelude/Char.agda
new file mode 100644
index 0000000..357e3f3
--- /dev/null
+++ b/Prelude/Char.agda
@@ -0,0 +1,12 @@
+module B.Prelude.Char where
+
+import Data.Char
+
+open Data.Char
+ using (Char)
+ public
+
+module Char where
+ open Data.Char
+ using (toNat)
+ public
diff --git a/Prelude/Eq.agda b/Prelude/Eq.agda
new file mode 100644
index 0000000..4a7b84f
--- /dev/null
+++ b/Prelude/Eq.agda
@@ -0,0 +1,40 @@
+module B.Prelude.Eq where
+
+import Data.Bool as Bool
+open Bool using (Bool)
+import Data.Char as Char
+open Char using (Char)
+import Data.Nat as ℕ
+open ℕ using (ℕ)
+open import Function using (_$_)
+import Level
+open Level using (_⊔_)
+open import Relation.Nullary.Decidable using (⌊_⌋)
+open import Relation.Binary using (DecSetoid)
+
+record Eq {c} {ℓ} (t : Set c) : Set (Level.suc $ c ⊔ ℓ) where
+ field
+ decSetoid : DecSetoid c ℓ
+
+ _≟_ = DecSetoid._≟_ decSetoid
+
+ _==_ : DecSetoid.Carrier decSetoid
+ → DecSetoid.Carrier decSetoid
+ → Bool
+ x == y = ⌊ x ≟ y ⌋
+
+open Eq ⦃...⦄ public
+
+instance
+ Eq-Bool : Eq Bool
+ Eq-Bool = record { decSetoid = Bool.decSetoid }
+
+ Eq-Char : Eq Char
+ Eq-Char = record { decSetoid = Char.decSetoid }
+
+ -- TODO: Float
+
+ Eq-ℕ : Eq ℕ
+ Eq-ℕ =
+ let module DecTotalOrder = Relation.Binary.DecTotalOrder in
+ record { decSetoid = DecTotalOrder.Eq.decSetoid ℕ.decTotalOrder }
diff --git a/Prelude/Maybe.agda b/Prelude/Maybe.agda
new file mode 100644
index 0000000..5b723db
--- /dev/null
+++ b/Prelude/Maybe.agda
@@ -0,0 +1,12 @@
+module B.Prelude.Maybe where
+
+import Data.Maybe
+
+open Data.Maybe
+ using (Maybe; just; nothing; maybe; maybe′)
+ public
+
+module Maybe where
+ open Data.Maybe
+ using (from-just; is-just; is-nothing)
+ public
diff --git a/Prelude/Product.agda b/Prelude/Product.agda
new file mode 100644
index 0000000..4732281
--- /dev/null
+++ b/Prelude/Product.agda
@@ -0,0 +1,9 @@
+module B.Prelude.Product where
+
+import Data.Product
+
+open Data.Product
+ using (_×_; proj₁; proj₂; _,_; _,′_; curry; uncurry; uncurry′)
+ public
+
+module Product where
diff --git a/Prelude/String.agda b/Prelude/String.agda
new file mode 100644
index 0000000..24fb3e2
--- /dev/null
+++ b/Prelude/String.agda
@@ -0,0 +1,12 @@
+module B.Prelude.String where
+
+import Data.String
+
+open Data.String
+ using (String; unlines)
+ public
+
+module String where
+ open Data.String
+ using (_++_; fromList; toCostring; toList; toVec)
+ public
diff --git a/Prelude/Sum.agda b/Prelude/Sum.agda
new file mode 100644
index 0000000..4cc1491
--- /dev/null
+++ b/Prelude/Sum.agda
@@ -0,0 +1,12 @@
+module B.Prelude.Sum where
+
+import Data.Sum
+
+open Data.Sum
+ using (_⊎_; inj₁; inj₂; [_,_]; [_,_]′)
+ public
+
+module Sum where
+ open Data.Sum
+ using (isInj₁; isInj₂)
+ public