pure-sum-0.1.0.0: Derive fromString/toString-like for pure sum types
CopyrightGautier DI FOLCO
LicenseBSD2
MaintainerGautier DI FOLCO <gautier.difolco@gmail.com>
StabilityUnstable
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Sum.Pure

Description

Derive fromText/toText-like for pure sum types.

Synopsis

Base type

newtype PureSumWith transformation a Source #

Wrapper for derivation. transformation is a Transformation applied during derivations

Constructors

PureSumWith 

Fields

Instances

Instances details
Show a => Show (PureSumWith transformation a) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 #

Methods

toSumText :: a -> Text Source #

Instances

Instances details
(Transformation transformation, Generic a, GToSumText (Rep a)) => ToSumText (PureSumWith transformation a) Source # 
Instance details

Defined in Data.Sum.Pure

Methods

toSumText :: PureSumWith transformation a -> Text Source #

class FromSumText a where Source #

Methods

fromSumText :: Text -> Maybe a Source #

Instances

Instances details
(Transformation transformation, Generic a, GFromSumText (Rep a)) => FromSumText (PureSumWith transformation a) Source # 
Instance details

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

Methods

transform :: Proxy a -> Text -> Text Source #

Instances

Instances details
Transformation CamelCase Source # 
Instance details

Defined in Data.Sum.Pure

Transformation PascalCase Source # 
Instance details

Defined in Data.Sum.Pure

Transformation SnakeCase Source # 
Instance details

Defined in Data.Sum.Pure

Transformation SpinalCase Source # 
Instance details

Defined in Data.Sum.Pure

Transformation TitleCase Source # 
Instance details

Defined in Data.Sum.Pure

Transformation TrainCase Source # 
Instance details

Defined in Data.Sum.Pure

KnownSymbol s => Transformation (DropPrefix s) Source # 
Instance details

Defined in Data.Sum.Pure

Methods

transform :: Proxy (DropPrefix s) -> Text -> Text Source #

(Transformation f, Transformation g) => Transformation (f <<< g) Source # 
Instance details

Defined in Data.Sum.Pure

Methods

transform :: Proxy (f <<< g) -> Text -> Text Source #

data f <<< g Source #

Compose two transformations (e.g. f << g is equivalent to f (g x))

Instances

Instances details
(Transformation f, Transformation g) => Transformation (f <<< g) Source # 
Instance details

Defined in Data.Sum.Pure

Methods

transform :: Proxy (f <<< g) -> Text -> Text Source #

data DropPrefix (s :: Symbol) Source #

DropPrefix prefix (e.g. DropPrefix A on ACase gives Case)

Instances

Instances details
KnownSymbol s => Transformation (DropPrefix s) Source # 
Instance details

Defined in Data.Sum.Pure

Methods

transform :: Proxy (DropPrefix s) -> Text -> Text Source #

data CamelCase Source #

Change case (e.g. "camelCasedPhrase")

Instances

Instances details
Transformation CamelCase Source # 
Instance details

Defined in Data.Sum.Pure

data PascalCase Source #

Change case (e.g. PascalCasedPhrase)

Instances

Instances details
Transformation PascalCase Source # 
Instance details

Defined in Data.Sum.Pure

data SnakeCase Source #

Change case (e.g. "snake_cased_phrase")

Instances

Instances details
Transformation SnakeCase Source # 
Instance details

Defined in Data.Sum.Pure

data SpinalCase Source #

Change case (e.g. "spinal-cased-phrase")

Instances

Instances details
Transformation SpinalCase Source # 
Instance details

Defined in Data.Sum.Pure

data TitleCase Source #

Change case (e.g. "Title Cased Phrase")

Instances

Instances details
Transformation TitleCase Source # 
Instance details

Defined in Data.Sum.Pure

data TrainCase Source #

Change case (e.g. "Train-Cased-Phrase")

Instances

Instances details
Transformation TrainCase Source # 
Instance details

Defined in Data.Sum.Pure