Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Grid (cs :: [*]) a = Grid {}
- type family Head xs where ...
- type family Tail xs where ...
- type family CollapseGrid cs a where ...
- type family AllGridSizeKnown cs :: Constraint where ...
- splitVectorBySize :: Int -> Vector a -> [Vector a]
- collapseGrid :: forall cs a. (SListI cs, AllGridSizeKnown cs) => Grid cs a -> CollapseGrid cs a
- gridFromList :: forall cs a. (SListI cs, AllGridSizeKnown cs) => CollapseGrid cs a -> Maybe (Grid cs a)
- transposeGrid :: (IsCoord h, IsCoord w, KnownNat (MaxCoordSize '[w, h]), KnownNat (MaxCoordSize '[h, w])) => Grid '[w, h] a -> Grid '[h, w] a
- splitGrid :: forall c cs a. AllSizedKnown cs => Grid (c ': cs) a -> Grid '[c] (Grid cs a)
- combineGrid :: Grid '[c] (Grid cs a) -> Grid (c ': cs) a
- combineHigherDim :: (CoordFromNat a ~ CoordFromNat b, c ~ CoordFromNat a ((+) (CoordSized a) (CoordSized b))) => Grid (a ': as) x -> Grid (b ': as) x -> Grid (c ': as) x
- dropGrid :: KnownNat n => Proxy n -> Grid '[c] x -> Grid '[CoordFromNat c (CoordSized c - n)] x
- takeGrid :: KnownNat n => Proxy n -> Grid '[c] x -> Grid '[CoordFromNat c n] x
- splitHigherDim :: forall a b c as x. (KnownNat (CoordSized b), c ~ CoordFromNat a (CoordSized a - CoordSized b), CoordSized b <= CoordSized a, AllSizedKnown as) => Grid (a ': as) x -> (Grid (b ': as) x, Grid (c ': as) x)
- mapLowerDim :: forall as bs x y c f. (AllSizedKnown as, Applicative f) => (Grid as x -> f (Grid bs y)) -> Grid (c ': as) x -> f (Grid (c ': bs) y)
- class ShrinkableGrid (cs :: [*]) (as :: [*]) (bs :: [*]) where
- shrinkGrid :: Coord cs -> Grid as x -> Grid bs x
Documentation
newtype Grid (cs :: [*]) a Source #
A multi dimensional sized grid
Instances
(AllSizedKnown cs, All IsCoord cs) => IsGrid cs (Grid cs) Source # | |
(AllSizedKnown cs, All IsCoord cs) => Monad (Grid cs) Source # | |
Functor (Grid cs) Source # | |
AllSizedKnown cs => Applicative (Grid cs) Source # | |
Foldable (Grid cs) Source # | |
Defined in SizedGrid.Grid.Grid fold :: Monoid m => Grid cs m -> m # foldMap :: Monoid m => (a -> m) -> Grid cs a -> m # foldr :: (a -> b -> b) -> b -> Grid cs a -> b # foldr' :: (a -> b -> b) -> b -> Grid cs a -> b # foldl :: (b -> a -> b) -> b -> Grid cs a -> b # foldl' :: (b -> a -> b) -> b -> Grid cs a -> b # foldr1 :: (a -> a -> a) -> Grid cs a -> a # foldl1 :: (a -> a -> a) -> Grid cs a -> a # elem :: Eq a => a -> Grid cs a -> Bool # maximum :: Ord a => Grid cs a -> a # minimum :: Ord a => Grid cs a -> a # | |
Traversable (Grid cs) Source # | |
(AllSizedKnown cs, All IsCoord cs) => Distributive (Grid cs) Source # | |
(All IsCoord cs, AllSizedKnown cs) => Representable (Grid cs) Source # | |
Eq1 (Grid cs) Source # | |
Show1 (Grid cs) Source # | |
All IsCoord cs => FunctorWithIndex (Coord cs) (Grid cs) Source # | |
All IsCoord cs => FoldableWithIndex (Coord cs) (Grid cs) Source # | |
Defined in SizedGrid.Grid.Grid ifoldMap :: Monoid m => (Coord cs -> a -> m) -> Grid cs a -> m # ifolded :: IndexedFold (Coord cs) (Grid cs a) a # ifoldr :: (Coord cs -> a -> b -> b) -> b -> Grid cs a -> b # ifoldl :: (Coord cs -> b -> a -> b) -> b -> Grid cs a -> b # ifoldr' :: (Coord cs -> a -> b -> b) -> b -> Grid cs a -> b # ifoldl' :: (Coord cs -> b -> a -> b) -> b -> Grid cs a -> b # | |
All IsCoord cs => TraversableWithIndex (Coord cs) (Grid cs) Source # | |
Defined in SizedGrid.Grid.Grid itraverse :: Applicative f => (Coord cs -> a -> f b) -> Grid cs a -> f (Grid cs b) # itraversed :: IndexedTraversal (Coord cs) (Grid cs a) (Grid cs b) a b # | |
Eq a => Eq (Grid cs a) Source # | |
Show a => Show (Grid cs a) Source # | |
Generic (Grid cs a) Source # | |
(AllGridSizeKnown cs, ToJSON a, SListI cs) => ToJSON (Grid cs a) Source # | |
Defined in SizedGrid.Grid.Grid | |
(All IsCoord cs, FromJSON a) => FromJSON (Grid cs a) Source # | |
type Rep (Grid cs) Source # | |
Defined in SizedGrid.Grid.Grid | |
type Rep (Grid cs a) Source # | |
Defined in SizedGrid.Grid.Grid |
type family Tail xs where ... Source #
All but the first elements of a type level list
Tail (x ': xs) = xs |
type family CollapseGrid cs a where ... Source #
Given a grid type, give back a series of nested lists repesenting the grid. The lists will have a number of layers equal to the dimensionality.
CollapseGrid '[] a = a | |
CollapseGrid (c ': cs) a = [CollapseGrid cs a] |
type family AllGridSizeKnown cs :: Constraint where ... Source #
A Constraint that all grid sizes are instances of KnownNat
AllGridSizeKnown '[] = () | |
AllGridSizeKnown cs = (KnownNat (CoordSized (Head cs)), KnownNat (MaxCoordSize (Tail cs)), AllGridSizeKnown (Tail cs)) |
splitVectorBySize :: Int -> Vector a -> [Vector a] Source #
Convert a vector into a list of Vector
s, where all the elements of the list have the given size.
collapseGrid :: forall cs a. (SListI cs, AllGridSizeKnown cs) => Grid cs a -> CollapseGrid cs a Source #
Convert a grid to a series of nested lists. This removes type level information, but it is sometimes easier to work with lists
gridFromList :: forall cs a. (SListI cs, AllGridSizeKnown cs) => CollapseGrid cs a -> Maybe (Grid cs a) Source #
Convert a series of nested lists to a grid. If the size of the grid does not match the size of lists this will be Nothing
transposeGrid :: (IsCoord h, IsCoord w, KnownNat (MaxCoordSize '[w, h]), KnownNat (MaxCoordSize '[h, w])) => Grid '[w, h] a -> Grid '[h, w] a Source #
combineHigherDim :: (CoordFromNat a ~ CoordFromNat b, c ~ CoordFromNat a ((+) (CoordSized a) (CoordSized b))) => Grid (a ': as) x -> Grid (b ': as) x -> Grid (c ': as) x Source #
dropGrid :: KnownNat n => Proxy n -> Grid '[c] x -> Grid '[CoordFromNat c (CoordSized c - n)] x Source #
splitHigherDim :: forall a b c as x. (KnownNat (CoordSized b), c ~ CoordFromNat a (CoordSized a - CoordSized b), CoordSized b <= CoordSized a, AllSizedKnown as) => Grid (a ': as) x -> (Grid (b ': as) x, Grid (c ': as) x) Source #
mapLowerDim :: forall as bs x y c f. (AllSizedKnown as, Applicative f) => (Grid as x -> f (Grid bs y)) -> Grid (c ': as) x -> f (Grid (c ': bs) y) Source #
class ShrinkableGrid (cs :: [*]) (as :: [*]) (bs :: [*]) where Source #
Instances
ShrinkableGrid ([] :: [Type]) ([] :: [Type]) ([] :: [Type]) Source # | |
Defined in SizedGrid.Grid.Grid | |
(KnownNat (CoordSized b), AllSizedKnown as, IsCoord c, ShrinkableGrid cs as bs, CoordFromNat b ~ CoordFromNat a, CoordSized b <= ((CoordSized a - CoordSized c) + 1)) => ShrinkableGrid (c ': cs) (a ': as) (b ': bs) Source # | |
Defined in SizedGrid.Grid.Grid |