enum-text-0.5.1.0: A text rendering and parsing toolkit for enumerated types

Safe HaskellNone
LanguageHaskell2010

Text.Enum.Text

Synopsis

Documentation

class (Buildable e, Bounded e, Enum e, Eq e, Ord e, Show e, TextParsable e) => EnumText e where Source #

Our toolkit for enumerated types which should be defined as follows:

import Fmt
import Text.Enum.Text

data Foo = FOO_bar | FOO_bar_baz
  deriving (Bounded,Enum,Eq,Ord,Show)

instance EnumText     Foo
instance Buildable    Foo where build     = buildEnumText
instance TextParsable Foo where parseText = parseEnumText

With the DeriveAnyClass language extension you can list EnumText in the deriving clause, and with DerivingVia (available from GHC 8.6.1) you can derive via UsingEnumText as follows:

{-# LANGUAGE DeriveAnyClass    #-}
{-# LANGUAGE DerivingVia       #-}

import Fmt
import Text.Enum.Text

data Foo = FOO_bar | FOO_bar_baz
  deriving (Bounded,Enum,EnumText,Eq,Ord,Show)
  deriving (Buildable,TextParsable) via UsingEnumText Foo

Minimal complete definition

Nothing

Methods

configEnumText :: e -> EnumTextConfig Source #

Configures the textual representation of e generated by renderEnumText.

renderEnumText :: e -> Text Source #

Generate the standard textual representation according to configEnumText by default.

buildEnumText :: e -> Builder Source #

Sames as renderEnumText, but generating a Builder.

parseEnumText :: Text -> Possibly e Source #

Parses an e according to the renderEnumText render.

toFieldEnumText :: e -> ByteString Source #

A cassava field encoder, using 'the renderEnumText' format.

fromFieldEnumText_ :: Monad m => ByteString -> m e Source #

A cassava field parser using the renderEnumText format.

hashWithSaltEnumText :: Int -> e -> Int Source #

For hashing e with the renderEnumText representation.

newtype UsingEnumText a Source #

Constructors

UsingEnumText 

Fields

Instances
EnumText a => Buildable (UsingEnumText a) Source # 
Instance details

Defined in Text.Enum.Text

Methods

build :: UsingEnumText a -> Builder #

EnumText a => TextParsable (UsingEnumText a) Source # 
Instance details

Defined in Text.Enum.Text

class TextParsable a where Source #

a class for Text parsers.

Methods

parseText :: Text -> Possibly a Source #

Instances
TextParsable Int Source # 
Instance details

Defined in Text.Enum.Text

TextParsable Text Source # 
Instance details

Defined in Text.Enum.Text

TextParsable UTCTime Source # 
Instance details

Defined in Text.Enum.Text

TextParsable Day Source # 
Instance details

Defined in Text.Enum.Text

a ~ Char => TextParsable [a] Source # 
Instance details

Defined in Text.Enum.Text

Methods

parseText :: Text -> Possibly [a] Source #

TextParsable a => TextParsable (Maybe a) Source # 
Instance details

Defined in Text.Enum.Text

Methods

parseText :: Text -> Possibly (Maybe a) Source #

EnumText a => TextParsable (UsingEnumText a) Source # 
Instance details

Defined in Text.Enum.Text

data EnumTextConfig Source #

Configures the default implementation of renderEnumText

Constructors

EnumTextConfig 

Fields

defaultEnumTextConfig :: EnumTextConfig Source #

The default configEnumText for EnumText: