| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Finite.Table
Description
Provides Vec-backed tables indexed by Finite types.
Combined with Finite and its Generics-based derivation, this can
effectively provide an array-backed container indexed by finite type. This
is a low-syntactic-overhead way to create Representable functors of any
desired shape: just define the index type, tack on the requisite deriving
clauses, and start using .Table MyType
data PrimaryColor = R | G | B
deriving Generic
deriving (Finite, Portray) via Wrapped Generic PrimaryColor
newtype Color = Color { getComponents :: Table PrimaryColor Int8 }
magenta :: Color
magenta = Color (Table $ Vec.fromList [255, 0, 255])
cyan :: Color
cyan = Color $ tabulate (\case { R -> 0; G -> 255; B -> 255 })
main = pp $ getComponents magenta
-- "mkTable (\case { R -> 255; G -> 0; B -> 255 })"
Synopsis
- newtype Table a b = Table (Vec (Cardinality a) b)
- (!) :: Finite a => Table a b -> a -> b
- ix :: Finite a => a -> Lens' (Table a b) b
- idTable :: Finite a => Table a a
- mkTable :: Finite a => (a -> b) -> Table a b
- lmapTable :: (Finite b, Finite c) => (b -> c) -> Table c a -> Table b a
- composeTable :: (Finite a, Finite b) => Table b c -> Table a b -> Table a c
- memoize :: Finite a => (a -> b) -> a -> b
- traverseRep :: forall x a b f. (Finite x, Applicative f) => (a -> f b) -> (x -> a) -> f (x -> b)
- tabulateA :: (Traversable t, Representable t, Applicative f) => (Rep t -> f b) -> f (t b)
- retabulated :: (Representable f, Representable g, Rep f ~ Rep g) => Iso (f a) (f b) (g a) (g b)
Tables
A compact array of bs indexed by a, according to .Finite a
Constructors
| Table (Vec (Cardinality a) b) |
Instances
| Finite a => FunctorWithIndex a (Table a) Source # | |
Defined in Data.Finite.Table | |
| Finite a => FoldableWithIndex a (Table a) Source # | |
Defined in Data.Finite.Table | |
| Finite a => TraversableWithIndex a (Table a) Source # | |
Defined in Data.Finite.Table Methods itraverse :: Applicative f => (a -> a0 -> f b) -> Table a a0 -> f (Table a b) # | |
| Functor (Table a) Source # | |
| Finite a => Applicative (Table a) Source # | |
| Foldable (Table a) Source # | |
Defined in Data.Finite.Table Methods fold :: Monoid m => Table a m -> m # foldMap :: Monoid m => (a0 -> m) -> Table a a0 -> m # foldMap' :: Monoid m => (a0 -> m) -> Table a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Table a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Table a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Table a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Table a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Table a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Table a a0 -> a0 # toList :: Table a a0 -> [a0] # elem :: Eq a0 => a0 -> Table a a0 -> Bool # maximum :: Ord a0 => Table a a0 -> a0 # minimum :: Ord a0 => Table a a0 -> a0 # | |
| Finite a => Traversable (Table a) Source # | |
| Finite a => Distributive (Table a) Source # | |
| Finite a => Representable (Table a) Source # | |
| Eq b => Eq (Table a b) Source # | |
| Ord b => Ord (Table a b) Source # | |
| Show b => Show (Table a b) Source # | |
| Generic (Table a b) Source # | |
| (Finite k, Serialize a) => Serialize (Table k a) Source # | |
| (Finite a, Default b) => Default (Table a b) Source # | |
Defined in Data.Finite.Table | |
| NFData a => NFData (Table k a) Source # | |
Defined in Data.Finite.Table | |
| (Finite a, Portray a, Portray b) => Portray (Table a b) Source # | Pretty-print a Table as a λ> pp $ (tabulate (even . finToInt) :: Table (Fin 3) Bool )
mkTable (\case { 0 -> True; 1 -> False; 2 -> True })
|
Defined in Data.Finite.Table | |
| (Finite a, Portray a, Diff b) => Diff (Table a b) Source # | |
| type Rep (Table a) Source # | |
Defined in Data.Finite.Table | |
| type Rep (Table a b) Source # | |
Defined in Data.Finite.Table type Rep (Table a b) = D1 ('MetaData "Table" "Data.Finite.Table" "finite-table-0.1.0.1-80KodpzxmlV375M2yGwzSk" 'True) (C1 ('MetaCons "Table" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vec (Cardinality a) b)))) | |
mkTable :: Finite a => (a -> b) -> Table a b Source #
Monomorphized tabulate. Can be useful for type ambiguity reasons.
lmapTable :: (Finite b, Finite c) => (b -> c) -> Table c a -> Table b a Source #
lmap for a constrained Profunctor.
composeTable :: (Finite a, Finite b) => Table b c -> Table a b -> Table a c Source #
The composition of a constrained category of Tables.
Function Utilities
memoize :: Finite a => (a -> b) -> a -> b Source #
Memoize a function by using a Vec as a lazy lookup table.
Given a function whose argument is a Finite type, return a new function
that looks up the argument in a table constructed by applying the original
function to every possible value. Since Vec stores its elements boxed,
none of the applications of f in the table are forced until they're forced
by calling the memoized function and forcing the result.
traverseRep :: forall x a b f. (Finite x, Applicative f) => (a -> f b) -> (x -> a) -> f (x -> b) Source #
traverse a function whose argument is a finite enumerable type.
Representable Utilities
tabulateA :: (Traversable t, Representable t, Applicative f) => (Rep t -> f b) -> f (t b) Source #
Convenience function for building any Representable as if by traverse.
tabulateA f = sequenceA (tabulate f) = traverse f (tabulate id)
retabulated :: (Representable f, Representable g, Rep f ~ Rep g) => Iso (f a) (f b) (g a) (g b) Source #
An Iso between two Representable Functors with the same Rep type.