| Copyright | Gautier DI FOLCO |
|---|---|
| License | BSD2 |
| Maintainer | Gautier DI FOLCO <gautier.difolco@gmail.com> |
| Stability | Unstable |
| Portability | GHC |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Data.Sum.Pure
Description
Derive fromText/toText-like for pure sum types.
Synopsis
- newtype PureSumWith transformation a = PureSumWith {
- unPureSumWith :: a
- type PureSum = PureSumWith IdTransformation
- class ToSumText a where
- class FromSumText a where
- fromSumText :: Text -> Maybe a
- class Transformation a where
- data f <<< g
- data DropPrefix (s :: Symbol)
- data CamelCase
- data PascalCase
- data SnakeCase
- data SpinalCase
- data TitleCase
- data TrainCase
Base type
newtype PureSumWith transformation a Source #
Wrapper for derivation.
transformation is a Transformation applied during derivations
Constructors
| PureSumWith | |
Fields
| |
Instances
| Show a => Show (PureSumWith transformation a) Source # | |
Defined in Data.Sum.Pure Methods showsPrec :: Int -> PureSumWith transformation a -> ShowS # show :: PureSumWith transformation a -> String # showList :: [PureSumWith transformation a] -> ShowS # | |
| Eq a => Eq (PureSumWith transformation a) Source # | |
Defined in Data.Sum.Pure Methods (==) :: PureSumWith transformation a -> PureSumWith transformation a -> Bool # (/=) :: PureSumWith transformation a -> PureSumWith transformation a -> Bool # | |
| Ord a => Ord (PureSumWith transformation a) Source # | |
Defined in Data.Sum.Pure Methods compare :: PureSumWith transformation a -> PureSumWith transformation a -> Ordering # (<) :: PureSumWith transformation a -> PureSumWith transformation a -> Bool # (<=) :: PureSumWith transformation a -> PureSumWith transformation a -> Bool # (>) :: PureSumWith transformation a -> PureSumWith transformation a -> Bool # (>=) :: PureSumWith transformation a -> PureSumWith transformation a -> Bool # max :: PureSumWith transformation a -> PureSumWith transformation a -> PureSumWith transformation a # min :: PureSumWith transformation a -> PureSumWith transformation a -> PureSumWith transformation a # | |
| (Transformation transformation, Generic a, GFromSumText (Rep a)) => FromSumText (PureSumWith transformation a) Source # | |
Defined in Data.Sum.Pure Methods fromSumText :: Text -> Maybe (PureSumWith transformation a) Source # | |
| (Transformation transformation, Generic a, GToSumText (Rep a)) => ToSumText (PureSumWith transformation a) Source # | |
Defined in Data.Sum.Pure Methods toSumText :: PureSumWith transformation a -> Text Source # | |
type PureSum = PureSumWith IdTransformation Source #
Basic sum derivation
from/to Text converters
class ToSumText a where Source #
Instances
| (Transformation transformation, Generic a, GToSumText (Rep a)) => ToSumText (PureSumWith transformation a) Source # | |
Defined in Data.Sum.Pure Methods toSumText :: PureSumWith transformation a -> Text Source # | |
class FromSumText a where Source #
Methods
fromSumText :: Text -> Maybe a Source #
Instances
| (Transformation transformation, Generic a, GFromSumText (Rep a)) => FromSumText (PureSumWith transformation a) Source # | |
Defined in Data.Sum.Pure Methods fromSumText :: Text -> Maybe (PureSumWith transformation a) Source # | |
Transformations
class Transformation a where Source #
Convert a type into a Text -> Text function
Instances
| Transformation CamelCase Source # | |
| Transformation PascalCase Source # | |
Defined in Data.Sum.Pure | |
| Transformation SnakeCase Source # | |
| Transformation SpinalCase Source # | |
Defined in Data.Sum.Pure | |
| Transformation TitleCase Source # | |
| Transformation TrainCase Source # | |
| KnownSymbol s => Transformation (DropPrefix s) Source # | |
Defined in Data.Sum.Pure | |
| (Transformation f, Transformation g) => Transformation (f <<< g) Source # | |
Compose two transformations (e.g. f << g is equivalent to f (g x))
Instances
| (Transformation f, Transformation g) => Transformation (f <<< g) Source # | |
data DropPrefix (s :: Symbol) Source #
Instances
| KnownSymbol s => Transformation (DropPrefix s) Source # | |
Defined in Data.Sum.Pure | |
Change case (e.g. "camelCasedPhrase")
data PascalCase Source #
Change case (e.g. PascalCasedPhrase)
Instances
| Transformation PascalCase Source # | |
Defined in Data.Sum.Pure | |
Change case (e.g. "snake_cased_phrase")
data SpinalCase Source #
Change case (e.g. "spinal-cased-phrase")
Instances
| Transformation SpinalCase Source # | |
Defined in Data.Sum.Pure | |
Change case (e.g. "Title Cased Phrase")