Improve docs
This commit is contained in:
parent
5d7ce06597
commit
c7508bc57e
@ -10,6 +10,7 @@
|
||||
{-# LANGUAGE PolyKinds #-}
|
||||
{-# LANGUAGE UnicodeSyntax #-}
|
||||
|
||||
-- | Defines the boolean type and logical operators
|
||||
module Data.Bool where
|
||||
|
||||
import Data.TypeClass (Eq, Enum, Show)
|
||||
@ -25,7 +26,8 @@ singletons [d|
|
||||
F β· πΉ -- ^ False
|
||||
deriving (Eq, Show)
|
||||
|
||||
-- Logical operatos
|
||||
|
||||
-- * Logical operatos
|
||||
|
||||
-- | Conjuction
|
||||
(β§) β· πΉ β πΉ β πΉ
|
||||
|
@ -11,7 +11,7 @@
|
||||
{-# LANGUAGE PolyKinds #-}
|
||||
{-# LANGUAGE UnicodeSyntax #-}
|
||||
|
||||
|
||||
-- | Defines commonly used functions and combinators
|
||||
module Data.Function where
|
||||
|
||||
-- | Identity Function
|
||||
|
@ -1,3 +1,4 @@
|
||||
-- | An arbitrary-precision integers datatype
|
||||
module Data.Integer
|
||||
( module GHC.Integer
|
||||
) where
|
||||
|
@ -11,6 +11,7 @@
|
||||
{-# LANGUAGE PolyKinds #-}
|
||||
{-# LANGUAGE UnicodeSyntax #-}
|
||||
|
||||
-- | Defines natural numbers on both term and type level
|
||||
module Data.Nat where
|
||||
|
||||
import Relation.Equality
|
||||
@ -86,13 +87,13 @@ instance Bounded β where
|
||||
maxBound = (β)
|
||||
|
||||
|
||||
-- | Convert a natural into an "Integer"
|
||||
-- | Convert a natural into an 'Integer'
|
||||
toInteger β· β β Integer
|
||||
toInteger Z = 0
|
||||
toInteger (S n) = 1 T.+ toInteger n
|
||||
|
||||
|
||||
-- | Convert na "Integer" into a natural
|
||||
-- | Convert an 'Integer' into a natural
|
||||
fromInteger β· Integer β β
|
||||
fromInteger 0 = Z
|
||||
fromInteger n
|
||||
|
@ -1,3 +1,4 @@
|
||||
-- | Exports haskell built-in typeclasses
|
||||
module Data.TypeClass
|
||||
( Eq(..)
|
||||
, Ord(..)
|
||||
|
@ -12,6 +12,9 @@
|
||||
{-# LANGUAGE PolyKinds #-}
|
||||
{-# LANGUAGE UnicodeSyntax #-}
|
||||
|
||||
-- | Defines a vector type, analogous to a list, that achieves
|
||||
-- type-safe operation like resizing and concatenation by using
|
||||
-- new dependantly typed language features in haskell
|
||||
module Data.Vec where
|
||||
|
||||
import Relation.Equality (gcastWith)
|
||||
@ -27,11 +30,13 @@ import qualified Data.TypeClass as T
|
||||
|
||||
infixr 5 :-
|
||||
|
||||
-- | The 'Vec' datatype
|
||||
data Vec (a β· β
) β· β β β
where
|
||||
Nil β· Vec a Z
|
||||
(:-) β· a β Vec a n β Vec a (S n)
|
||||
Nil β· Vec a Z -- ^ empty 'Vec', length 0
|
||||
(:-) β· a β Vec a n β Vec a (S n) -- ^ "cons" operator
|
||||
|
||||
|
||||
-- | 'String' type alias for vector of characters
|
||||
type String n = Vec Char n
|
||||
|
||||
|
||||
@ -49,11 +54,20 @@ instance SingI n β IsString (String n) where
|
||||
fromString = fromList
|
||||
|
||||
|
||||
|
||||
-- * Conversions
|
||||
|
||||
-- | Convert a 'Vec' into a List
|
||||
toList β· Vec a n β [a]
|
||||
toList Nil = []
|
||||
toList (x :- xs) = x : toList xs
|
||||
|
||||
|
||||
-- | Convert a List into a 'Vec'
|
||||
--
|
||||
-- It's not possible to convert an infinite list to a vector
|
||||
-- as haskell does not permit constructing infinite type,
|
||||
-- which the resulting vector length would be.
|
||||
fromList β· SingI n β [a] β Vec a n
|
||||
fromList = f sing
|
||||
where f β· Sβ n β [a] β Vec a n
|
||||
@ -61,84 +75,127 @@ fromList = f sing
|
||||
f (SS n) (x:xs) = x :- f n xs
|
||||
|
||||
|
||||
|
||||
-- * Basic functions
|
||||
|
||||
-- | Vector concatenation
|
||||
(β§Ί) β· Vec a n β Vec a m β Vec a (n :+ m)
|
||||
(β§Ί) (x :- xs) ys = x :- xs β§Ί ys
|
||||
(β§Ί) Nil ys = ys
|
||||
|
||||
|
||||
-- | Given a nonempty 'Vec' returns the first element
|
||||
-- and the rest of the vector in a tuple.
|
||||
-- > uncons x β‘ (head x, tail x)
|
||||
uncons β· Vec a (S n) β (a, Vec a n)
|
||||
uncons (x :- xs) = (x, xs)
|
||||
|
||||
|
||||
-- | Returns the 'head' (ie the first element) of a nonempty 'Vec'.
|
||||
head β· Vec a (S n) β a
|
||||
head (x :- _) = x
|
||||
|
||||
|
||||
-- | Returns the last element of a nonempty 'Vec'.
|
||||
last β· Vec a (S n) β a
|
||||
last (x :- Nil) = x
|
||||
last (x :- y :- ys) = last (y :- ys)
|
||||
|
||||
|
||||
-- | Applied to a nonempty 'Vec' returns everything but its first element.
|
||||
-- > x β‘ head x β§Ί tail x
|
||||
tail β· Vec a (S n) β Vec a n
|
||||
tail (_ :- xs) = xs
|
||||
|
||||
|
||||
-- | Applied to a nonempty 'Vec' returns everything but its last element.
|
||||
-- > x β‘ init x β§Ί last x
|
||||
init β· Vec a (S n) β Vec a n
|
||||
init (x :- Nil) = Nil
|
||||
init (x :- y :- ys) = x :- init (y :- ys)
|
||||
|
||||
|
||||
uncons β· Vec a (S n) β (a, Vec a n)
|
||||
uncons (x :- xs) = (x, xs)
|
||||
|
||||
-- * Length information
|
||||
|
||||
-- | Test whether a 'Vec' has zero length.
|
||||
null β· Vec a n β πΉ
|
||||
null Nil = T
|
||||
null _ = F
|
||||
|
||||
|
||||
-- | Returns the length (numbers of elements) of a 'Vec'.
|
||||
length β· Vec a n β β
|
||||
length Nil = Z
|
||||
length (_ :- xs) = S (length xs)
|
||||
|
||||
|
||||
-- | Same as 'length' but produces a singleton type 'Sβ'.
|
||||
sLength β· Vec a n β Sβ n
|
||||
sLength Nil = SZ
|
||||
sLength (x :- xs) = SS (sLength xs)
|
||||
|
||||
|
||||
|
||||
-- * Transforming and reducing a 'Vec'
|
||||
|
||||
-- | Applies a function on every element of a 'Vec'.
|
||||
map β· (a β b) β Vec a n β Vec b n
|
||||
map _ Nil = Nil
|
||||
map f (x :- xs) = f x :- map f xs
|
||||
|
||||
|
||||
-- | 'foldl' applied to a binary operator, a starting value
|
||||
-- and a 'Vec' reduces the vector to a single value obtained
|
||||
-- by sequentially applying the operation from the left to the right.
|
||||
foldl β· (a β b β a) β a β Vec b n β a
|
||||
foldl _ x Nil = x
|
||||
foldl f x (y :- ys) = foldl f (f x y) ys
|
||||
|
||||
|
||||
-- | Same as "fold" but reduces the vector in the opposite
|
||||
-- direction: from the right to the left.
|
||||
foldr β· (a β b β b) β b β Vec a n β b
|
||||
foldr f x Nil = x
|
||||
foldr f x (y:-ys) = f y (foldr f x ys)
|
||||
|
||||
|
||||
-- | Variant of 'foldl' which requires no starting value but
|
||||
-- applies only on nonempty 'Vec'
|
||||
foldlβ β· (a β a β a) β Vec a (S n) β a
|
||||
foldlβ f (x :- Nil) = x
|
||||
foldlβ f (x :- y :- ys) = foldlβ f (f x y :- ys)
|
||||
|
||||
|
||||
-- | As for 'foldl', a variant of 'foldr' with no starting point
|
||||
foldrβ β· (a β a β a) β Vec a (S n) β a
|
||||
foldrβ f (x :- Nil) = x
|
||||
foldrβ f (x :- y :- ys) = f x (foldrβ f (y :- ys))
|
||||
|
||||
|
||||
-- | Reverse the order of the element of a 'Vec'
|
||||
-- > reverse β reverse = id
|
||||
reverse β· Vec a n β Vec a n
|
||||
reverse Nil = Nil
|
||||
reverse (y :- ys) = gcastWith proof (reverse ys β§Ί (y :- Nil))
|
||||
where proof = succ_plus (sLength ys)
|
||||
|
||||
|
||||
-- | Applied to a singleton natural @n@ and a value produces
|
||||
-- a vector obtained by duplicating the value @n@ times
|
||||
replicate β· Sβ n β a β Vec a n
|
||||
replicate SZ _ = Nil
|
||||
replicate (SS n) a = a :- replicate n a
|
||||
|
||||
|
||||
-- | 'take' @n@ applied to a 'Vec', returns the first @n@ element
|
||||
-- of the vector
|
||||
take β· Sβ n β Vec a m β Vec a n
|
||||
take SZ _ = Nil
|
||||
take (SS n) (x :- xs) = x :- take n xs
|
||||
|
||||
|
||||
-- | 'drop' @n@ applied to a 'Vec', returns every element of
|
||||
-- the vector but the first @n@
|
||||
drop β· Sβ n β Vec a m β Vec a (m :- n)
|
||||
drop SZ x = x
|
||||
drop (SS n) (x :- xs) = drop n xs
|
||||
|
@ -11,6 +11,8 @@
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE UnicodeSyntax #-}
|
||||
|
||||
-- | Defines equality relation on types and provides
|
||||
-- a simple interface to write proof on haskell types
|
||||
module Relation.Equality where
|
||||
|
||||
import Data.Singletons (Sing)
|
||||
@ -44,4 +46,3 @@ castWith Refl x = x
|
||||
-- | Generalized form of cast
|
||||
gcastWith β· β a b r. (a :β‘ b) β ((a ~ b) β r) β r
|
||||
gcastWith Refl x = x
|
||||
|
||||
|
Loadingβ¦
Reference in New Issue
Block a user