parsable-0.1.0.0: Parsable and Printable classes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Parsable

Description

This module contains two simple classes, Parsable and Printable.

There is an implicit "soft isomorphism" between parser and toString. (Successfully parsing a string and then running toString on the result should result in the original string.)

Language extensions

Because parser does not take any arguments, it may be necessary to explicitly declare the type of t for these functions.

It may be helpful to enable and use the TypeApplications and possibly ScopedTypeVariables extensions..

Look at the Language Extensions section of the GHC documentation for instructions on how to use these extensions.

Synopsis

Parsing

class Parsable a (m :: Type -> Type) u s where Source #

Represents types that have a valid Parsec parser.

Methods

parser :: ParsecT s u m a Source #

parserName :: ParserName a s u m Source #

Instances

Instances details
(Stream s m Char, Read a, Typeable a) => Parsable (NaturalParsable a) m u s Source # 
Instance details

Defined in Data.Parsable

newtype ParserName a s u (m :: Type -> Type) Source #

Constructors

ParserName 

Instances

Instances details
IsString (ParserName a s u m) Source # 
Instance details

Defined in Data.Parsable

Methods

fromString :: String -> ParserName a s u m #

Show (ParserName a s u m) Source # 
Instance details

Defined in Data.Parsable

Methods

showsPrec :: Int -> ParserName a s u m -> ShowS #

show :: ParserName a s u m -> String #

showList :: [ParserName a s u m] -> ShowS #

Eq (ParserName a s u m) Source # 
Instance details

Defined in Data.Parsable

Methods

(==) :: ParserName a s u m -> ParserName a s u m -> Bool #

(/=) :: ParserName a s u m -> ParserName a s u m -> Bool #

Ord (ParserName a s u m) Source # 
Instance details

Defined in Data.Parsable

Methods

compare :: ParserName a s u m -> ParserName a s u m -> Ordering #

(<) :: ParserName a s u m -> ParserName a s u m -> Bool #

(<=) :: ParserName a s u m -> ParserName a s u m -> Bool #

(>) :: ParserName a s u m -> ParserName a s u m -> Bool #

(>=) :: ParserName a s u m -> ParserName a s u m -> Bool #

max :: ParserName a s u m -> ParserName a s u m -> ParserName a s u m #

min :: ParserName a s u m -> ParserName a s u m -> ParserName a s u m #

runParsableT :: forall a m s. (Stream s m Char, Parsable a m () s) => String -> s -> m (Either ParseError a) Source #

Convenience function to run a Parsable parser.

runParsable :: forall a s. (Stream s Identity Char, Parsable a Identity () s) => String -> s -> Either ParseError a Source #

Wrappers

newtype NaturalParsable a Source #

Constructors

NaturalParsable 

Instances

Instances details
(Stream s m Char, Read a, Typeable a) => Parsable (NaturalParsable a) m u s Source # 
Instance details

Defined in Data.Parsable

Parsing functions

satisfyAny :: Stream s m Char => [Char -> Bool] -> ParsecT s u m Char Source #

Parse a token that satisfies any of the given predicates

wordAllowed Source #

Arguments

:: Stream s m Char 
=> [Char -> Bool]

Tokens that start the word

-> [Char -> Bool]

Any subsequent tokens

-> ParsecT s u m [Char] 

Parsing of "words" which require a list of predicates for the first token, and a list of predicates for any remaining tokens. This always parses at least one token.

readParsec :: forall a s u m. (Typeable a, Read a) => String -> ParsecT s u m a Source #

Pass a previously-parsed string to this function in order to attempt using read. Produces proper error messages on failure.

Printing

class Printable t where Source #

Types that can be converted back to a String.

Minimal complete definition

toString

Methods

toString :: t -> String Source #

default toString :: Show t => t -> String Source #

Instances

Instances details
Printable Text Source # 
Instance details

Defined in Data.Parsable

Methods

toString :: Text -> String Source #

Printable String Source # 
Instance details

Defined in Data.Parsable

Show a => Printable (ShowPrintable a) Source #

Uses show after unwrapping the contents.

Instance details

Defined in Data.Parsable

toText :: (Printable t, IsString s) => t -> s Source #

Convenience function that will turn a Printable to any IsString.

Wrappers

newtype ShowPrintable a Source #

Wrapper for types that inherit toString directly from their Show instance.

It is convenient to use the DerivingVia language extension with this.

{-# Language DerivingVia #-}

newtype MyNum Int
    deriving Printable via (ShowPrintable Int) -- Uses Show instance of Int

Constructors

ShowPrintable 

Fields

Instances

Instances details
Foldable ShowPrintable Source # 
Instance details

Defined in Data.Parsable

Methods

fold :: Monoid m => ShowPrintable m -> m #

foldMap :: Monoid m => (a -> m) -> ShowPrintable a -> m #

foldMap' :: Monoid m => (a -> m) -> ShowPrintable a -> m #

foldr :: (a -> b -> b) -> b -> ShowPrintable a -> b #

foldr' :: (a -> b -> b) -> b -> ShowPrintable a -> b #

foldl :: (b -> a -> b) -> b -> ShowPrintable a -> b #

foldl' :: (b -> a -> b) -> b -> ShowPrintable a -> b #

foldr1 :: (a -> a -> a) -> ShowPrintable a -> a #

foldl1 :: (a -> a -> a) -> ShowPrintable a -> a #

toList :: ShowPrintable a -> [a] #

null :: ShowPrintable a -> Bool #

length :: ShowPrintable a -> Int #

elem :: Eq a => a -> ShowPrintable a -> Bool #

maximum :: Ord a => ShowPrintable a -> a #

minimum :: Ord a => ShowPrintable a -> a #

sum :: Num a => ShowPrintable a -> a #

product :: Num a => ShowPrintable a -> a #

Traversable ShowPrintable Source # 
Instance details

Defined in Data.Parsable

Methods

traverse :: Applicative f => (a -> f b) -> ShowPrintable a -> f (ShowPrintable b) #

sequenceA :: Applicative f => ShowPrintable (f a) -> f (ShowPrintable a) #

mapM :: Monad m => (a -> m b) -> ShowPrintable a -> m (ShowPrintable b) #

sequence :: Monad m => ShowPrintable (m a) -> m (ShowPrintable a) #

Applicative ShowPrintable Source # 
Instance details

Defined in Data.Parsable

Functor ShowPrintable Source # 
Instance details

Defined in Data.Parsable

Methods

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

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

Monad ShowPrintable Source # 
Instance details

Defined in Data.Parsable

Generic1 ShowPrintable Source # 
Instance details

Defined in Data.Parsable

Associated Types

type Rep1 ShowPrintable :: k -> Type #

Methods

from1 :: forall (a :: k). ShowPrintable a -> Rep1 ShowPrintable a #

to1 :: forall (a :: k). Rep1 ShowPrintable a -> ShowPrintable a #

Data a => Data (ShowPrintable a) Source # 
Instance details

Defined in Data.Parsable

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShowPrintable a -> c (ShowPrintable a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ShowPrintable a) #

toConstr :: ShowPrintable a -> Constr #

dataTypeOf :: ShowPrintable a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ShowPrintable a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ShowPrintable a)) #

gmapT :: (forall b. Data b => b -> b) -> ShowPrintable a -> ShowPrintable a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShowPrintable a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShowPrintable a -> r #

gmapQ :: (forall d. Data d => d -> u) -> ShowPrintable a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ShowPrintable a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShowPrintable a -> m (ShowPrintable a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShowPrintable a -> m (ShowPrintable a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShowPrintable a -> m (ShowPrintable a) #

IsString a => IsString (ShowPrintable a) Source # 
Instance details

Defined in Data.Parsable

Monoid a => Monoid (ShowPrintable a) Source # 
Instance details

Defined in Data.Parsable

Semigroup a => Semigroup (ShowPrintable a) Source # 
Instance details

Defined in Data.Parsable

Bounded a => Bounded (ShowPrintable a) Source # 
Instance details

Defined in Data.Parsable

Enum a => Enum (ShowPrintable a) Source # 
Instance details

Defined in Data.Parsable

Floating a => Floating (ShowPrintable a) Source # 
Instance details

Defined in Data.Parsable

Generic (ShowPrintable a) Source # 
Instance details

Defined in Data.Parsable

Associated Types

type Rep (ShowPrintable a) :: Type -> Type #

Num a => Num (ShowPrintable a) Source # 
Instance details

Defined in Data.Parsable

Read a => Read (ShowPrintable a) Source # 
Instance details

Defined in Data.Parsable

Fractional a => Fractional (ShowPrintable a) Source # 
Instance details

Defined in Data.Parsable

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

Defined in Data.Parsable

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

Defined in Data.Parsable

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

Defined in Data.Parsable

Show a => Printable (ShowPrintable a) Source #

Uses show after unwrapping the contents.

Instance details

Defined in Data.Parsable

type Rep1 ShowPrintable Source # 
Instance details

Defined in Data.Parsable

type Rep1 ShowPrintable = D1 ('MetaData "ShowPrintable" "Data.Parsable" "parsable-0.1.0.0-8GIQ9IPea3WAJjcRP81G2D" 'True) (C1 ('MetaCons "ShowPrintable" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapShowPrintable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (ShowPrintable a) Source # 
Instance details

Defined in Data.Parsable

type Rep (ShowPrintable a) = D1 ('MetaData "ShowPrintable" "Data.Parsable" "parsable-0.1.0.0-8GIQ9IPea3WAJjcRP81G2D" 'True) (C1 ('MetaCons "ShowPrintable" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapShowPrintable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Re-exports

module Data.Char