Safe Haskell | None |
---|---|
Language | GHC2021 |
Harpie.Shape
Description
Functions for manipulating shape. The module tends to supply equivalent functionality at type-level and value-level with functions of the same name (except for capitalization).
Synopsis
- data SNat (n :: Nat)
- pattern SNat :: () => KnownNat n => SNat n
- valueOf :: forall (n :: Nat). KnownNat n => Int
- data SNats (ns :: [Nat])
- pattern SNats :: () => KnownNats ns => SNats ns
- fromSNats :: forall (s :: [Nat]). SNats s -> [Nat]
- class KnownNats (ns :: [Nat]) where
- natVals :: forall (ns :: [Nat]) proxy. KnownNats ns => proxy ns -> [Nat]
- withKnownNats :: forall (ns :: [Nat]) r. SNats ns -> (KnownNats ns => r) -> r
- data SomeNats
- someNatVals :: [Nat] -> SomeNats
- withSomeSNats :: [Nat] -> (forall (s :: [Nat]). SNats s -> r) -> r
- valuesOf :: forall (s :: [Nat]). KnownNats s => [Int]
- rankOf :: forall (s :: [Nat]). KnownNats s => Int
- sizeOf :: forall (s :: [Nat]). KnownNats s => Int
- newtype Fin (s :: k) = UnsafeFin {}
- fin :: forall (n :: Nat). KnownNat n => Int -> Fin n
- safeFin :: forall (n :: Nat). KnownNat n => Int -> Maybe (Fin n)
- newtype Fins (s :: k) = UnsafeFins {}
- fins :: forall (s :: [Nat]). KnownNats s => [Int] -> Fins s
- safeFins :: forall (s :: [Nat]). KnownNats s => [Int] -> Maybe (Fins s)
- rank :: [a] -> Int
- data Rank (b :: [a]) (c :: Natural)
- range :: Int -> [Int]
- data Range (a :: Nat) (b :: [Nat])
- rerank :: Int -> [Int] -> [Int]
- data Rerank (a :: Nat) (b :: [Nat]) (c :: [Nat])
- dimsOf :: [Int] -> [Int]
- data DimsOf (a :: [Nat]) (b :: [Nat])
- endDimsOf :: [Int] -> [Int] -> [Int]
- data EndDimsOf (a :: [Nat]) (b :: [Nat]) (c :: [Nat])
- size :: [Int] -> Int
- data Size (a :: [Nat]) (b :: Nat)
- flatten :: [Int] -> [Int] -> Int
- shapen :: [Int] -> Int -> [Int]
- asSingleton :: [Int] -> [Int]
- data AsSingleton (a :: [Nat]) (b :: [Nat])
- asScalar :: [Int] -> [Int]
- data AsScalar (a :: [Nat]) (b :: [Nat])
- isSubset :: [Int] -> [Int] -> Bool
- data IsSubset (a :: [Nat]) (b :: [Nat]) (c :: Bool)
- exceptDims :: [Int] -> [Int] -> [Int]
- data ExceptDims (a :: [Nat]) (b :: [Nat]) (c :: [Nat])
- reorder :: [Int] -> [Int] -> [Int]
- data Reorder (a :: [Nat]) (b :: [Nat]) (c :: [Nat])
- data ReorderOk (a :: [Nat]) (b :: [Nat]) (c :: Bool)
- squeeze :: [Int] -> [Int]
- data Squeeze (b :: [a]) (c :: [a])
- data Min (b :: a) (c :: a) (d :: a)
- data Max (b :: a) (c :: a) (d :: a)
- minimum :: [Int] -> Int
- data Minimum (b :: [a]) (c :: a)
- isFin :: Int -> Int -> Bool
- data IsFin (a :: Nat) (b :: Nat) (c :: Bool)
- isFins :: [Int] -> [Int] -> Bool
- data IsFins (a :: [Nat]) (b :: [Nat]) (c :: Bool)
- isDim :: Int -> [Int] -> Bool
- data IsDim (a :: Nat) (b :: [Nat]) (c :: Bool)
- isDims :: [Int] -> [Int] -> Bool
- data IsDims (a :: [Nat]) (b :: [Nat]) (c :: Bool)
- lastPos :: Int -> [Int] -> Int
- data LastPos (a :: Nat) (b :: [Nat]) (c :: Nat)
- minDim :: [Int] -> [Int]
- data MinDim (a :: [Nat]) (b :: [Nat])
- data EnumFromTo (a :: Nat) (b :: Nat) (c :: [Nat])
- data Foldl' (c :: b -> a -> Exp b) (d :: b) (e :: t a) (f :: b)
- data GetIndex (b :: Nat) (c :: [a]) (d :: Maybe a)
- data SetIndex (b :: Nat) (c :: a) (d :: [a]) (e :: [a])
- getDim :: Int -> [Int] -> Int
- data GetDim (a :: Nat) (b :: [Nat]) (c :: Nat)
- modifyDim :: Int -> (Int -> Int) -> [Int] -> [Int]
- data ModifyDim (a :: Nat) (b :: Nat -> Exp Nat) (c :: [Nat]) (d :: [Nat])
- incAt :: Int -> [Int] -> [Int]
- data IncAt (a :: Nat) (b :: [Nat]) (c :: [Nat])
- decAt :: Int -> [Int] -> [Int]
- data DecAt (a :: Nat) (b :: [Nat]) (c :: [Nat])
- setDim :: Int -> Int -> [Int] -> [Int]
- data SetDim (a :: Nat) (b :: Nat) (c :: [Nat]) (d :: [Nat])
- takeDim :: Int -> Int -> [Int] -> [Int]
- data TakeDim (a :: Nat) (b :: Nat) (c :: [Nat]) (d :: [Nat])
- dropDim :: Int -> Int -> [Int] -> [Int]
- data DropDim (a :: Nat) (b :: Nat) (c :: [Nat]) (d :: [Nat])
- deleteDim :: Int -> [Int] -> [Int]
- data DeleteDim (a :: Nat) (b :: [Nat]) (c :: [Nat])
- insertDim :: Int -> Int -> [Int] -> [Int]
- data InsertDim (a :: Nat) (b :: Nat) (c :: [Nat]) (d :: [Nat])
- data InsertOk (a :: Nat) (b :: [Nat]) (c :: [Nat]) (d :: Bool)
- data SliceOk (a :: Nat) (b :: Nat) (c :: Nat) (d :: [Nat]) (e :: Bool)
- data SlicesOk (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) (d :: [Nat]) (e :: Bool)
- concatenate :: Int -> [Int] -> [Int] -> [Int]
- data Concatenate (a :: Nat) (b :: [Nat]) (c :: [Nat]) (d :: [Nat])
- data ConcatenateOk (a :: Nat) (b :: [Nat]) (c :: [Nat]) (d :: Bool)
- getDims :: [Int] -> [Int] -> [Int]
- data GetDims (a :: [Nat]) (b :: [Nat]) (c :: [Nat])
- getLastPositions :: [Int] -> [Int] -> [Int]
- data GetLastPositions (a :: [Nat]) (b :: [Nat]) (c :: [Nat])
- modifyDims :: [Int] -> [Int -> Int] -> [Int] -> [Int]
- insertDims :: [Int] -> [Int] -> [Int] -> [Int]
- data InsertDims (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) (d :: [Nat])
- preDeletePositions :: [Int] -> [Int]
- data PreDeletePositions (a :: [Nat]) (b :: [Nat])
- preInsertPositions :: [Int] -> [Int]
- data PreInsertPositions (a :: [Nat]) (b :: [Nat])
- setDims :: [Int] -> [Int] -> [Int] -> [Int]
- data SetDims (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) (d :: [Nat])
- deleteDims :: [Int] -> [Int] -> [Int]
- data DeleteDims (a :: [Nat]) (b :: [Nat]) (c :: [Nat])
- dropDims :: [Int] -> [Int] -> [Int] -> [Int]
- data DropDims (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) (d :: [Nat])
- concatDims :: [Int] -> Int -> [Int] -> [Int]
- data ConcatDims (a :: [Nat]) (b :: Nat) (c :: [Nat]) (d :: [Nat])
- unconcatDimsIndex :: [Int] -> Int -> [Int] -> [Int] -> [Int]
- reverseIndex :: [Int] -> [Int] -> [Int] -> [Int]
- rotate :: Int -> [a] -> [a]
- rotateIndex :: Int -> Int -> [Int] -> [Int] -> [Int]
- rotatesIndex :: [Int] -> [Int] -> [Int] -> [Int] -> [Int]
- isDiag :: Eq a => [a] -> Bool
- expandWindows :: [Int] -> [Int] -> [Int]
- data ExpandWindows (a :: [Nat]) (b :: [Nat]) (c :: [Nat])
- indexWindows :: Int -> [Int] -> [Int]
- dimWindows :: [Int] -> [Int] -> [Int]
- data DimWindows (a :: [Nat]) (b :: [Nat]) (c :: [Nat])
- type family Eval (e :: Exp a) :: a
- data ((b :: [a]) ++ (c :: [a])) (d :: [a])
Type-level Nat
A value-level witness for a type-level natural number. This is commonly
referred to as a singleton type, as for each n
, there is a single value
that inhabits the type
(aside from bottom).SNat
n
The definition of SNat
is intentionally left abstract. To obtain an SNat
value, use one of the following:
- The
natSing
method ofKnownNat
. - The
SNat
pattern synonym. - The
withSomeSNat
function, which creates anSNat
from aNatural
number.
Since: base-4.18.0.0
Instances
TestCoercion SNat | Since: base-4.18.0.0 |
Defined in GHC.TypeNats | |
TestEquality SNat | Since: base-4.18.0.0 |
Defined in GHC.TypeNats | |
Show (SNat n) | Since: base-4.18.0.0 |
Eq (SNat n) | Since: base-4.19.0.0 |
Ord (SNat n) | Since: base-4.19.0.0 |
pattern SNat :: () => KnownNat n => SNat n #
A explicitly bidirectional pattern synonym relating an SNat
to a
KnownNat
constraint.
As an expression: Constructs an explicit
value from an
implicit SNat
n
constraint:KnownNat
n
SNat @n ::KnownNat
n =>SNat
n
As a pattern: Matches on an explicit
value bringing
an implicit SNat
n
constraint into scope:KnownNat
n
f :: SNat
n -> ..
f SNat = {- SNat n in scope -}
Since: base-4.18.0.0
valueOf :: forall (n :: Nat). KnownNat n => Int Source #
Get the value of a type level Nat. Use with explicit type application
>>>
valueOf @42
42
Type-level [Nat]
data SNats (ns :: [Nat]) Source #
A value-level witness for a type-level list of natural numbers.
Obtain an SNats value using:
- The natsSing method of KnownNats
- The SNats pattern
- The withSomeSNats function
>>>
:t SNats @[2,3,4]
SNats @[2,3,4] :: KnownNats [2, 3, 4] => SNats [2, 3, 4]>>>
SNats @[2,3,4]
SNats @[2, 3, 4]
pattern SNats :: () => KnownNats ns => SNats ns Source #
A explicitly bidirectional pattern synonym relating an SNats
to a KnownNats
constraint.
As an expression: Constructs an explicit SNats
ns value from an implicit KnownNats
ns constraint:
SNat @n :: KnownNat n => SNat n
As a pattern: Matches on an explicit SNats n value bringing an implicit KnownNats n constraint into scope:
f :: SNats ns -> .. f SNat = {- KnownNats ns in scope -}
or, if you need to both bring the KnownNats into scope and reuse the SNats input:
f (SNats :: SNats s) = g (SNats @s)
fromSNats :: forall (s :: [Nat]). SNats s -> [Nat] Source #
Return the value-level list of naturals in an SNats ns value.
>>>
fromSNats (SNats @[2,3,4])
[2,3,4]
class KnownNats (ns :: [Nat]) where Source #
Reflect a list of naturals.
>>>
natsSing @'[2]
SNats @'[2]
natVals :: forall (ns :: [Nat]) proxy. KnownNats ns => proxy ns -> [Nat] Source #
Obtain a value-level list of naturals from a type-level proxy
>>>
natVals (SNats @[2,3,4])
[2,3,4]
withKnownNats :: forall (ns :: [Nat]) r. SNats ns -> (KnownNats ns => r) -> r Source #
Convert an explicit SNats ns value into an implicit KnownNats ns constraint.
someNatVals :: [Nat] -> SomeNats Source #
Promote a list of naturals to unknown type-level
withSomeSNats :: [Nat] -> (forall (s :: [Nat]). SNats s -> r) -> r Source #
Convert a list of naturals into an SNats ns value, where ns is a fresh type-level list of naturals.
Shape
valuesOf :: forall (s :: [Nat]). KnownNats s => [Int] Source #
The value of a KnownNats
.
>>>
valuesOf @[2,3,4]
[2,3,4]
rankOf :: forall (s :: [Nat]). KnownNats s => Int Source #
The rank (or length) of a KnownNats.
>>>
rankOf @[2,3,4]
3
sizeOf :: forall (s :: [Nat]). KnownNats s => Int Source #
The size (or product) of a KnownNats.
>>>
sizeOf @[2,3,4]
24
Fin most often represents a (finite) zero-based index for a single dimension (of a multi-dimensioned hyper-rectangular array).
fin :: forall (n :: Nat). KnownNat n => Int -> Fin n Source #
Construct a Fin.
Errors on out-of-bounds
>>>
fin @2 1
1
>>>
fin @2 2
*** Exception: value outside bounds ...
safeFin :: forall (n :: Nat). KnownNat n => Int -> Maybe (Fin n) Source #
Construct a Fin safely.
>>>
safeFin 1 :: Maybe (Fin 2)
Just 1
>>>
safeFin 2 :: Maybe (Fin 2)
Nothing
newtype Fins (s :: k) Source #
Fins most often represents (finite) indexes for multiple dimensions (of a multi-dimensioned hyper-rectangular array).
Constructors
UnsafeFins | |
fins :: forall (s :: [Nat]). KnownNats s => [Int] -> Fins s Source #
Construct a Fins.
Errors on out-of-bounds
>>>
fins @[2,3,4] [1,2,3]
[1,2,3]
>>>
fins @[2,3,4] [1,2,5]
*** Exception: value outside bounds ...
safeFins :: forall (s :: [Nat]). KnownNats s => [Int] -> Maybe (Fins s) Source #
Construct a Fins safely.
>>>
safeFins [1,2,3] :: Maybe (Fins [2,3,4])
Just [1,2,3]
>>>
safeFins [2] :: Maybe (Fins '[2])
Nothing
Shape Operators at value- and type- level.
data Range (a :: Nat) (b :: [Nat]) Source #
Enumerate a range of rank n
>>>
:k! Eval (Range 0)
... = '[]
>>>
:k! Eval (Range 3)
... = [0, 1, 2]
rerank :: Int -> [Int] -> [Int] Source #
Create a new rank by adding ones to the left, if the new rank is greater, or combining dimensions (from left to right) into rows, if the new rank is lower.
>>>
rerank 4 [2,3,4]
[1,2,3,4]>>>
rerank 2 [2,3,4]
[6,4]
data Rerank (a :: Nat) (b :: [Nat]) (c :: [Nat]) Source #
Create a new rank by adding ones to the left, if the new rank is greater, or combining dimensions (from left to right) into rows, if the new rank is lower.
>>>
:k! Eval (Rerank 4 [2,3,4])
... = [1, 2, 3, 4]>>>
:k! Eval (Rerank 2 [2,3,4])
... = [6, 4]
data DimsOf (a :: [Nat]) (b :: [Nat]) Source #
Enumerate the dimensions of a shape.
>>>
:k! Eval (DimsOf [2,3,4])
... = [0, 1, 2]
endDimsOf :: [Int] -> [Int] -> [Int] Source #
Enumerate the final dimensions of a shape.
>>>
endDimsOf [1,0] [2,3,4]
[2,1]
data EndDimsOf (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) Source #
Enumerate the final dimensions of a shape.
>>>
:k! Eval (EndDimsOf [1,0] [2,3,4])
... = [2, 1]
Total number of elements (if the list is the shape of a hyper-rectangular array).
>>>
size [2,3,4]
24
data Size (a :: [Nat]) (b :: Nat) Source #
Total number of elements (if the list is the shape of a hyper-rectangular array).
>>>
:k! (Eval (Size [2,3,4]))
... = 24
flatten :: [Int] -> [Int] -> Int Source #
Convert from a n-dimensional shape list index to a flat index, which, technically is the lexicographic position of the position in a row-major array.
>>>
flatten [2,3,4] [1,1,1]
17
>>>
flatten [] [1,1,1]
0
shapen :: [Int] -> Int -> [Int] Source #
Convert from a flat index to a shape index.
>>>
shapen [2,3,4] 17
[1,1,1]
asSingleton :: [Int] -> [Int] Source #
Convert a scalar to a dimensioned shape
>>>
asSingleton []
[1]>>>
asSingleton [2,3,4]
[2,3,4]
data AsSingleton (a :: [Nat]) (b :: [Nat]) Source #
Convert a scalar to a dimensioned shape >>> :k! Eval (AsSingleton '[]) ... = '[1] >>> :k! Eval (AsSingleton [2,3,4]) ... = [2, 3, 4]
Instances
type Eval (AsSingleton xs :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape |
asScalar :: [Int] -> [Int] Source #
Convert a (potentially) [1] dimensioned shape to a scalar shape
>>>
asScalar [1]
[]>>>
asScalar [2,3,4]
[2,3,4]
data AsScalar (a :: [Nat]) (b :: [Nat]) Source #
Convert a (potentially) [1] dimensioned shape to a scalar shape >>> :k! Eval (AsScalar '[1]) ... = '[] >>> :k! Eval (AsScalar [2,3,4]) ... = [2, 3, 4]
isSubset :: [Int] -> [Int] -> Bool Source #
Check if a shape is a subset (<=) another shape after reranking.
>>>
isSubset [2,3,4] [2,3,4]
True
>>>
isSubset [1,2] [2,3,4]
True
>>>
isSubset [2,1] [1]
False
data IsSubset (a :: [Nat]) (b :: [Nat]) (c :: Bool) Source #
Check if a shape is a subset (<=) another shape after reranking.
>>>
:k! Eval (IsSubset [2,3,4] [2,3,4])
... = True
>>>
:k! Eval (IsSubset [1,2] [2,3,4])
... = True
>>>
:k! Eval (IsSubset [2,1] '[1])
... = False
exceptDims :: [Int] -> [Int] -> [Int] Source #
Compute dimensions for a shape other than the supplied dimensions.
>>>
exceptDims [1,2] [2,3,4]
[0]
data ExceptDims (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) Source #
Compute dimensions for a shape other than the supplied dimensions.
>>>
:k! Eval (ExceptDims [1,2] [2,3,4])
... = '[0]
Instances
type Eval (ExceptDims ds s :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape type Eval (ExceptDims ds s :: [Nat] -> Type) = Eval (DeleteDims ds =<< EnumFromTo 0 (Eval (Eval (Rank s) - 1))) |
reorder :: [Int] -> [Int] -> [Int] Source #
Reorder the dimensions of shape according to a list of positions.
>>>
reorder [2,3,4] [2,0,1]
[4,2,3]
data Reorder (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) Source #
Reorder the dimensions of shape according to a list of positions.
>>>
:k! Eval (Reorder [2,3,4] [2,0,1])
... = [4, 2, 3]
data ReorderOk (a :: [Nat]) (b :: [Nat]) (c :: Bool) Source #
Test if a Reorder is valid.
>>>
:k! Eval (ReorderOk [2,3,4] [0,1])
... = False
data Squeeze (b :: [a]) (c :: [a]) Source #
Remove 1's from a list.
>>>
:k! (Eval (Squeeze [0,1,2,3]))
... = [0, 2, 3]
Primitives
data Min (b :: a) (c :: a) (d :: a) Source #
Minimum of two type values.
>>>
:k! Eval (Min 0 1)
... = 0
data Max (b :: a) (c :: a) (d :: a) Source #
Maximum of two type values.
>>>
:k! Eval (Max 0 1)
... = 1
minimum :: [Int] -> Int Source #
minimum of a list
>>>
S.minimum []
*** Exception: zero-ranked ...>>>
S.minimum [2,3,4]
2
data Minimum (b :: [a]) (c :: a) Source #
minimum of a list
>>>
:k! Eval (Minimum '[])
... = (TypeError ...)
>>>
:k! Eval (Minimum [2,3,4])
... = 2
Position
isFin :: Int -> Int -> Bool Source #
Check if i is a valid Fin (aka in-bounds index of a dimension)
>>>
isFin 0 2
True>>>
isFin 2 2
False
data IsFin (a :: Nat) (b :: Nat) (c :: Bool) Source #
Check if i is a valid Fin (aka in-bounds index of a dimension)
>>>
:k! Eval (IsFin 0 2)
... = True>>>
:k! Eval (IsFin 2 2)
... = False
isFins :: [Int] -> [Int] -> Bool Source #
Check if i is a valid Fins (aka in-bounds index of a Shape)
>>>
isFins [0,1] [2,2]
True>>>
isFins [0,1] [2,1]
False
data IsFins (a :: [Nat]) (b :: [Nat]) (c :: Bool) Source #
Check if i is a valid Fins (aka in-bounds index of a Shape)
>>>
:k! Eval (IsFins [0,1] [2,2])
... = True>>>
:k! Eval (IsFins [0,1] [2,1])
... = False
isDim :: Int -> [Int] -> Bool Source #
Is a value a valid dimension of a shape.
>>>
isDim 2 [2,3,4]
True>>>
isDim 0 []
True
data IsDim (a :: Nat) (b :: [Nat]) (c :: Bool) Source #
Is a value a valid dimension of a shape.
>>>
:k! Eval (IsDim 2 [2,3,4])
... = True>>>
:k! Eval (IsDim 0 '[])
... = True
isDims :: [Int] -> [Int] -> Bool Source #
Are values valid dimensions of a shape.
>>>
isDims [2,1] [2,3,4]
True>>>
isDims [0] []
True
data IsDims (a :: [Nat]) (b :: [Nat]) (c :: Bool) Source #
Are values valid dimensions of a shape.
>>>
:k! Eval (IsDims [2,1] [2,3,4])
... = True>>>
:k! Eval (IsDims '[0] '[])
... = True
lastPos :: Int -> [Int] -> Int Source #
Get the last position of a dimension of a shape.
>>>
lastPos 2 [2,3,4]
3>>>
lastPos 0 []
0
data LastPos (a :: Nat) (b :: [Nat]) (c :: Nat) Source #
Get the last position of a dimension of a shape.
>>>
:k! Eval (LastPos 2 [2,3,4])
... = 3>>>
:k! Eval (LastPos 0 '[])
... = 0
minDim :: [Int] -> [Int] Source #
Get the minimum dimension as a singleton dimension.
>>>
minDim [2,3,4]
[2]>>>
minDim []
[]
data MinDim (a :: [Nat]) (b :: [Nat]) Source #
Get the minimum dimension as a singleton dimension.
>>>
:k! Eval (MinDim [2,3,4])
... = '[2]>>>
:k! Eval (MinDim '[])
... = '[]
combinators
data EnumFromTo (a :: Nat) (b :: Nat) (c :: [Nat]) Source #
Enumerate between two Nats
>>>
:k! Eval (EnumFromTo 0 3)
... = [0, 1, 2, 3]
Instances
type Eval (EnumFromTo a b :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape |
data Foldl' (c :: b -> a -> Exp b) (d :: b) (e :: t a) (f :: b) Source #
Left fold.
>>>
:k! Eval (Foldl' (Fcf.+) 0 [1,2,3])
... = 6
single dimension
data GetIndex (b :: Nat) (c :: [a]) (d :: Maybe a) Source #
Get an element at a given index.
>>>
:kind! Eval (GetIndex 2 [2,3,4])
... = Just 4
data SetIndex (b :: Nat) (c :: a) (d :: [a]) (e :: [a]) #
Modify an element at a given index.
The list is unchanged if the index is out of bounds.
Example
>>>
:kind! Eval (SetIndex 2 7 [1,2,3])
Eval (SetIndex 2 7 [1,2,3]) :: [Natural] = [1, 2, 7]
getDim :: Int -> [Int] -> Int Source #
Get the dimension of a shape at the supplied index. Error if out-of-bounds.
>>>
getDim 1 [2,3,4]
3>>>
getDim 3 [2,3,4]
*** Exception: getDim outside bounds ...>>>
getDim 0 []
1
data GetDim (a :: Nat) (b :: [Nat]) (c :: Nat) Source #
Get the dimension of a shape at the supplied index. Error if out-of-bounds or non-computable (usually unknown to the compiler).
>>>
:k! Eval (GetDim 1 [2,3,4])
... = 3>>>
:k! Eval (GetDim 3 [2,3,4])
... = (TypeError ...)>>>
:k! Eval (GetDim 0 '[])
... = 1
modifyDim :: Int -> (Int -> Int) -> [Int] -> [Int] Source #
modify an index at a specific dimension. Errors if out of bounds.
>>>
modifyDim 0 (+1) [0,1,2]
[1,1,2]>>>
modifyDim 0 (+1) []
[2]
data ModifyDim (a :: Nat) (b :: Nat -> Exp Nat) (c :: [Nat]) (d :: [Nat]) Source #
modify an index at a specific dimension. Errors if out of bounds.
>>>
:k! Eval (ModifyDim 0 ((Fcf.+) 1) [0,1,2])
... = [1, 1, 2]
incAt :: Int -> [Int] -> [Int] Source #
Increment the index at a dimension of a shape by 1. Scalars turn into singletons.
>>>
incAt 1 [2,3,4]
[2,4,4]>>>
incAt 0 []
[2]
data IncAt (a :: Nat) (b :: [Nat]) (c :: [Nat]) Source #
Increment the index at a dimension of a shape by 1. Scalars turn into singletons.
>>>
:k! Eval (IncAt 1 [2,3,4])
... = [2, 4, 4]>>>
:k! Eval (IncAt 0 '[])
... = '[2]
decAt :: Int -> [Int] -> [Int] Source #
Decrement the index at a dimension os a shape by 1.
>>>
decAt 1 [2,3,4]
[2,2,4]
data DecAt (a :: Nat) (b :: [Nat]) (c :: [Nat]) Source #
Decrement the index at a dimension of a shape by 1.
>>>
:k! Eval (DecAt 1 [2,3,4])
... = [2, 2, 4]
setDim :: Int -> Int -> [Int] -> [Int] Source #
replace an index at a specific dimension, or transform a scalar into being 1-dimensional.
>>>
setDim 0 1 [2,3,4]
[1,3,4]>>>
setDim 0 3 []
[3]
data SetDim (a :: Nat) (b :: Nat) (c :: [Nat]) (d :: [Nat]) Source #
replace an index at a specific dimension.
>>>
:k! Eval (SetDim 0 1 [2,3,4])
... = [1, 3, 4]
takeDim :: Int -> Int -> [Int] -> [Int] Source #
Take along a dimension.
>>>
takeDim 0 1 [2,3,4]
[1,3,4]
data TakeDim (a :: Nat) (b :: Nat) (c :: [Nat]) (d :: [Nat]) Source #
Take along a dimension.
>>>
:k! Eval (TakeDim 0 1 [2,3,4])
... = [1, 3, 4]
dropDim :: Int -> Int -> [Int] -> [Int] Source #
Drop along a dimension.
>>>
dropDim 2 1 [2,3,4]
[2,3,3]
data DropDim (a :: Nat) (b :: Nat) (c :: [Nat]) (d :: [Nat]) Source #
Drop along a dimension.
>>>
:k! Eval (DropDim 2 1 [2,3,4])
... = [2, 3, 3]
deleteDim :: Int -> [Int] -> [Int] Source #
delete the i'th dimension. No effect on a scalar.
>>>
deleteDim 1 [2, 3, 4]
[2,4]>>>
deleteDim 2 []
[]
data DeleteDim (a :: Nat) (b :: [Nat]) (c :: [Nat]) Source #
delete the i'th dimension
>>>
:k! Eval (DeleteDim 1 [2, 3, 4])
... = [2, 4]>>>
:k! Eval (DeleteDim 1 '[])
... = '[]
insertDim :: Int -> Int -> [Int] -> [Int] Source #
Insert a new dimension at a position (or at the end if > rank).
>>>
insertDim 1 3 [2,4]
[2,3,4]>>>
insertDim 0 4 []
[4]
data InsertDim (a :: Nat) (b :: Nat) (c :: [Nat]) (d :: [Nat]) Source #
Insert a new dimension at a position (or at the end if > rank).
>>>
:k! Eval (InsertDim 1 3 [2,4])
... = [2, 3, 4]>>>
:k! Eval (InsertDim 0 4 '[])
... = '[4]
data InsertOk (a :: Nat) (b :: [Nat]) (c :: [Nat]) (d :: Bool) Source #
Is a slice ok constraint.
>>>
:k! Eval (InsertOk 2 [2,3,4] [2,3])
... = True>>>
:k! Eval (InsertOk 0 '[] '[])
... = True
data SliceOk (a :: Nat) (b :: Nat) (c :: Nat) (d :: [Nat]) (e :: Bool) Source #
Is a slice ok?
>>>
:k! Eval (SliceOk 1 1 2 [2,3,4])
... = True
data SlicesOk (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) (d :: [Nat]) (e :: Bool) Source #
Are slices ok?
>>>
:k! Eval (SlicesOk '[1] '[1] '[2] [2,3,4])
... = True
concatenate :: Int -> [Int] -> [Int] -> [Int] Source #
concatenate two arrays at dimension i
Bespoke logic for scalars.
>>>
concatenate 1 [2,3,4] [2,3,4]
[2,6,4]>>>
concatenate 0 [3] []
[4]>>>
concatenate 0 [] [3]
[4]>>>
concatenate 0 [] []
[2]
data Concatenate (a :: Nat) (b :: [Nat]) (c :: [Nat]) (d :: [Nat]) Source #
concatenate two arrays at dimension i
Bespoke logic for scalars.
>>>
:k! Eval (Concatenate 1 [2,3,4] [2,3,4])
... = [2, 6, 4]>>>
:k! Eval (Concatenate 0 '[3] '[])
... = '[4]>>>
:k! Eval (Concatenate 0 '[] '[3])
... = '[4]>>>
:k! Eval (Concatenate 0 '[] '[])
... = '[2]
data ConcatenateOk (a :: Nat) (b :: [Nat]) (c :: [Nat]) (d :: Bool) Source #
Concatenate is Ok if ranks are the same and the non-indexed portion of the shapes are the same.
Instances
type Eval (ConcatenateOk i s0 s1 :: Bool -> Type) Source # | |
Defined in Harpie.Shape type Eval (ConcatenateOk i s0 s1 :: Bool -> Type) = Eval (IsDim i s0) && (Eval (IsDim i s1) && (Eval (LiftM2 (TyEq :: [Nat] -> [Nat] -> Bool -> Type) (DeleteDim i s0) (DeleteDim i s1)) && Eval (LiftM2 (TyEq :: Natural -> Natural -> Bool -> Type) ((Rank :: [Nat] -> Natural -> Type) =<< AsSingleton s0) ((Rank :: [Nat] -> Natural -> Type) =<< AsSingleton s1)))) |
multiple dimension
getDims :: [Int] -> [Int] -> [Int] Source #
Get dimensions of a shape.
>>>
getDims [2,0] [2,3,4]
[4,2]>>>
getDims [2] []
[]
data GetDims (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) Source #
Get dimensions of a shape.
>>>
:k! Eval (GetDims [2,0] [2,3,4])
... = [4, 2]>>>
:k! Eval (GetDims '[2] '[])
... = '[(TypeError ...)]
getLastPositions :: [Int] -> [Int] -> [Int] Source #
Get the index of the last position in the selected dimensions of a shape. Errors on a 0-dimension.
>>>
getLastPositions [2,0] [2,3,4]
[3,1]>>>
getLastPositions [0] [0]
[-1]
data GetLastPositions (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) Source #
Get the index of the last position in the selected dimensions of a shape. Errors on a 0-dimension.
>>>
:k! Eval (GetLastPositions [2,0] [2,3,4])
... = [3, 1]
modifyDims :: [Int] -> [Int -> Int] -> [Int] -> [Int] Source #
modify dimensions of a shape with (separate) functions.
>>>
modifyDims [0,1] [(+1), (+5)] [2,3,4]
[3,8,4]
insertDims :: [Int] -> [Int] -> [Int] -> [Int] Source #
Insert a list of dimensions according to dimensions and positions. Note that the list of positions references the final shape and not the initial shape.
>>>
insertDims [0] [5] []
[5]>>>
insertDims [1,0] [3,2] [4]
[2,3,4]
data InsertDims (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) (d :: [Nat]) Source #
insert a list of dimensions according to dimension,position tuple lists. Note that the list of positions references the final shape and not the initial shape.
>>>
:k! Eval (InsertDims '[0] '[5] '[])
... = '[5]>>>
:k! Eval (InsertDims [1,0] [3,2] '[4])
... = [2, 3, 4]
Instances
type Eval (InsertDims ds xs s :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape |
preDeletePositions :: [Int] -> [Int] Source #
Convert a list of positions that reference deletions according to a final shape to 1 that references deletions relative to an initial shape.
To delete the positions [1,2,5] from a list, for example, you need to delete position 1, (arriving at a 4 element list), then position 1, arriving at a 3 element list, and finally position 3.
>>>
preDeletePositions [1,2,5]
[1,1,3]
>>>
preDeletePositions [1,2,0]
[1,1,0]
data PreDeletePositions (a :: [Nat]) (b :: [Nat]) Source #
Convert a list of positions that reference deletions according to a final shape to 1 that references deletions relative to an initial shape.
To delete the positions [1,2,5] from a list, for example, you need to delete position 1, (arriving at a 4 element list), then position 1, arriving at a 3 element list, and finally position 3.
>>>
:k! Eval (PreDeletePositions [1,2,5])
... = [1, 1, 3]
>>>
:k! Eval (PreDeletePositions [1,2,0])
... = [1, 1, 0]
Instances
type Eval (PreDeletePositions xs :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape |
preInsertPositions :: [Int] -> [Int] Source #
Convert a list of position that reference insertions according to a final shape to 1 that references list insertions relative to an initial shape.
To insert into positions [1,2,0] from a list, starting from a 2 element list, for example, you need to insert at position 0, (arriving at a 3 element list), then position 1, arriving at a 4 element list, and finally position 0.
preInsertPositions == reverse . preDeletePositions . reverse >> preInsertPositions [1,2,5]
- 1,2,5
>>>
preInsertPositions [1,2,0]
[0,1,0]
data PreInsertPositions (a :: [Nat]) (b :: [Nat]) Source #
Convert a list of position that reference insertions according to a final shape to 1 that references list insertions relative to an initial shape.
To insert into positions [1,2,0] from a list, starting from a 2 element list, for example, you need to insert at position 0, (arriving at a 3 element list), then position 1, arriving at a 4 element list, and finally position 0.
preInsertPositions == reverse . preDeletePositions . reverse >> :k! Eval (PreInsertPositions [1,2,5])
... = [1, 2, 5]
>>>
:k! Eval (PreInsertPositions [1,2,0])
... = [0, 1, 0]
Instances
type Eval (PreInsertPositions xs :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape |
setDims :: [Int] -> [Int] -> [Int] -> [Int] Source #
Set dimensions of a shape.
>>>
setDims [0,1] [1,5] [2,3,4]
[1,5,4]
>>>
setDims [0] [3] []
[3]
data SetDims (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) (d :: [Nat]) Source #
Set dimensions of a shape.
>>>
:k! Eval (SetDims [0,1] [1,5] [2,3,4])
... = [1, 5, 4]
>>>
:k! Eval (SetDims '[0] '[3] '[])
... = '[3]
deleteDims :: [Int] -> [Int] -> [Int] Source #
drop dimensions of a shape according to a list of positions (where position refers to the initial shape)
>>>
deleteDims [1,0] [2, 3, 4]
[4]
data DeleteDims (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) Source #
drop dimensions of a shape according to a list of positions (where position refers to the initial shape)
>>>
:k! Eval (DeleteDims [1,0] [2, 3, 4])
... = '[4]
Instances
type Eval (DeleteDims xs ds :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape |
dropDims :: [Int] -> [Int] -> [Int] -> [Int] Source #
Drop a number of elements of a shape along the supplied dimensions.
>>>
dropDims [0,2] [1,3] [2,3,4]
[1,3,1]
data DropDims (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) (d :: [Nat]) Source #
Drop a number of elements of a shape along the supplied dimensions.
>>>
:k! Eval (DropDims [0,2] [1,3] [2,3,4])
... = [1, 3, 1]
concatDims :: [Int] -> Int -> [Int] -> [Int] Source #
Concatenate and replace dimensions, creating a new dimension at the supplied postion.
>>>
concatDims [0,1] 1 [2,3,4]
[4,6]
data ConcatDims (a :: [Nat]) (b :: Nat) (c :: [Nat]) (d :: [Nat]) Source #
Drop a number of elements of a shape along the supplied dimensions.
>>>
:k! Eval (ConcatDims [0,1] 1 [2,3,4])
... = [4, 6]
Instances
type Eval (ConcatDims ds n s :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape |
value-only operations
unconcatDimsIndex :: [Int] -> Int -> [Int] -> [Int] -> [Int] Source #
Unconcatenate and reinsert dimensions for an index.
>>>
unconcatDimsIndex [0,1] 1 [4,6] [2,3]
[0,3,2]
reverseIndex :: [Int] -> [Int] -> [Int] -> [Int] Source #
reverse an index along specific dimensions.
>>>
reverseIndex [0] [2,3,4] [0,1,2]
[1,1,2]
rotate :: Int -> [a] -> [a] Source #
rotate a list
>>>
rotate 1 [0..3]
[1,2,3,0]>>>
rotate (-1) [0..3]
[3,0,1,2]
rotateIndex :: Int -> Int -> [Int] -> [Int] -> [Int] Source #
rotate an index along a specific dimension.
>>>
rotateIndex 0 1 [2,3,4] [0,1,2]
[1,1,2]
rotatesIndex :: [Int] -> [Int] -> [Int] -> [Int] -> [Int] Source #
rotate an index along specific dimensions.
>>>
rotatesIndex [0] [1] [2,3,4] [0,1,2]
[1,1,2]
isDiag :: Eq a => [a] -> Bool Source #
Test whether an index is a diagonal one.
>>>
isDiag [2,2,2]
True>>>
isDiag [1,2]
False
windowed
expandWindows :: [Int] -> [Int] -> [Int] Source #
Expanded shape of a windowed array
>>>
expandWindows [2,2] [4,3,2]
[3,2,2,2,2]
data ExpandWindows (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) Source #
Expanded shape of a windowed array
>>>
:k! Eval (ExpandWindows [2,2] [4,3,2])
... = [3, 2, 2, 2, 2]
indexWindows :: Int -> [Int] -> [Int] Source #
Index into windows of an expanded windowed array, given a rank of the windows.
>>>
indexWindows 2 [0,1,2,1,1]
[2,2,1]
dimWindows :: [Int] -> [Int] -> [Int] Source #
Dimensions of a windowed array.
>>>
dimWindows [2,2] [2,3,4]
[0,1,2]
data DimWindows (a :: [Nat]) (b :: [Nat]) (c :: [Nat]) Source #
Dimensions of a windowed array.
>>>
:k! Eval (DimWindows [2,2] [4,3,2])
... = [0, 1, 2]
Fcf re-exports
type family Eval (e :: Exp a) :: a #
Expression evaluator.
Instances
type Eval (Size xs :: Nat -> Type) Source # | |
type Eval (Not 'False) | |
Defined in Fcf.Data.Bool | |
type Eval (Not 'True) | |
Defined in Fcf.Data.Bool | |
type Eval (Constraints (a ': as) :: Constraint -> Type) | |
Defined in Fcf.Utils | |
type Eval (Constraints ('[] :: [Constraint])) | |
Defined in Fcf.Utils | |
type Eval (MEmpty_ :: a -> Type) | |
Defined in Fcf.Class.Monoid | |
type Eval (Sum ns :: Nat -> Type) | |
type Eval (Length ('[] :: [a]) :: Nat -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Length (a2 ': as) :: Nat -> Type) | |
type Eval (a * b :: Nat -> Type) | |
type Eval (a + b :: Nat -> Type) | |
type Eval (a - b :: Nat -> Type) | |
type Eval (a ^ b :: Nat -> Type) | |
type Eval (GetDim n xs :: Nat -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (LastPos d s :: Nat -> Type) Source # | |
type Eval (Rank xs :: Natural -> Type) Source # | |
type Eval (And lst :: Bool -> Type) | |
type Eval (Or lst :: Bool -> Type) | |
type Eval ('False && b :: Bool -> Type) | |
type Eval ('True && b :: Bool -> Type) | |
type Eval (a && 'False :: Bool -> Type) | |
type Eval (a && 'True :: Bool -> Type) | |
type Eval ('False || b :: Bool -> Type) | |
type Eval ('True || b :: Bool -> Type) | |
type Eval (a || 'False :: Bool -> Type) | |
type Eval (a || 'True :: Bool -> Type) | |
type Eval (IsJust ('Just _a) :: Bool -> Type) | |
type Eval (IsJust ('Nothing :: Maybe a) :: Bool -> Type) | |
type Eval (IsNothing ('Just _a) :: Bool -> Type) | |
type Eval (IsNothing ('Nothing :: Maybe a) :: Bool -> Type) | |
type Eval (Null ('[] :: [a]) :: Bool -> Type) | |
type Eval (Null (a2 ': as) :: Bool -> Type) | |
type Eval (a < b :: Bool -> Type) | |
type Eval (a <= b :: Bool -> Type) | |
type Eval (a > b :: Bool -> Type) | |
type Eval (a >= b :: Bool -> Type) | |
type Eval (IsDim d s :: Bool -> Type) Source # | |
type Eval (IsDims ds s :: Bool -> Type) Source # | |
type Eval (IsFin x d :: Bool -> Type) Source # | |
type Eval (IsFins xs ds :: Bool -> Type) Source # | |
type Eval (IsSubset xs ys :: Bool -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (ReorderOk ds xs :: Bool -> Type) Source # | |
type Eval (Join e :: a -> Type) | |
type Eval (Pure x :: a -> Type) | |
Defined in Fcf.Combinators | |
type Eval (Error msg :: a -> Type) | |
type Eval (TError msg :: a -> Type) | |
type Eval (Minimum (x ': xs) :: a -> Type) Source # | |
type Eval (Minimum ('[] :: [a]) :: a -> Type) Source # | |
type Eval (Compare ('Left _a :: Either a b) ('Right _b :: Either a b) :: Ordering -> Type) | |
type Eval (Compare ('Right _a :: Either a b) ('Left _b :: Either a b) :: Ordering -> Type) | |
type Eval (Compare ('Left a2 :: Either a1 b1) ('Left b2 :: Either a1 b1) :: Ordering -> Type) | |
type Eval (Compare ('Right a3 :: Either a2 a1) ('Right b :: Either a2 a1) :: Ordering -> Type) | |
type Eval (Compare 'EQ 'GT) | |
type Eval (Compare 'EQ 'LT) | |
type Eval (Compare 'GT 'EQ) | |
type Eval (Compare 'GT 'LT) | |
type Eval (Compare 'LT 'EQ) | |
type Eval (Compare 'LT 'GT) | |
type Eval (Compare a a :: Ordering -> Type) | |
type Eval (Compare ('Just _a) ('Nothing :: Maybe a) :: Ordering -> Type) | |
type Eval (Compare ('Nothing :: Maybe a) ('Just _b) :: Ordering -> Type) | |
type Eval (Compare ('Nothing :: Maybe a) ('Nothing :: Maybe a) :: Ordering -> Type) | |
type Eval (Compare ('Just a2) ('Just b) :: Ordering -> Type) | |
type Eval (Compare a b :: Ordering -> Type) | |
type Eval (Compare '(a3, a4) '(b1, b2) :: Ordering -> Type) | |
type Eval (Compare '(a4, a5, a6) '(b1, b2, b3) :: Ordering -> Type) | |
type Eval (Compare a b :: Ordering -> Type) | |
type Eval (Compare 'False 'True) | |
type Eval (Compare 'True 'False) | |
type Eval (Compare a a :: Ordering -> Type) | |
type Eval (Compare (_x ': _xs) ('[] :: [a]) :: Ordering -> Type) | |
type Eval (Compare (x ': xs) (y ': ys) :: Ordering -> Type) | |
type Eval (Compare ('[] :: [a]) (_y ': _ys) :: Ordering -> Type) | |
type Eval (Compare ('[] :: [a]) ('[] :: [a]) :: Ordering -> Type) | |
type Eval (Compare a b :: Ordering -> Type) | |
type Eval (a2 < b :: Bool -> Type) | |
type Eval (a2 <= b :: Bool -> Type) | |
type Eval (a2 > b :: Bool -> Type) | |
type Eval (a2 >= b :: Bool -> Type) | |
type Eval (IsLeft ('Left _a :: Either a b) :: Bool -> Type) | |
type Eval (IsLeft ('Right _a :: Either a b) :: Bool -> Type) | |
type Eval (IsRight ('Left _a :: Either a b) :: Bool -> Type) | |
type Eval (IsRight ('Right _a :: Either a b) :: Bool -> Type) | |
type Eval (Elem a2 as :: Bool -> Type) | |
type Eval (IsInfixOf xs ys :: Bool -> Type) | |
type Eval (IsPrefixOf xs ys :: Bool -> Type) | |
Defined in Fcf.Data.List | |
type Eval (IsSuffixOf xs ys :: Bool -> Type) | |
Defined in Fcf.Data.List | |
type Eval (ConcatenateOk i s0 s1 :: Bool -> Type) Source # | |
Defined in Harpie.Shape type Eval (ConcatenateOk i s0 s1 :: Bool -> Type) = Eval (IsDim i s0) && (Eval (IsDim i s1) && (Eval (LiftM2 (TyEq :: [Nat] -> [Nat] -> Bool -> Type) (DeleteDim i s0) (DeleteDim i s1)) && Eval (LiftM2 (TyEq :: Natural -> Natural -> Bool -> Type) ((Rank :: [Nat] -> Natural -> Type) =<< AsSingleton s0) ((Rank :: [Nat] -> Natural -> Type) =<< AsSingleton s1)))) | |
type Eval (InsertOk d s si :: Bool -> Type) Source # | |
type Eval (Concat xs :: a -> Type) | |
type Eval (x .<> y :: a -> Type) | |
Defined in Fcf.Class.Monoid | |
type Eval (FromMaybe _a ('Just b) :: a -> Type) | |
Defined in Fcf.Data.Common | |
type Eval (FromMaybe a2 ('Nothing :: Maybe a1) :: a1 -> Type) | |
type Eval (Fst '(a2, _b) :: a1 -> Type) | |
Defined in Fcf.Data.Common | |
type Eval (Snd '(_a, b) :: a2 -> Type) | |
Defined in Fcf.Data.Common | |
type Eval (Max a b :: k -> Type) Source # | |
type Eval (Min a b :: k -> Type) Source # | |
type Eval (All p lst :: Bool -> Type) | |
type Eval (Any p lst :: Bool -> Type) | |
type Eval (TyEq a b :: Bool -> Type) | |
type Eval (SliceOk d off l s :: Bool -> Type) Source # | |
type Eval (SlicesOk ds offs ls s :: Bool -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (UnBool fal tru 'False :: a -> Type) | |
type Eval (UnBool fal tru 'True :: a -> Type) | |
type Eval (ConstFn a2 _b :: a1 -> Type) | |
Defined in Fcf.Combinators | |
type Eval (f $ a3 :: a2 -> Type) | |
Defined in Fcf.Combinators | |
type Eval (f <$> e :: a2 -> Type) | |
Defined in Fcf.Combinators | |
type Eval (f <*> e :: a2 -> Type) | |
type Eval (k =<< e :: a2 -> Type) | |
type Eval (e >>= k :: a2 -> Type) | |
type Eval (Pure1 f x :: a2 -> Type) | |
Defined in Fcf.Combinators | |
type Eval (x & f :: a2 -> Type) | |
Defined in Fcf.Data.Function | |
type Eval (Case ms a :: k -> Type) | |
type Eval (UnMaybe y f ('Just x) :: a1 -> Type) | |
type Eval (UnMaybe y f ('Nothing :: Maybe a2) :: a1 -> Type) | |
type Eval (UnList y f xs :: a1 -> Type) | |
type Eval (FoldMap f ('Left _a :: Either a3 a1) :: a2 -> Type) | |
type Eval (FoldMap f ('Right x :: Either a3 a1) :: a2 -> Type) | |
type Eval (FoldMap f ('Just x) :: a2 -> Type) | |
type Eval (FoldMap f ('Nothing :: Maybe a1) :: a2 -> Type) | |
type Eval (FoldMap f (x ': xs) :: a2 -> Type) | |
type Eval (FoldMap f ('[] :: [a1]) :: a2 -> Type) | |
Defined in Fcf.Class.Foldable | |
type Eval (Uncurry f '(x, y) :: a2 -> Type) | |
Defined in Fcf.Data.Common | |
type Eval (Foldl' f y (x ': xs) :: a1 -> Type) Source # | |
type Eval (Foldl' f y ('[] :: [a2]) :: a1 -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (Foldr f y ('Left _a :: Either a3 a1) :: a2 -> Type) | |
type Eval (Foldr f y ('Right x :: Either a3 a1) :: a2 -> Type) | |
type Eval (Foldr f y ('Just x) :: a2 -> Type) | |
type Eval (Foldr f y ('Nothing :: Maybe a1) :: a2 -> Type) | |
type Eval (Foldr f y (x ': xs) :: a2 -> Type) | |
type Eval (Foldr f y ('[] :: [a1]) :: a2 -> Type) | |
Defined in Fcf.Class.Foldable | |
type Eval ((f <=< g) x :: a2 -> Type) | |
type Eval (Flip f y x :: a2 -> Type) | |
Defined in Fcf.Combinators | |
type Eval (Pure2 f x y :: a2 -> Type) | |
Defined in Fcf.Combinators | |
type Eval (UnEither f g ('Left x :: Either a1 b) :: a2 -> Type) | |
type Eval (UnEither f g ('Right y :: Either a1 b) :: a2 -> Type) | |
type Eval (LiftM2 f x y :: a3 -> Type) | |
type Eval (On r f x y :: a2 -> Type) | |
type Eval (Pure3 f x y z :: a2 -> Type) | |
Defined in Fcf.Combinators | |
type Eval (LiftM3 f x y z :: a4 -> Type) | |
type Eval (Bicomap f g r x y :: a4 -> Type) | |
type Eval (AsScalar xs :: [Nat] -> Type) Source # | |
type Eval (AsSingleton xs :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (DimsOf xs :: [Nat] -> Type) Source # | |
type Eval (MinDim s :: [Nat] -> Type) Source # | |
type Eval (PreDeletePositions xs :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (PreInsertPositions xs :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (Range x :: [Nat] -> Type) Source # | |
type Eval (Init ('[] :: [a]) :: Maybe [a] -> Type) | |
type Eval (Tail (_a ': as) :: Maybe [a] -> Type) | |
type Eval (Tail ('[] :: [a]) :: Maybe [a] -> Type) | |
type Eval (Init (a2 ': (b ': as)) :: Maybe [a1] -> Type) | |
type Eval (Init '[a2] :: Maybe [a1] -> Type) | |
type Eval (Head ('[] :: [a]) :: Maybe a -> Type) | |
type Eval (Last ('[] :: [a]) :: Maybe a -> Type) | |
type Eval (Head (a2 ': _as) :: Maybe a1 -> Type) | |
type Eval (Last (a2 ': (b ': as)) :: Maybe a1 -> Type) | |
type Eval (Last '[a2] :: Maybe a1 -> Type) | |
type Eval (DecAt d ds :: [Nat] -> Type) Source # | |
type Eval (DeleteDim i ds :: [Nat] -> Type) Source # | |
type Eval (DeleteDims xs ds :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (DimWindows ws s :: [Nat] -> Type) Source # | |
type Eval (EndDimsOf xs s :: [Nat] -> Type) Source # | |
type Eval (EnumFromTo a b :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (ExceptDims ds s :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape type Eval (ExceptDims ds s :: [Nat] -> Type) = Eval (DeleteDims ds =<< EnumFromTo 0 (Eval (Eval (Rank s) - 1))) | |
type Eval (ExpandWindows ws ds :: [Nat] -> Type) Source # | |
type Eval (GetDims xs ds :: [Nat] -> Type) Source # | |
type Eval (GetLastPositions ds s :: [Nat] -> Type) Source # | |
type Eval (IncAt d ds :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (Reorder ds xs :: [Nat] -> Type) Source # | |
type Eval (Rerank r xs :: [Nat] -> Type) Source # | |
type Eval (Tails ('[] :: [a]) :: [[a]] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Tails (a2 ': as) :: [[a1]] -> Type) | |
type Eval (Reverse l :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Squeeze xs :: [a] -> Type) Source # | |
type Eval (FindIndex _p ('[] :: [a]) :: Maybe Nat -> Type) | |
type Eval (FindIndex p (a2 ': as) :: Maybe Nat -> Type) | |
type Eval (NumIter a s :: Maybe (k, Nat) -> Type) | |
type Eval (Find _p ('[] :: [a]) :: Maybe a -> Type) | |
type Eval (Find p (a2 ': as) :: Maybe a1 -> Type) | |
type Eval (GetIndex d xs :: Maybe k -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (ConcatDims ds n s :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (Concatenate i s0 s1 :: [Nat] -> Type) Source # | |
type Eval (DropDim d t s :: [Nat] -> Type) Source # | |
type Eval (DropDims ds xs s :: [Nat] -> Type) Source # | |
type Eval (InsertDim d i ds :: [Nat] -> Type) Source # | |
type Eval (InsertDims ds xs s :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (ModifyDim d f s :: [Nat] -> Type) Source # | |
type Eval (SetDim d x ds :: [Nat] -> Type) Source # | |
type Eval (SetDims ds xs ns :: [Nat] -> Type) Source # | |
Defined in Harpie.Shape | |
type Eval (TakeDim d t s :: [Nat] -> Type) Source # | |
type Eval (xs ++ ys :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Drop n as :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (DropWhile p (x ': xs) :: [a] -> Type) | |
type Eval (DropWhile p ('[] :: [a]) :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Filter _p ('[] :: [a]) :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Intercalate xs xss :: [a] -> Type) | |
Defined in Fcf.Data.List type Eval (Intercalate xs xss :: [a] -> Type) = Eval ((Concat :: [[a]] -> [a] -> Type) =<< Intersperse xs xss) | |
type Eval (Intersperse _1 ('[] :: [a]) :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Intersperse sep (x ': xs) :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (PrependToAll _1 ('[] :: [a]) :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (PrependToAll sep (x ': xs) :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Rev (x ': xs) ys :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Rev ('[] :: [a]) ys :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Take n as :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (TakeWhile p (x ': xs) :: [a] -> Type) | |
type Eval (TakeWhile p ('[] :: [a]) :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Cons a2 as :: [a1] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Filter p (a2 ': as) :: [a1] -> Type) | |
type Eval (Replicate n a2 :: [a1] -> Type) | |
type Eval (Snoc lst a :: [k] -> Type) | |
type Eval (Lookup a as :: Maybe b -> Type) | |
type Eval (Zip as bs :: [(a, b)] -> Type) | |
type Eval (Unfoldr f c :: [a] -> Type) | |
type Eval (UnfoldrCase _1 ('Nothing :: Maybe (a, b)) :: [a] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (UnfoldrCase f ('Just ab) :: [a2] -> Type) | |
type Eval (SetIndex n a' as :: [k] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Map f ('Just a3) :: Maybe a2 -> Type) | |
type Eval (Map f ('Nothing :: Maybe a) :: Maybe b -> Type) | |
type Eval (ConcatMap f xs :: [b] -> Type) | |
type Eval (Map f ('[] :: [a]) :: [b] -> Type) | |
Defined in Fcf.Class.Functor | |
type Eval (Map f (a2 ': as) :: [b] -> Type) | |
type Eval (ZipWith _f ('[] :: [a]) _bs :: [c] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (ZipWith _f _as ('[] :: [b]) :: [c] -> Type) | |
Defined in Fcf.Data.List | |
type Eval (ZipWith f (a2 ': as) (b2 ': bs) :: [c] -> Type) | |
type Eval (Break p lst :: ([a], [a]) -> Type) | |
type Eval (Partition p lst :: ([a], [a]) -> Type) | |
type Eval (Span p lst :: ([a], [a]) -> Type) | |
type Eval (Unzip as :: ([a], [b]) -> Type) | |
type Eval (PartHelp p a2 '(xs, ys) :: ([a1], [a1]) -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Cons2 '(a3, b) '(as, bs) :: ([a1], [a2]) -> Type) | |
Defined in Fcf.Data.List | |
type Eval (Map f ('Left x :: Either a2 a1) :: Either a2 b -> Type) | |
type Eval (Map f ('Right a3 :: Either a2 a1) :: Either a2 b -> Type) | |
type Eval (Map f '(x, a2) :: (k2, k1) -> Type) | |
Defined in Fcf.Class.Functor | |
type Eval ((f *** f') '(b2, b'2) :: (k1, k2) -> Type) | |
type Eval (Second g x :: f a' b' -> Type) | |
type Eval (First f2 x :: f1 a' b' -> Type) | |
type Eval (Bimap f g ('Right y :: Either a b1) :: Either a' b2 -> Type) | |
type Eval (Bimap f g ('Left x :: Either a1 b) :: Either a2 b' -> Type) | |
type Eval (Bimap f g '(x, y) :: (k1, k2) -> Type) | |
type Eval (Map f '(x, y, a2) :: (k2, k3, k1) -> Type) | |
Defined in Fcf.Class.Functor | |
type Eval (Map f '(x, y, z, a2) :: (k2, k3, k4, k1) -> Type) | |
Defined in Fcf.Class.Functor | |
type Eval (Map f '(x, y, z, w, a2) :: (k2, k3, k4, k5, k1) -> Type) | |
Defined in Fcf.Class.Functor |
data ((b :: [a]) ++ (c :: [a])) (d :: [a]) #
List catenation.
Example
>>>
data Example where Ex :: a -> Example -- Hide the type of examples to avoid brittleness in different GHC versions
>>>
:kind! Ex (Eval ([1, 2] ++ [3, 4]) :: [Natural])
Ex (Eval ([1, 2] ++ [3, 4]) :: [Natural]) :: Example = Ex [1, 2, 3, 4]