sized-grid-0.1.1.5: Multidimensional grids with sized specified at compile time

Safe HaskellNone
LanguageHaskell2010

SizedGrid.Coord.Class

Synopsis

Documentation

coordFromNatCollapse :: forall a x y. Dict (CoordFromNat (CoordFromNat a x) y ~ CoordFromNat a y) Source #

Proof an idiom about how CoordFromNat works. This relies on 'CoordFromNat a (CoordSized a ~ a'

class (1 <= CoordSized c, KnownNat (CoordSized c)) => IsCoord c where Source #

Everything that can be uses as a Coordinate. The only required function is asOrdinal and the type instance of CoordSized: the rest can be derived automatically.

This is kind * -> Constraint for ease of use later. There is some argument that it should be of kind (Nat -> *) -> Constraint and we could remove CoordSized, but that has other complications

Minimal complete definition

asOrdinal

Associated Types

type CoordSized c :: Nat Source #

The maximum number of values that a Coord can take

type CoordFromNat c :: Nat -> * Source #

Methods

asOrdinal :: Iso' c (Ordinal (CoordSized c)) Source #

As each coord represents a finite number of states, it must be isomorphic to an Ordinal

zeroPosition :: c Source #

The origin. If c is an instance of Monoid, this should be mempty

zeroPosition :: Monoid c => c Source #

The origin. If c is an instance of Monoid, this should be mempty

sCoordSized :: proxy c -> Proxy (CoordSized c) Source #

Retrive a Proxy of the size

maxCoordSize :: proxy c -> Integer Source #

The largest possible number expressable

maxCoord :: c Source #

asSizeProxy :: c -> (forall n. (KnownNat n, (n + 1) <= CoordSized c) => Proxy n -> x) -> x Source #

weakenIsCoord :: IsCoord (CoordFromNat c n) => c -> Maybe (CoordFromNat c n) Source #

strengthenIsCoord :: (IsCoord (CoordFromNat c n), CoordSized c <= CoordSized (CoordFromNat c n)) => c -> CoordFromNat c n Source #

Instances
(1 <= n, KnownNat n) => IsCoord (Ordinal n) Source # 
Instance details

Defined in SizedGrid.Coord.Class

Associated Types

type CoordSized (Ordinal n) :: Nat Source #

type CoordFromNat (Ordinal n) :: Nat -> Type Source #

(1 <= n, KnownNat n) => IsCoord (Periodic n) Source # 
Instance details

Defined in SizedGrid.Coord.Periodic

Associated Types

type CoordSized (Periodic n) :: Nat Source #

type CoordFromNat (Periodic n) :: Nat -> Type Source #

(1 <= n, KnownNat n) => IsCoord (HardWrap n) Source # 
Instance details

Defined in SizedGrid.Coord.HardWrap

Associated Types

type CoordSized (HardWrap n) :: Nat Source #

type CoordFromNat (HardWrap n) :: Nat -> Type Source #

allCoordLike :: IsCoord c => [c] Source #

Enumerate all possible values of a coord, in order