Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Parsed a
- = Possibly a
- | Definitely a
- parsedValue :: Parsed a -> a
- class Parseable a where
- discardConfidence :: Parsed a -> a
- parse' :: (MonadPlus m, Parseable a) => Text -> m a
- parseIntish :: (Readable a, MonadPlus f) => Text -> f (Parsed a)
- class ColumnTypeable a where
Documentation
Possibly a | |
Definitely a |
parsedValue :: Parsed a -> a Source #
class Parseable a where Source #
Values that can be read from a Text
with more or less
discrimination.
Nothing
parse :: MonadPlus m => Text -> m (Parsed a) Source #
Returns Nothing
if a value of the given type can not be read;
returns 'Just Possibly' if a value can be read, but is likely
ambiguous (e.g. an empty string); returns 'Just Definitely' if a
value can be read and is unlikely to be ambiguous."
parseCombine :: MonadPlus m => Parsed a -> Parsed a -> m (Parsed a) Source #
Combine two parse results such that the combination can
fail. Useful when we have two Possibly
parsed values that are
different enough to suggest the parse of each should be
considered a failure. The default implementation is to return
the first argument.
representableAsType :: Parsed a -> Const (Either (String -> Q [Dec]) Type) a Source #
Instances
Parseable Int32 Source # | |
Parseable Int64 Source # | |
Parseable Text Source # | |
Parseable Integer Source # | |
Parseable Bool Source # | |
Parseable Double Source # | |
Parseable Float Source # | |
Parseable Int Source # | |
KnownNat n => Parseable (Categorical n) Source # | |
Defined in Frames.Categorical parse :: MonadPlus m => Text -> m (Parsed (Categorical n)) Source # parseCombine :: MonadPlus m => Parsed (Categorical n) -> Parsed (Categorical n) -> m (Parsed (Categorical n)) Source # representableAsType :: Parsed (Categorical n) -> Const (Either (String -> Q [Dec]) Type) (Categorical n) Source # |
discardConfidence :: Parsed a -> a Source #
Discard any estimate of a parse's ambiguity.
class ColumnTypeable a where Source #
This class relates a universe of possible column types to Haskell types, and provides a mechanism to infer which type best represents some textual data.
Instances
(RPureConstrained Parseable ts, FoldRec ts ts, RPureConstrained (ShowF ColInfo) ts, RecApplicative ts, Text ∈ ts) => ColumnTypeable (CoRec ColInfo ts) Source # | |