| Copyright | (c) Galois Inc 2021 | 
|---|---|
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Data.Parameterized.Fin
Description
Fin nn elements. Essentially, they bundle a
NatRepr that has an existentially-quantified type parameter with a proof that
its parameter is less than some fixed natural.
They are useful in combination with types of a fixed size. For example Fin is
used as the index in the FunctorWithIndex instance for
Vector. As another example, a Map ( is a Fin n) aMap
that naturally has a fixed size bound of n.
Synopsis
- data Fin n
- mkFin :: forall i n. (i + 1) <= n => NatRepr i -> Fin n
- viewFin :: (forall i. (i + 1) <= n => NatRepr i -> r) -> Fin n -> r
- finToNat :: Fin n -> Natural
- embed :: forall n m. n <= m => Fin n -> Fin m
- tryEmbed :: NatRepr n -> NatRepr m -> Fin n -> Maybe (Fin m)
- minFin :: 1 <= n => Fin n
- fin0Void :: Iso' (Fin 0) Void
- fin1Unit :: Iso' (Fin 1) ()
- fin2Bool :: Iso' (Fin 2) Bool
Documentation
The type Fin nn inhabitants.
Instances
| (1 <= n, KnownNat n) => Bounded (Fin n) Source # | |
| Eq (Fin n) Source # | |
| Ord (Fin n) Source # | |
| Show (Fin n) Source # | Non-lawful instance, intended only for testing. | 
| FunctorWithIndex (Fin n) (Vector n) Source # | |
| FoldableWithIndex (Fin n) (Vector n) Source # | |
| Defined in Data.Parameterized.Vector Methods ifoldMap :: Monoid m => (Fin n -> a -> m) -> Vector n a -> m # ifoldMap' :: Monoid m => (Fin n -> a -> m) -> Vector n a -> m # ifoldr :: (Fin n -> a -> b -> b) -> b -> Vector n a -> b # ifoldl :: (Fin n -> b -> a -> b) -> b -> Vector n a -> b # | |
| TraversableWithIndex (Fin n) (Vector n) Source # | |
| Defined in Data.Parameterized.Vector | |