lambda-options-1.0.1.0: Declarative command-line parser using type-driven pattern matching.

Safe HaskellSafe
LanguageHaskell2010

Text.LambdaOptions.Parseable

Description

Class used for parsing command-line options.

Synopsis

Documentation

class Parseable a where Source #

Class describing parseable values. Much like the Read class.

Methods

parse :: [String] -> (Maybe a, Int) Source #

Given a sequence of strings, parse returns Nothing and the number of strings (not characters) consumed if the parse failed. Otherwise, parse returns Just the parsed value and the number of strings consumed.

Element-wise, an entire string must be parsed in the sequence to be considered a successful parse.

Instances
Parseable Char Source #

Parses a single character string.

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe Char, Int) Source #

Parseable Double Source #

Parses an Double using its Read instance.

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe Double, Int) Source #

Parseable Float Source #

Parses a Float using its Read instance.

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe Float, Int) Source #

Parseable Int Source #

Parses an Int using its ReadBounded instance.

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe Int, Int) Source #

Parseable Integer Source #

Parses an Integer using its Read instance.

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe Integer, Int) Source #

Parseable Word Source #

Parses a Word using its ReadBounded instance.

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe Word, Int) Source #

Parseable () Source #

Always succeeds and never consumes any input.

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe (), Int) Source #

Parseable SomeSymbol Source #

Opaque identity parser for SymbolVal.

Ex: parse [""] == (Just (SomeSymbol (Proxy :: Proxy "")), 1) parse ["foo"] == (Just (SomeSymbol (Proxy :: Proxy "foo")), 1) parse [] == (Nothing, 0)

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe SomeSymbol, Int) Source #

Parseable SomeNat Source #

Parses a SomeNat by matching its corresponding shown natVal.

Ex: parse ["0"] == (Just (Proxy :: SomeNat (Proxy 0)), 1) parse ["13"] == (Just (Proxy :: SomeNat (Proxy 13)), 1) parse ["00"] == Nothing parse ["0xFF"] == Nothing

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe SomeNat, Int) Source #

Parseable String Source #

Identity parser.

 parse [""] == (Just "", 1)
 parse ["foo"] == (Just "foo", 1)
 parse [] == (Nothing, 0)
Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe String, Int) Source #

Parseable a => Parseable (Maybe a) Source #

Greedily parses a single argument or no argument. Never fails.

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe (Maybe a), Int) Source #

Parseable a => Parseable (List a) Source #

Greedily parses arguments item-wise. Never fails.

Example: parse (words "5 67 NaN") == (Just (List [5,67]), 2)

Instance details

Defined in Text.LambdaOptions.List

Methods

parse :: [String] -> (Maybe (List a), Int) Source #

(Parseable a, Parseable b) => Parseable (a, b) Source #

Parses two values sequentially.

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe (a, b), Int) Source #

KnownNat n => Parseable (Proxy n) Source #

Parses a KnownNat by matching its corresponding shown natVal.

Ex: parse ["0"] == (Just (Proxy :: Proxy 0), 1) parse ["13"] == (Just (Proxy :: Proxy 13), 1) parse ["00"] == Nothing parse ["0xFF"] == Nothing

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe (Proxy n), Int) Source #

KnownSymbol s => Parseable (Proxy s) Source #

Parses the exact string given by symbolVal.

Ex: parse [""] == (Just (Proxy :: Proxy ""), 1) parse ["foo"] == (Just (Proxy :: Proxy "foo"), 1) parse ["foo"] == (Nothing :: Maybe (Proxy :: "bar"), 0) parse [] == (Nothing, 0)

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe (Proxy s), Int) Source #

(Parseable a, Parseable b, Parseable c) => Parseable (a, b, c) Source #

Parses three values sequentially.

Instance details

Defined in Text.LambdaOptions.Parseable

Methods

parse :: [String] -> (Maybe (a, b, c), Int) Source #

(ReadBoolWord w, ReadBoolLetter l, ReadBoolNumber n, BoolCasingVals c) => Parseable (Booly w l n c) Source # 
Instance details

Defined in Text.LambdaOptions.Bool

Methods

parse :: [String] -> (Maybe (Booly w l n c), Int) Source #

maybeParse :: (String -> Maybe a) -> [String] -> (Maybe a, Int) Source #

Turns a parser of a single string into a parser suitable for a Parseable instance.

Useful for implementing a Parseable for a type with a Read instance by supplying readMaybe to this function.

Note: The string is not tokenized in any way before being passed into the input parser.

boundedParse :: (String -> BoundedRead a) -> [String] -> (Maybe a, Int) Source #

Turns a parser of a single string into a parser suitable for a Parseable instance.

Useful for implementing a Parseable for a type with a ReadBounded instance by supplying readMaybe to this function.

Note: The string is not tokenized in any way before being passed into the input parser.

repeatedParse :: Parseable a => Int -> [String] -> (Maybe [a], Int) Source #

Repeatedly applies parse the given number of times, accumulating the results.

Useful for implementing new parsers.

Example:

 data Point = Point Float Float Float

 instance Parseable Point where
   parse args = case repeatedParse 3 args of
     (Just [x,y,z], n) -> (Just (Point x y z), n)`
     (Nothing, n) -> (Nothing, n)

simpleParse :: (String -> Maybe a) -> [String] -> (Maybe a, Int) Source #

Deprecated: Use maybeParse instead.

Deprecated: Use maybeParse instead.