Frames-0.6.1: Data frames For working with tabular data files

Safe HaskellNone
LanguageHaskell2010

Frames.ColumnTypeable

Synopsis

Documentation

data Parsed a Source #

Constructors

Possibly a 
Definitely a 
Instances
Functor Parsed Source # 
Instance details

Defined in Frames.ColumnTypeable

Methods

fmap :: (a -> b) -> Parsed a -> Parsed b #

(<$) :: a -> Parsed b -> Parsed a #

Eq a => Eq (Parsed a) Source # 
Instance details

Defined in Frames.ColumnTypeable

Methods

(==) :: Parsed a -> Parsed a -> Bool #

(/=) :: Parsed a -> Parsed a -> Bool #

Ord a => Ord (Parsed a) Source # 
Instance details

Defined in Frames.ColumnTypeable

Methods

compare :: Parsed a -> Parsed a -> Ordering #

(<) :: Parsed a -> Parsed a -> Bool #

(<=) :: Parsed a -> Parsed a -> Bool #

(>) :: Parsed a -> Parsed a -> Bool #

(>=) :: Parsed a -> Parsed a -> Bool #

max :: Parsed a -> Parsed a -> Parsed a #

min :: Parsed a -> Parsed a -> Parsed a #

Show a => Show (Parsed a) Source # 
Instance details

Defined in Frames.ColumnTypeable

Methods

showsPrec :: Int -> Parsed a -> ShowS #

show :: Parsed a -> String #

showList :: [Parsed a] -> ShowS #

class Parseable a where Source #

Values that can be read from a Text with more or less discrimination.

Minimal complete definition

Nothing

Methods

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."

parse :: (Readable a, 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.

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 #

representableAsType :: Typeable a => Parsed a -> Const (Either (String -> Q [Dec]) Type) a Source #

Instances
Parseable Bool Source # 
Instance details

Defined in Frames.ColumnTypeable

Parseable Double Source # 
Instance details

Defined in Frames.ColumnTypeable

Parseable Float Source # 
Instance details

Defined in Frames.ColumnTypeable

Parseable Int Source # 
Instance details

Defined in Frames.ColumnTypeable

Parseable Int32 Source # 
Instance details

Defined in Frames.ColumnTypeable

Parseable Int64 Source # 
Instance details

Defined in Frames.ColumnTypeable

Parseable Integer Source # 
Instance details

Defined in Frames.ColumnTypeable

Parseable Text Source # 
Instance details

Defined in Frames.ColumnTypeable

KnownNat n => Parseable (Categorical n) Source # 
Instance details

Defined in Frames.Categorical

discardConfidence :: Parsed a -> a Source #

Discard any estimate of a parse's ambiguity.

parse' :: (MonadPlus m, Parseable a) => Text -> m a Source #

Acts just like fromText: tries to parse a value from a Text and discards any estimate of the 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.

Methods

colType :: a -> Either (String -> Q [Dec]) Type Source #

inferType :: Text -> a Source #

Instances
(RPureConstrained Parseable ts, FoldRec ts ts, RecApplicative ts, Text ts) => ColumnTypeable (CoRec ColInfo ts) Source # 
Instance details

Defined in Frames.ColumnUniverse