coalpit-0.2.0.0: DSV (de)serialization
Maintainerdefanor <defanor@uberspace.net>
Stabilityunstable
Portabilitynon-portable (uses GHC extensions)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Coalpit

Description

Coalpit is a library for building command-line interfaces: the goal is to build interfaces quickly and easily (by deriving those), while keeping them language-agnostic and more user- and shell scripting-friendly than JSON and similar formats.

Synopsis

Documentation

fromDSV :: Coalpit a => Options -> String -> Either String a Source #

Parse a single record from a string.

fromDSVList :: Coalpit a => Options -> String -> Either String [a] Source #

Parse multiple records from a string.

toDSV :: Coalpit a => Options -> a -> String Source #

Serialize a value.

toDSVList :: Coalpit a => Options -> [a] -> String Source #

Serialize multiple values.

dsvFromList :: Options -> [String] -> String Source #

Build a record ("line") out of individual strings, escaping those if needed.

class Coalpit a where Source #

Coalpit class: parsing, printing, usage strings.

Minimal complete definition

Nothing

Methods

coalpitParser :: Options -> Parser a Source #

default coalpitParser :: (Generic a, GCoalpit (Rep a)) => Options -> Parser a Source #

coalpitPrint :: Options -> a -> [String] Source #

default coalpitPrint :: (Generic a, GCoalpit (Rep a)) => Options -> a -> [String] Source #

coalpitDescription :: Options -> [String] -> Proxy a -> Usage Source #

default coalpitDescription :: GCoalpit (Rep a) => Options -> [String] -> Proxy a -> Usage Source #

Instances

Instances details
Coalpit Version Source # 
Instance details

Defined in Coalpit

Coalpit ExitCode Source # 
Instance details

Defined in Coalpit

Coalpit Int16 Source # 
Instance details

Defined in Coalpit

Coalpit Int32 Source # 
Instance details

Defined in Coalpit

Coalpit Int64 Source # 
Instance details

Defined in Coalpit

Coalpit Int8 Source # 
Instance details

Defined in Coalpit

Coalpit Rational Source # 
Instance details

Defined in Coalpit

Coalpit Word16 Source # 
Instance details

Defined in Coalpit

Coalpit Word32 Source # 
Instance details

Defined in Coalpit

Coalpit Word64 Source # 
Instance details

Defined in Coalpit

Coalpit Word8 Source # 
Instance details

Defined in Coalpit

Coalpit Ordering Source # 
Instance details

Defined in Coalpit

Coalpit URI Source #

An URI reference (absolute or relative).

Instance details

Defined in Coalpit

Coalpit Scientific Source # 
Instance details

Defined in Coalpit

Coalpit Day Source #

Uses dateFormat.

Instance details

Defined in Coalpit

Coalpit DiffTime Source #

Converts to/from Scientific.

Instance details

Defined in Coalpit

Coalpit NominalDiffTime Source #

Converts to/from Scientific.

Instance details

Defined in Coalpit

Coalpit UTCTime Source #

Uses dateTimeFormat.

Instance details

Defined in Coalpit

Coalpit UniversalTime Source #

Uses dateTimeFormat.

Instance details

Defined in Coalpit

Coalpit LocalTime Source #

Uses dateTimeFormat.

Instance details

Defined in Coalpit

Coalpit TimeOfDay Source #

Uses timeFormat.

Instance details

Defined in Coalpit

Coalpit ZonedTime Source #

Uses dateTimeFormat.

Instance details

Defined in Coalpit

Coalpit String Source # 
Instance details

Defined in Coalpit

Coalpit Integer Source # 
Instance details

Defined in Coalpit

Coalpit Natural Source # 
Instance details

Defined in Coalpit

Coalpit () Source # 
Instance details

Defined in Coalpit

Coalpit Bool Source # 
Instance details

Defined in Coalpit

Coalpit Char Source # 
Instance details

Defined in Coalpit

Coalpit Double Source # 
Instance details

Defined in Coalpit

Coalpit Float Source # 
Instance details

Defined in Coalpit

Coalpit Int Source # 
Instance details

Defined in Coalpit

Coalpit a => Coalpit (Complex a) Source # 
Instance details

Defined in Coalpit

Coalpit a => Coalpit (NonEmpty a) Source # 
Instance details

Defined in Coalpit

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

Defined in Coalpit

Coalpit a => Coalpit [a] Source # 
Instance details

Defined in Coalpit

(Coalpit a, Coalpit b) => Coalpit (Either a b) Source # 
Instance details

Defined in Coalpit

(Coalpit a, Coalpit b) => Coalpit (a, b) Source # 
Instance details

Defined in Coalpit

(Coalpit a, Coalpit b, Coalpit c) => Coalpit (a, b, c) Source # 
Instance details

Defined in Coalpit

Methods

coalpitParser :: Options -> Parser (a, b, c) Source #

coalpitPrint :: Options -> (a, b, c) -> [String] Source #

coalpitDescription :: Options -> [String] -> Proxy (a, b, c) -> Usage Source #

(Coalpit a, Coalpit b, Coalpit c, Coalpit d) => Coalpit (a, b, c, d) Source # 
Instance details

Defined in Coalpit

Methods

coalpitParser :: Options -> Parser (a, b, c, d) Source #

coalpitPrint :: Options -> (a, b, c, d) -> [String] Source #

coalpitDescription :: Options -> [String] -> Proxy (a, b, c, d) -> Usage Source #

Usage

usage :: Coalpit a => Options -> Proxy a -> Usage Source #

Compose Usage description.

usageString :: Coalpit a => Options -> Proxy a -> String Source #

Compose a usage string.

data Usage Source #

Usage description: can be translated into help messages or documentation formats.

Constructors

UConstructor String

Data constructor.

URecursive String

Constructor of a recursive data structure (its second appearance in the tree).

USelector Bool String Usage

Record selector.

UOptional Usage

Optional element.

USum Usage Usage

Sum.

UProduct Usage Usage

Product.

UUnit

Unit.

UType String

Type name (e.g., "INT").

Instances

Instances details
Show Usage Source # 
Instance details

Defined in Coalpit

Methods

showsPrec :: Int -> Usage -> ShowS #

show :: Usage -> String #

showList :: [Usage] -> ShowS #

Options

data SelNamePolicy Source #

How to handle selector names.

Constructors

SNDisable

Do not parse or print selector names

SNAvoid

Allow selector names on parsing, but do not print them

SNPrefer

Allow selector names on parsing, print them

SNRequire

Require selector names on parsing, print them

Instances

Instances details
Show SelNamePolicy Source # 
Instance details

Defined in Coalpit

Eq SelNamePolicy Source # 
Instance details

Defined in Coalpit

data Options Source #

Printing and parsing options.

Constructors

Options 

Fields

defOpt :: Options Source #

Default options.

Parsing and composition helpers

escape :: Options -> String -> String Source #

Enquote and escape a string, if it contains any characters that need it.

pString :: Options -> Parsec String m String Source #

Parse a token: either a quoted string or a string without unescaped separators. The opposite of escape.

pFieldSep :: Options -> Parsec String m () Source #

Parse a field separator.

pRecordSep :: Options -> Parsec String m () Source #

Parse a record (line) separator.