Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type family Length cs where ...
- newtype Coord cs = Coord {}
- _WrappedCoord :: Lens' (Coord cs) (NP I cs)
- coordHead :: Lens (Coord (a ': as)) (Coord (a' ': as)) a a'
- coordTail :: Lens (Coord (a ': as)) (Coord (a ': as')) (Coord as) (Coord as')
- singleCoord :: a -> Coord '[a]
- appendCoord :: a -> Coord as -> Coord (a ': as)
- type family CoordDiff (cs :: [k]) :: *
- type family MapDiff xs where ...
- allCoord :: forall cs. All IsCoord cs => [Coord cs]
- type family MaxCoordSize (cs :: [k]) :: Nat where ...
- coordPosition :: All IsCoord cs => Coord cs -> Int
- type family AllDiffSame a xs :: Constraint where ...
- moorePoints :: forall a cs. (Enum a, Num a, AllDiffSame a cs, All AffineSpace cs) => a -> Coord cs -> [Coord cs]
- vonNeumanPoints :: forall a cs. (Enum a, Num a, Ord a, All Integral (MapDiff cs), AllDiffSame a cs, All AffineSpace cs, Ord (CoordDiff cs), IsProductType (CoordDiff cs) (MapDiff cs), AdditiveGroup (CoordDiff cs)) => a -> Coord cs -> [Coord cs]
Documentation
A multideminsion coordinate
coordHead :: Lens (Coord (a ': as)) (Coord (a' ': as)) a a' Source #
Get the first element of a coord. Thanks to type level information, we can write this as a total Lens
singleCoord :: a -> Coord '[a] Source #
Turn a single element into a one dimensional Coord
appendCoord :: a -> Coord as -> Coord (a ': as) Source #
Add a new element to a Coord
. This increases the dimensionality
type family CoordDiff (cs :: [k]) :: * Source #
The type of difference between two coords. A n-dimensional coord should have a Diff
of an n-tuple of Integers
. We use Identity
and our 1-tuple. Unfortuantly, each instance is manual at the moment.
type CoordDiff k ([] k) Source # | |
type CoordDiff * ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ([] *))))))) Source # | |
type CoordDiff * ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ([] *)))))) Source # | |
type CoordDiff * ((:) * a ((:) * b ((:) * c ((:) * d ([] *))))) Source # | |
type CoordDiff * ((:) * a ((:) * b ((:) * c ([] *)))) Source # | |
type CoordDiff * ((:) * a ((:) * b ([] *))) Source # | |
type CoordDiff * ((:) * a ([] *)) Source # | |
type family MapDiff xs where ... Source #
Apply Diff
to each element of a type level list. This is required as type families can't be partially applied.
type family MaxCoordSize (cs :: [k]) :: Nat where ... Source #
The number of elements a coord can have. This is equal to the product of the CoordSized
of each element
MaxCoordSize '[] = 1 | |
MaxCoordSize (c ': cs) = CoordSized c * MaxCoordSize cs |
coordPosition :: All IsCoord cs => Coord cs -> Int Source #
Convert a Coord
to its position in a vector
type family AllDiffSame a xs :: Constraint where ... Source #
All Diffs of the members of the list must be equal
AllDiffSame _ '[] = () | |
AllDiffSame a (x ': xs) = (Diff x ~ a, AllDiffSame a xs) |
moorePoints :: forall a cs. (Enum a, Num a, AllDiffSame a cs, All AffineSpace cs) => a -> Coord cs -> [Coord cs] Source #
Calculate the Moore neighbourhood around a point. Includes the center
vonNeumanPoints :: forall a cs. (Enum a, Num a, Ord a, All Integral (MapDiff cs), AllDiffSame a cs, All AffineSpace cs, Ord (CoordDiff cs), IsProductType (CoordDiff cs) (MapDiff cs), AdditiveGroup (CoordDiff cs)) => a -> Coord cs -> [Coord cs] Source #
Calculate the von Neuman neighbourhood around a point. Includes the center