Safe Haskell | None |
---|---|
Language | Haskell2010 |
Support for representing so-called categorical variables: a (usually small) finite set of textual values. We map these onto regular Haskell data types and offer help to generate useful type class instances for such types.
Synopsis
- newtype Categorical (n :: Nat) = Categorical {
- categories :: Set Text
- cap :: String -> String
- unboxDecls :: String -> Int -> DecsQ
- declareCategorical :: String -> Maybe String -> [String] -> Q [Dec]
Documentation
newtype Categorical (n :: Nat) Source #
A categorical variable can take on one of a finite number of
textual names. Any value of type Categorical n
has no more than
n
variants.
Instances
Eq (Categorical n) Source # | |
Defined in Frames.Categorical (==) :: Categorical n -> Categorical n -> Bool # (/=) :: Categorical n -> Categorical n -> Bool # | |
Show (Categorical n) Source # | |
Defined in Frames.Categorical showsPrec :: Int -> Categorical n -> ShowS # show :: Categorical n -> String # showList :: [Categorical n] -> ShowS # | |
KnownNat n => Parseable (Categorical n) Source # | |
Defined in Frames.Categorical parse :: MonadPlus m => Text -> m (Parsed (Categorical n)) Source # parseCombine :: MonadPlus m => Parsed (Categorical n) -> Parsed (Categorical n) -> m (Parsed (Categorical n)) Source # representableAsType :: Parsed (Categorical n) -> Const (Either (String -> Q [Dec]) Type) (Categorical n) Source # |
unboxDecls :: String -> Int -> DecsQ Source #
Helper for working with derivingUnbox
. Takes the name of the
type and the number of variants in the sum type in order to
determine a compact representation.
declareCategorical :: String -> Maybe String -> [String] -> Q [Dec] Source #
Generate a splice with data type declaration and associated
instances for type suitable for representing a categorical
variable. This is a type that maps between a finite set of textual
names and Haskell data constructors. Usage: declareCategorical
typeName optionalConPrefix variantNames
will produce a data type
with name typeName
and data constructors whose names are a
concatenation of optionalConPrefix
and each element of
variantNames
.