Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- coordFromNatCollapse :: forall a x y. Dict (CoordFromNat (CoordFromNat a x) y ~ CoordFromNat a y)
- coordFromNatSame :: (CoordFromNat a ~ CoordFromNat b) :- (a ~ CoordFromNat b (CoordSized a))
- coordSizedCollapse :: forall c n. Dict (CoordSized (CoordFromNat c n) ~ n)
- class (1 <= CoordSized c, KnownNat (CoordSized c)) => IsCoord c where
- type CoordSized c :: Nat
- type CoordFromNat c :: Nat -> *
- asOrdinal :: Iso' c (Ordinal (CoordSized c))
- zeroPosition :: c
- sCoordSized :: proxy c -> Proxy (CoordSized c)
- maxCoordSize :: proxy c -> Integer
- maxCoord :: c
- asSizeProxy :: c -> (forall n. (KnownNat n, (n + 1) <= CoordSized c) => Proxy n -> x) -> x
- weakenIsCoord :: IsCoord (CoordFromNat c n) => c -> Maybe (CoordFromNat c n)
- strengthenIsCoord :: (IsCoord (CoordFromNat c n), CoordSized c <= CoordSized (CoordFromNat c n)) => c -> CoordFromNat c n
- allCoordLike :: IsCoord c => [c]
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'
coordFromNatSame :: (CoordFromNat a ~ CoordFromNat b) :- (a ~ CoordFromNat b (CoordSized a)) Source #
coordSizedCollapse :: forall c n. Dict (CoordSized (CoordFromNat c n) ~ n) Source #
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
type CoordSized c :: Nat Source #
The maximum number of values that a Coord can take
type CoordFromNat c :: Nat -> * Source #
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
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
allCoordLike :: IsCoord c => [c] Source #
Enumerate all possible values of a coord, in order