module Disco.Doc (
DocKey (..),
RefType (..),
Reference (..),
mkRef,
mkIntro,
docMap,
) where
import Data.Map (Map)
import qualified Data.Map as M
import Disco.Syntax.Operators
import Disco.Syntax.Prims
import Disco.Util ((==>))
data DocKey where
PrimKey :: Prim -> DocKey
OtherKey :: String -> DocKey
deriving (DocKey -> DocKey -> Bool
(DocKey -> DocKey -> Bool)
-> (DocKey -> DocKey -> Bool) -> Eq DocKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DocKey -> DocKey -> Bool
== :: DocKey -> DocKey -> Bool
$c/= :: DocKey -> DocKey -> Bool
/= :: DocKey -> DocKey -> Bool
Eq, Eq DocKey
Eq DocKey =>
(DocKey -> DocKey -> Ordering)
-> (DocKey -> DocKey -> Bool)
-> (DocKey -> DocKey -> Bool)
-> (DocKey -> DocKey -> Bool)
-> (DocKey -> DocKey -> Bool)
-> (DocKey -> DocKey -> DocKey)
-> (DocKey -> DocKey -> DocKey)
-> Ord DocKey
DocKey -> DocKey -> Bool
DocKey -> DocKey -> Ordering
DocKey -> DocKey -> DocKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DocKey -> DocKey -> Ordering
compare :: DocKey -> DocKey -> Ordering
$c< :: DocKey -> DocKey -> Bool
< :: DocKey -> DocKey -> Bool
$c<= :: DocKey -> DocKey -> Bool
<= :: DocKey -> DocKey -> Bool
$c> :: DocKey -> DocKey -> Bool
> :: DocKey -> DocKey -> Bool
$c>= :: DocKey -> DocKey -> Bool
>= :: DocKey -> DocKey -> Bool
$cmax :: DocKey -> DocKey -> DocKey
max :: DocKey -> DocKey -> DocKey
$cmin :: DocKey -> DocKey -> DocKey
min :: DocKey -> DocKey -> DocKey
Ord, Int -> DocKey -> ShowS
[DocKey] -> ShowS
DocKey -> String
(Int -> DocKey -> ShowS)
-> (DocKey -> String) -> ([DocKey] -> ShowS) -> Show DocKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DocKey -> ShowS
showsPrec :: Int -> DocKey -> ShowS
$cshow :: DocKey -> String
show :: DocKey -> String
$cshowList :: [DocKey] -> ShowS
showList :: [DocKey] -> ShowS
Show)
data RefType where
Intro :: RefType
Ref :: RefType
URL :: RefType
deriving (RefType -> RefType -> Bool
(RefType -> RefType -> Bool)
-> (RefType -> RefType -> Bool) -> Eq RefType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RefType -> RefType -> Bool
== :: RefType -> RefType -> Bool
$c/= :: RefType -> RefType -> Bool
/= :: RefType -> RefType -> Bool
Eq, Eq RefType
Eq RefType =>
(RefType -> RefType -> Ordering)
-> (RefType -> RefType -> Bool)
-> (RefType -> RefType -> Bool)
-> (RefType -> RefType -> Bool)
-> (RefType -> RefType -> Bool)
-> (RefType -> RefType -> RefType)
-> (RefType -> RefType -> RefType)
-> Ord RefType
RefType -> RefType -> Bool
RefType -> RefType -> Ordering
RefType -> RefType -> RefType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RefType -> RefType -> Ordering
compare :: RefType -> RefType -> Ordering
$c< :: RefType -> RefType -> Bool
< :: RefType -> RefType -> Bool
$c<= :: RefType -> RefType -> Bool
<= :: RefType -> RefType -> Bool
$c> :: RefType -> RefType -> Bool
> :: RefType -> RefType -> Bool
$c>= :: RefType -> RefType -> Bool
>= :: RefType -> RefType -> Bool
$cmax :: RefType -> RefType -> RefType
max :: RefType -> RefType -> RefType
$cmin :: RefType -> RefType -> RefType
min :: RefType -> RefType -> RefType
Ord, Int -> RefType -> ShowS
[RefType] -> ShowS
RefType -> String
(Int -> RefType -> ShowS)
-> (RefType -> String) -> ([RefType] -> ShowS) -> Show RefType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RefType -> ShowS
showsPrec :: Int -> RefType -> ShowS
$cshow :: RefType -> String
show :: RefType -> String
$cshowList :: [RefType] -> ShowS
showList :: [RefType] -> ShowS
Show, ReadPrec [RefType]
ReadPrec RefType
Int -> ReadS RefType
ReadS [RefType]
(Int -> ReadS RefType)
-> ReadS [RefType]
-> ReadPrec RefType
-> ReadPrec [RefType]
-> Read RefType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RefType
readsPrec :: Int -> ReadS RefType
$creadList :: ReadS [RefType]
readList :: ReadS [RefType]
$creadPrec :: ReadPrec RefType
readPrec :: ReadPrec RefType
$creadListPrec :: ReadPrec [RefType]
readListPrec :: ReadPrec [RefType]
Read, RefType
RefType -> RefType -> Bounded RefType
forall a. a -> a -> Bounded a
$cminBound :: RefType
minBound :: RefType
$cmaxBound :: RefType
maxBound :: RefType
Bounded, Int -> RefType
RefType -> Int
RefType -> [RefType]
RefType -> RefType
RefType -> RefType -> [RefType]
RefType -> RefType -> RefType -> [RefType]
(RefType -> RefType)
-> (RefType -> RefType)
-> (Int -> RefType)
-> (RefType -> Int)
-> (RefType -> [RefType])
-> (RefType -> RefType -> [RefType])
-> (RefType -> RefType -> [RefType])
-> (RefType -> RefType -> RefType -> [RefType])
-> Enum RefType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RefType -> RefType
succ :: RefType -> RefType
$cpred :: RefType -> RefType
pred :: RefType -> RefType
$ctoEnum :: Int -> RefType
toEnum :: Int -> RefType
$cfromEnum :: RefType -> Int
fromEnum :: RefType -> Int
$cenumFrom :: RefType -> [RefType]
enumFrom :: RefType -> [RefType]
$cenumFromThen :: RefType -> RefType -> [RefType]
enumFromThen :: RefType -> RefType -> [RefType]
$cenumFromTo :: RefType -> RefType -> [RefType]
enumFromTo :: RefType -> RefType -> [RefType]
$cenumFromThenTo :: RefType -> RefType -> RefType -> [RefType]
enumFromThenTo :: RefType -> RefType -> RefType -> [RefType]
Enum)
data Reference = Reference {Reference -> RefType
refType :: RefType, Reference -> String
ref :: String}
deriving (Reference -> Reference -> Bool
(Reference -> Reference -> Bool)
-> (Reference -> Reference -> Bool) -> Eq Reference
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Reference -> Reference -> Bool
== :: Reference -> Reference -> Bool
$c/= :: Reference -> Reference -> Bool
/= :: Reference -> Reference -> Bool
Eq, Eq Reference
Eq Reference =>
(Reference -> Reference -> Ordering)
-> (Reference -> Reference -> Bool)
-> (Reference -> Reference -> Bool)
-> (Reference -> Reference -> Bool)
-> (Reference -> Reference -> Bool)
-> (Reference -> Reference -> Reference)
-> (Reference -> Reference -> Reference)
-> Ord Reference
Reference -> Reference -> Bool
Reference -> Reference -> Ordering
Reference -> Reference -> Reference
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Reference -> Reference -> Ordering
compare :: Reference -> Reference -> Ordering
$c< :: Reference -> Reference -> Bool
< :: Reference -> Reference -> Bool
$c<= :: Reference -> Reference -> Bool
<= :: Reference -> Reference -> Bool
$c> :: Reference -> Reference -> Bool
> :: Reference -> Reference -> Bool
$c>= :: Reference -> Reference -> Bool
>= :: Reference -> Reference -> Bool
$cmax :: Reference -> Reference -> Reference
max :: Reference -> Reference -> Reference
$cmin :: Reference -> Reference -> Reference
min :: Reference -> Reference -> Reference
Ord, Int -> Reference -> ShowS
[Reference] -> ShowS
Reference -> String
(Int -> Reference -> ShowS)
-> (Reference -> String)
-> ([Reference] -> ShowS)
-> Show Reference
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Reference -> ShowS
showsPrec :: Int -> Reference -> ShowS
$cshow :: Reference -> String
show :: Reference -> String
$cshowList :: [Reference] -> ShowS
showList :: [Reference] -> ShowS
Show)
mkRef :: String -> Reference
mkRef :: String -> Reference
mkRef = RefType -> String -> Reference
Reference RefType
Ref
mkIntro :: String -> Reference
mkIntro :: String -> Reference
mkIntro = RefType -> String -> Reference
Reference RefType
Intro
docMap :: Map DocKey (String, [Reference])
docMap :: Map DocKey (String, [Reference])
docMap =
[(DocKey, (String, [Reference]))]
-> Map DocKey (String, [Reference])
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ Prim -> DocKey
PrimKey (UOp -> Prim
PrimUOp UOp
Neg)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Arithmetic negation."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> []
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Add)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"The sum of two numbers, types, or graphs."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkIntro String
"arithmetic", String -> Reference
mkRef String
"addition"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Sub)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"The difference of two numbers."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkIntro String
"arithmetic", String -> Reference
mkRef String
"subtraction"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
SSub)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"The difference of two numbers, with a lower bound of 0."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkIntro String
"arithmetic", String -> Reference
mkRef String
"subtraction", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Mul)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"The product of two numbers, types, or graphs."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkIntro String
"arithmetic", String -> Reference
mkRef String
"multiplication"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Div)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Divide two numbers."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkIntro String
"arithmetic", String -> Reference
mkRef String
"division"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
IDiv)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"The integer quotient of two numbers, rounded down."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkIntro String
"arithmetic", String -> Reference
mkRef String
"integerdiv"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Mod)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"a mod b is the remainder when a is divided by b."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"mod"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Exp)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Exponentiation. a ^ b is a raised to the b power."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkIntro String
"arithmetic", String -> Reference
mkRef String
"exponentiation"]
, Prim -> DocKey
PrimKey (UOp -> Prim
PrimUOp UOp
Fact)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"n! computes the factorial of n, that is, 1 * 2 * ... * n."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"factorial"]
, Prim -> DocKey
PrimKey Prim
PrimFloor
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"floor(x) is the largest integer which is <= x."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkIntro String
"arithmetic", String -> Reference
mkRef String
"round", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey Prim
PrimCeil
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"ceiling(x) is the smallest integer which is >= x."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkIntro String
"arithmetic", String -> Reference
mkRef String
"round", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey Prim
PrimAbs
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"abs(x) is the absolute value of x."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkIntro String
"arithmetic", String -> Reference
mkRef String
"abs"]
, Prim -> DocKey
PrimKey Prim
PrimMin
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"min(x,y) is the minimum of x and y, i.e. whichever is smaller."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"compare"]
, Prim -> DocKey
PrimKey Prim
PrimMax
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"max(x,y) is the maximum of x and y, i.e. whichever is larger."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"compare"]
, Prim -> DocKey
PrimKey (UOp -> Prim
PrimUOp UOp
Not)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Logical negation: not(T) = F and not(F) = T."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"logic-ops", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
And)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Logical conjunction (and): T /\\ T = T; otherwise x /\\ y = F."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"logic-ops", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Or)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Logical disjunction (or): F \\/ F = F; otherwise x \\/ y = T."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"logic-ops", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Impl)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Logical implication (implies): T -> F = F; otherwise x -> y = T."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"logic-ops", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Iff)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Biconditional (if and only if)."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"logic-ops", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Eq)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Equality test. x == y is T if x and y are equal."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"compare"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Neq)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Inequality test. x /= y is T if x and y are unequal."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"compare", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Lt)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Less-than test. x < y is T if x is less than (but not equal to) y."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"compare"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Gt)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Greater-than test. x > y is T if x is greater than (but not equal to) y."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"compare"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Leq)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Less-than-or-equal test. x <= y is T if x is less than or equal to y."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"compare", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Geq)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Greater-than-or-equal test. x >= y is T if x is greater than or equal to y."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"compare", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
CartProd)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Cartesian product, i.e. the collection of all pairs. Also works on bags and sets."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"cp", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey Prim
PrimPower
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Power set, i.e. the set of all subsets. Also works on bags."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"power"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Union)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Union of two sets (or bags)."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"set-ops", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Inter)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Intersection of two sets (or bags)."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"set-ops", String -> Reference
mkRef String
"symbols"]
, Prim -> DocKey
PrimKey (BOp -> Prim
PrimBOp BOp
Diff)
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Difference of two sets (or bags)."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"set-ops"]
, String -> DocKey
OtherKey String
"N" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docN
, String -> DocKey
OtherKey String
"ℕ" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docN
, String -> DocKey
OtherKey String
"Nat" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docN
, String -> DocKey
OtherKey String
"Natural" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docN
, String -> DocKey
OtherKey String
"Z" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docZ
, String -> DocKey
OtherKey String
"ℤ" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docZ
, String -> DocKey
OtherKey String
"Int" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docZ
, String -> DocKey
OtherKey String
"Integer" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docZ
, String -> DocKey
OtherKey String
"F" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docF
, String -> DocKey
OtherKey String
"𝔽" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docF
, String -> DocKey
OtherKey String
"Frac" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docF
, String -> DocKey
OtherKey String
"Fractional" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docF
, String -> DocKey
OtherKey String
"Q" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docQ
, String -> DocKey
OtherKey String
"ℚ" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docQ
, String -> DocKey
OtherKey String
"Rational" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docQ
, String -> DocKey
OtherKey String
"Bool" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docB
, String -> DocKey
OtherKey String
"Boolean" DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> (String, [Reference])
docB
, String -> DocKey
OtherKey String
"Unit"
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"The unit type, i.e. a type with only a single value."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"unit", String -> Reference
mkRef String
"symbols"]
, String -> DocKey
OtherKey String
"Prop"
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"The type of propositions."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"prop"]
, String -> DocKey
OtherKey String
"List"
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"List(T) is the type of lists whose elements have type T."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"list", String -> Reference
mkRef String
"list-lib"]
, String -> DocKey
OtherKey String
"Bag"
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Bag(T) is the type of bags (i.e. sets with multiplicity) whose elements have type T."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"bag", String -> Reference
mkRef String
"symbols"]
, String -> DocKey
OtherKey String
"Set"
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Set(T) is the type of finite sets whose elements have type T."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"set", String -> Reference
mkRef String
"symbols"]
, String -> DocKey
OtherKey String
"|~|"
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"Absolute value, or the size of a collection."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkIntro String
"arithmetic", String -> Reference
mkRef String
"size"]
, String -> DocKey
OtherKey String
"{?"
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"{? ... ?} is a case expression, for choosing a result based on conditions."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"case"]
, String -> DocKey
OtherKey String
"λ"
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"λ (aka lambda, alternatively `\\`) introduces an anonymous function."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"anonymous-func", String -> Reference
mkRef String
"symbols"]
, String -> DocKey
OtherKey String
"#"
DocKey -> (String, [Reference]) -> (DocKey, (String, [Reference]))
forall a b. a -> b -> (a, b)
==> String
"The # character is used to denote the cardinality of an element in a bag."
String -> [Reference] -> (String, [Reference])
forall a b. a -> b -> (a, b)
==> [String -> Reference
mkRef String
"bag"]
]
where
docN :: (String, [Reference])
docN = (String
"The type of natural numbers: 0, 1, 2, ...", [Reference]
refsN)
refsN :: [Reference]
refsN = [String -> Reference
mkIntro String
"types", String -> Reference
mkRef String
"natural", String -> Reference
mkRef String
"symbols"]
docZ :: (String, [Reference])
docZ = (String
"The type of integers: ..., -2, -1, 0, 1, 2, ...", [Reference]
refsZ)
refsZ :: [Reference]
refsZ = [String -> Reference
mkIntro String
"types", String -> Reference
mkRef String
"integer", String -> Reference
mkRef String
"symbols"]
docF :: (String, [Reference])
docF = (String
"The type of fractional numbers p/q >= 0.", [Reference]
refsF)
refsF :: [Reference]
refsF = [String -> Reference
mkIntro String
"types", String -> Reference
mkRef String
"fraction", String -> Reference
mkRef String
"symbols"]
docQ :: (String, [Reference])
docQ = (String
"The type of rational numbers p/q.", [Reference]
refsQ)
refsQ :: [Reference]
refsQ = [String -> Reference
mkIntro String
"types", String -> Reference
mkRef String
"rational", String -> Reference
mkRef String
"symbols"]
docB :: (String, [Reference])
docB = (String
"The type of Booleans (T or F).", [Reference]
refsB)
refsB :: [Reference]
refsB = [String -> Reference
mkRef String
"bool"]