Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Class used for parsing command-line options.
Synopsis
- class Parseable a where
- maybeParse :: (String -> Maybe a) -> [String] -> (Maybe a, Int)
- boundedParse :: (String -> BoundedRead a) -> [String] -> (Maybe a, Int)
- repeatedParse :: Parseable a => Int -> [String] -> (Maybe [a], Int)
- simpleParse :: (String -> Maybe a) -> [String] -> (Maybe a, Int)
Documentation
class Parseable a where Source #
Class describing parseable values. Much like the Read
class.
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. |
Parseable Double Source # | |
Parseable Float Source # | |
Parseable Int Source # | Parses an |
Parseable Integer Source # | |
Parseable Word Source # | Parses a |
Parseable () Source # | Always succeeds and never consumes any input. |
Parseable SomeSymbol Source # | Opaque identity parser for Ex: > parse [""] == (Just (SomeSymbol (Proxy :: Proxy "")), 1) > parse ["foo"] == (Just (SomeSymbol (Proxy :: Proxy "foo")), 1) > parse [] == (Nothing, 0) |
Defined in Text.LambdaOptions.Parseable | |
Parseable SomeNat Source # | Parses a Ex: > parse ["0"] == (Just (Proxy :: SomeNat (Proxy 0)), 1) > parse ["13"] == (Just (Proxy :: SomeNat (Proxy 13)), 1) > parse ["00"] == Nothing > parse ["0xFF"] == Nothing |
Parseable String Source # | Identity parser. parse [""] == (Just "", 1) parse ["foo"] == (Just "foo", 1) parse [] == (Nothing, 0) |
Parseable a => Parseable (Maybe a) Source # | Greedily parses a single argument or no argument. Never fails. |
Parseable a => Parseable (List a) Source # | Greedily parses arguments item-wise. Never fails. Example:
|
(Parseable a, Parseable b) => Parseable (a, b) Source # | Parses two values sequentially. |
KnownNat n => Parseable (Proxy n) Source # | Parses a Ex: > parse ["0"] == (Just (Proxy :: Proxy 0), 1) > parse ["13"] == (Just (Proxy :: Proxy 13), 1) > parse ["00"] == Nothing > parse ["0xFF"] == Nothing |
KnownSymbol s => Parseable (Proxy s) Source # | Parses the exact string given by Ex: > parse [""] == (Just (Proxy :: Proxy ""), 1) > parse ["foo"] == (Just (Proxy :: Proxy "foo"), 1) > parse ["foo"] == (Nothing :: Maybe (Proxy :: "bar"), 0) > parse [] == (Nothing, 0) |
(Parseable a, Parseable b, Parseable c) => Parseable (a, b, c) Source # | Parses three values sequentially. |
(ReadBoolWord w, ReadBoolLetter l, ReadBoolNumber n, BoolCasingVal c) => Parseable (Booly w l n c) Source # | |
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 readBounded
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.