Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Finite :: Nat -> Type where
- finite :: forall n. KnownNat n => Int -> Maybe (Finite n)
- azipWith :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
- showVector :: [String] -> String
- data Pair a = Pair a a
- newtype Vector (n :: Nat) a = Vector (Vector a)
- tail :: Vector (n + 1) a -> Vector n a
- fromList :: forall n a. KnownNat n => [a] -> Maybe (Vector n a)
- zipWith :: (a -> b -> c) -> Vector n a -> Vector n b -> Vector n c
- length :: forall n a. KnownNat n => Vector n a -> Int
- replicate :: forall n a. KnownNat n => a -> Vector n a
- index :: Vector n a -> Finite n -> a
- viota :: forall n. KnownNat n => Vector n (Finite n)
- class Functor f => Naperian f where
- type Log f
- transpose :: (Naperian f, Naperian g) => f (g a) -> g (f a)
- class (Applicative f, Naperian f, Traversable f) => Dimension f where
- inner :: (Num a, Dimension f) => f a -> f a -> a
- matrix :: (Num a, Dimension f, Dimension g, Dimension h) => f (g a) -> g (h a) -> f (h a)
- data Hyper :: [Type -> Type] -> Type -> Type where
- point :: Hyper '[] a -> a
- crystal :: Hyper (f ': fs) a -> Hyper fs (f a)
- class Shapely fs where
- hzipWith :: (a -> b -> c) -> Hyper fs a -> Hyper fs b -> Hyper fs c
- first :: Shapely fs => Hyper fs a -> a
- transposeH :: Hyper (f ': (g ': fs)) a -> Hyper (g ': (f ': fs)) a
- foldrH :: (a -> a -> a) -> a -> Hyper (f ': fs) a -> Hyper fs a
- unary :: Shapely fs => (a -> b) -> Hyper fs a -> Hyper fs b
- binary :: (Compatible fs gs, Max fs gs ~ hs, Alignable fs hs, Alignable gs hs) => (a -> b -> c) -> Hyper fs a -> Hyper gs b -> Hyper hs c
- up :: (Shapely fs, Dimension f) => Hyper fs a -> Hyper (f ': fs) a
- innerH :: (Max fs gs ~ (f ': hs), Alignable fs (f ': hs), Alignable gs (f ': hs), Compatible fs gs, Num a) => Hyper fs a -> Hyper gs a -> Hyper hs a
- matrixH :: (Num a, Dimension f, Dimension g, Dimension h) => Hyper '[g, f] a -> Hyper '[h, g] a -> Hyper '[h, f] a
- class (Shapely fs, Shapely gs) => Alignable fs gs where
- type family Max (fs :: [Type -> Type]) (gs :: [Type -> Type]) :: [Type -> Type] where ...
- type family Compatible (fs :: [Type -> Type]) (gs :: [Type -> Type]) :: Constraint where ...
- elements :: Shapely fs => Hyper fs a -> [a]
- data Flat fs a where
- flatten :: Shapely fs => Hyper fs a -> Flat fs a
- data Sparse fs a where
- unsparse :: forall fs a. Shapely fs => Sparse fs a -> Flat fs a
- type Matrix n m v = Vector n (Vector m v)
- example1 :: Int
- example2 :: Matrix 2 2 Int
- example3 :: Hyper '[] Int
- example4 :: Hyper '[Vector 2, Vector 2] Int
Documentation
data Finite :: Nat -> Type where Source #
The finite set of type-bounded Naturals. A value of type
has
exactly Fin
nn
inhabitants, the natural numbers from [0..n-1]
.
azipWith :: Applicative f => (a -> b -> c) -> f a -> f b -> f c Source #
"Applicative
zipping".
showVector :: [String] -> String Source #
Format a vector to make it look nice.
The cartesian product of
, equivalent to a
(a, a)
.
Pair a a |
newtype Vector (n :: Nat) a Source #
Functor (Vector n) Source # | |
KnownNat n => Applicative (Vector n) Source # | |
Foldable (Vector n) Source # | |
Traversable (Vector n) Source # | |
KnownNat n => Dimension (Vector n) Source # | |
KnownNat n => Naperian (Vector n) Source # | |
(KnownNat n, Traversable (Vector n)) => IsList (Vector n a) Source # | |
Eq a => Eq (Vector n a) Source # | |
Ord a => Ord (Vector n a) Source # | |
Show a => Show (Vector n a) Source # | |
type Log (Vector n) Source # | |
type Item (Vector n a) Source # | |
class Functor f => Naperian f where Source #
Naperian functors.
The "logarithm" of f
. This type represents the input
you use to
look up values inside f a
. For example, if you have a list [a]
, and
you want to look up a value, then you use an
to index into
the list. In this case, Int
. If you have a type-bounded
Vector Log
[a] = Int
, then Vector
(n :: Nat
) a
is the
range of integers Log
(Vector
n)[0..n-1]
(represented here as
.)Finite
n
lookup :: f a -> Log f -> a Source #
Look up an element a
inside f a
. If you read this function type in
english, it says "if you give me an f a
, then I will give you a
function, so you can look up the elements of f a
and get back an a
"
tabulate :: (Log f -> a) -> f a Source #
Tabulate a
. This creates Naperian
f a
values by mapping the logarithm
of f
onto every "position" inside f a
positions :: f (Log f) Source #
Find every position in the "space" of the
.Naperian
f
transpose :: (Naperian f, Naperian g) => f (g a) -> g (f a) Source #
The transposition of two
functors Naperian
f
and g
.
class (Applicative f, Naperian f, Traversable f) => Dimension f where Source #
data Hyper :: [Type -> Type] -> Type -> Type where Source #
Arbitrary-rank Hypercuboids, parameterized over their dimension.
transposeH :: Hyper (f ': (g ': fs)) a -> Hyper (g ': (f ': fs)) a Source #
Generalized transposition over arbitrary-rank hypercuboids.
foldrH :: (a -> a -> a) -> a -> Hyper (f ': fs) a -> Hyper fs a Source #
Fold over a single dimension of a Hypercuboid.
unary :: Shapely fs => (a -> b) -> Hyper fs a -> Hyper fs b Source #
Lift an unary function from values to hypercuboids of values.
binary :: (Compatible fs gs, Max fs gs ~ hs, Alignable fs hs, Alignable gs hs) => (a -> b -> c) -> Hyper fs a -> Hyper gs b -> Hyper hs c Source #
Lift a binary function from values to two sets of hypercuboids, which can be aligned properly.
innerH :: (Max fs gs ~ (f ': hs), Alignable fs (f ': hs), Alignable gs (f ': hs), Compatible fs gs, Num a) => Hyper fs a -> Hyper gs a -> Hyper hs a Source #
Generalized, rank-polymorphic inner product.
matrixH :: (Num a, Dimension f, Dimension g, Dimension h) => Hyper '[g, f] a -> Hyper '[h, g] a -> Hyper '[h, f] a Source #
Generalized, rank-polymorphic matrix product.
type family Compatible (fs :: [Type -> Type]) (gs :: [Type -> Type]) :: Constraint where ... Source #
Compatible '[] '[] = () | |
Compatible '[] (f ': gs) = () | |
Compatible (f ': fs) '[] = () | |
Compatible (f ': fs) (f ': gs) = Compatible fs gs | |
Compatible a b = TypeError ((Text "Mismatched dimensions!" :$$: ((Text "The dimension " :<>: ShowType a) :<>: Text " can't be aligned with")) :$$: (Text "the dimension " :<>: ShowType b)) |