Copyright | (c) Grant Weyburne 2022 |
---|---|
License | BSD-3 |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- type family NatToPeanoT n where ...
- type family PeanoToNatT n where ...
- data Peano
- type DiffT i j n = (j + 1) - i
- type DiffTC i j n = (i <=! j, j <=! n)
- type family FacT x where ...
- type (<=!) i n = (FailUnless (i <=? n) (((('Text "i>n" :<>: 'Text ": i=") :<>: 'ShowType i) :<>: 'Text " n=") :<>: 'ShowType n), PosC i)
- type (<!) i n = (FailUnless ((i + 1) <=? n) (((('Text "i>=n" :<>: 'Text ": i=") :<>: 'ShowType i) :<>: 'Text " n=") :<>: 'ShowType n), KnownNat i)
- type LTEQT msg i n = (FailUnless (i <=? n) ((((('Text "i>n" :<>: 'Text ": i=") :<>: 'ShowType i) :<>: 'Text " n=") :<>: 'ShowType n) :<>: msg), PosC i)
- type D1 a = '[a]
- type D2 a b = '[a, b]
- type D3 a b c = '[a, b, c]
- type D4 a b c d = '[a, b, c, d]
- type D5 a b c d e = '[a, b, c, d, e]
- type D6 a b c d e f = '[a, b, c, d, e, f]
- type D7 a b c d e f g = '[a, b, c, d, e, f, g]
- type D8 a b c d e f g h = '[a, b, c, d, e, f, g, h]
- type D9 a b c d e f g h i = '[a, b, c, d, e, f, g, h, i]
- type D10 a b c d e f g h i j = '[a, b, c, d, e, f, g, h, i, j]
- type family ProductT ns where ...
- type NN n = NN' '[] n
- type family NN' ns n where ...
- type family ReverseT ns where ...
- type family ListTupleT n a = result | result -> n a where ...
- class ValidateNestedListC x y where
- class ValidateNestedNonEmptyC x y where
- validateNestedList :: forall x. ValidateNestedListC x (ValidateNestedListT x) => x -> Either String (NonEmpty Pos)
- validateNestedNonEmpty :: forall x. ValidateNestedNonEmptyC x (ValidateNestedNonEmptyT x) => x -> Either String (NonEmpty Pos)
- type family ValidateNestedListT x where ...
- type family ValidateNestedNonEmptyT x where ...
- nestedNonEmptyToList :: forall ns a. NestedListC ns => NonEmptyNST ns a -> Either String (ListNST ns a)
- nestedListToNonEmpty :: forall ns a. NestedListC ns => ListNST ns a -> Either String (NonEmptyNST ns a)
- class NestedListC ns where
- nestedListToNonEmptyC :: proxy a -> ListNST ns a -> Either String (NonEmptyNST ns a)
- nestedNonEmptyToListC :: proxy a -> NonEmptyNST ns a -> Either String (ListNST ns a)
- flattenNestedListC :: proxy a -> ListNST ns a -> Either String [a]
- type family NonEmptyNST ns a where ...
- type family ListNST ns a where ...
peano
type family NatToPeanoT n where ... Source #
convert Nat to Peano
NatToPeanoT 0 = 'Z | |
NatToPeanoT n = 'S (NatToPeanoT (n - 1)) |
type family PeanoToNatT n where ... Source #
convert Peano to Nat
PeanoToNatT 'Z = 0 | |
PeanoToNatT ('S n) = 1 + PeanoToNatT n |
peano numbers for converting between Nat
and peano
arithmetic
type DiffT i j n = (j + 1) - i Source #
find the number of N between "i" and "j" while ensuring i<=j and j<=n
type (<=!) i n = (FailUnless (i <=? n) (((('Text "i>n" :<>: 'Text ": i=") :<>: 'ShowType i) :<>: 'Text " n=") :<>: 'ShowType n), PosC i) Source #
constraint for ensuring that "i" <= "n"
type (<!) i n = (FailUnless ((i + 1) <=? n) (((('Text "i>=n" :<>: 'Text ": i=") :<>: 'ShowType i) :<>: 'Text " n=") :<>: 'ShowType n), KnownNat i) Source #
constraint for ensuring that "i" <= "n"
type LTEQT msg i n = (FailUnless (i <=? n) ((((('Text "i>n" :<>: 'Text ": i=") :<>: 'ShowType i) :<>: 'Text " n=") :<>: 'ShowType n) :<>: msg), PosC i) Source #
constraint for ensuring that "i" <= "n" with a custom error message
matrix dimension synonyms
type D10 a b c d e f g h i j = '[a, b, c, d, e, f, g, h, i, j] Source #
matrix dimension of degree 10
matrix helpers
type family NN' ns n where ... Source #
generates a list of indices using the individual digits of the given Nat
type family ReverseT ns where ... Source #
reverse a type level list
ReverseT (n ': ns) = ReverseT' (n ': ns) '[] |
type family ListTupleT n a = result | result -> n a where ... Source #
translates a type of size "n" to a tuple of size "n"
ListTupleT 1 a = One a | |
ListTupleT 2 a = (a, a) | |
ListTupleT 3 a = (a, a, a) | |
ListTupleT 4 a = (a, a, a, a) | |
ListTupleT 5 a = (a, a, a, a, a) | |
ListTupleT 6 a = (a, a, a, a, a, a) | |
ListTupleT 7 a = (a, a, a, a, a, a, a) | |
ListTupleT 8 a = (a, a, a, a, a, a, a, a) | |
ListTupleT 9 a = (a, a, a, a, a, a, a, a, a) | |
ListTupleT 10 a = (a, a, a, a, a, a, a, a, a, a) | |
ListTupleT 11 a = (a, a, a, a, a, a, a, a, a, a, a) | |
ListTupleT 12 a = (a, a, a, a, a, a, a, a, a, a, a, a) | |
ListTupleT 13 a = (a, a, a, a, a, a, a, a, a, a, a, a, a) | |
ListTupleT 14 a = (a, a, a, a, a, a, a, a, a, a, a, a, a, a) | |
ListTupleT 15 a = (a, a, a, a, a, a, a, a, a, a, a, a, a, a, a) | |
ListTupleT 16 a = (a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a) | |
ListTupleT 17 a = (a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a) | |
ListTupleT 18 a = (a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a) | |
ListTupleT 19 a = (a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a) | |
ListTupleT 20 a = (a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a) |
list and nonempty conversions
class ValidateNestedListC x y where Source #
extracts the dimensions of a nested list: doesnt allow empty dimensions
Instances
(TypeError ('Text "ValidateNestedListC: not defined at 0") :: Constraint) => ValidateNestedListC x 'Z Source # | |
Defined in Cybus.NatHelper | |
ValidateNestedListC x ('S 'Z) Source # | |
Defined in Cybus.NatHelper | |
ValidateNestedListC x ('S n) => ValidateNestedListC [x] ('S ('S n)) Source # | |
Defined in Cybus.NatHelper |
class ValidateNestedNonEmptyC x y where Source #
extracts the dimensions of a nested nonempty list: doesnt allow empty dimensions
Instances
(TypeError ('Text "ValidateNestedNonEmptyC: not defined at 'Z") :: Constraint) => ValidateNestedNonEmptyC x 'Z Source # | |
Defined in Cybus.NatHelper | |
ValidateNestedNonEmptyC x ('S 'Z) Source # | |
Defined in Cybus.NatHelper | |
ValidateNestedNonEmptyC x ('S zs) => ValidateNestedNonEmptyC (NonEmpty x) ('S ('S zs)) Source # | |
validateNestedList :: forall x. ValidateNestedListC x (ValidateNestedListT x) => x -> Either String (NonEmpty Pos) Source #
validate that the nested list is consistent in size along all dimensions
validateNestedNonEmpty :: forall x. ValidateNestedNonEmptyC x (ValidateNestedNonEmptyT x) => x -> Either String (NonEmpty Pos) Source #
validate that the nested nonempty list is consistent in size along all dimensions
type family ValidateNestedListT x where ... Source #
extracts the dimensions of a nested list
ValidateNestedListT [x] = 'S (ValidateNestedListT x) | |
ValidateNestedListT _ = 'S 'Z |
type family ValidateNestedNonEmptyT x where ... Source #
extracts the dimensions of a nested nonempty list
ValidateNestedNonEmptyT (NonEmpty x) = 'S (ValidateNestedNonEmptyT x) | |
ValidateNestedNonEmptyT _ = 'S 'Z |
nestedNonEmptyToList :: forall ns a. NestedListC ns => NonEmptyNST ns a -> Either String (ListNST ns a) Source #
convert a nested nonempty list into a nested list
nestedListToNonEmpty :: forall ns a. NestedListC ns => ListNST ns a -> Either String (NonEmptyNST ns a) Source #
convert a nested list into a nested nonempty list
class NestedListC ns where Source #
methods for working with nested lists
nestedListToNonEmptyC :: proxy a -> ListNST ns a -> Either String (NonEmptyNST ns a) Source #
convert a nested list to a nested nonempty list
nestedNonEmptyToListC :: proxy a -> NonEmptyNST ns a -> Either String (ListNST ns a) Source #
convert a nested nonempty list to a nested list
flattenNestedListC :: proxy a -> ListNST ns a -> Either String [a] Source #
Instances
type family NonEmptyNST ns a where ... Source #
convert a matrix index into nested lists
NonEmptyNST '[] _ = TypeError ('Text "NonEmptyNST: empty indices") | |
NonEmptyNST '[_] a = NonEmpty a | |
NonEmptyNST (_ ': (n1 ': ns)) a = NonEmpty (NonEmptyNST (n1 ': ns) a) |