| Safe Haskell | None | 
|---|
Data.Textual
Contents
Description
- class Printable α where
 - maybePrint :: (Printer p, Printable α) => Maybe α -> p
 - toString :: Printable α => α -> String
 - toText :: Printable α => α -> Text
 - toLazyText :: Printable α => α -> Text
 - toAscii :: Printable α => α -> ByteString
 - toLazyAscii :: Printable α => α -> ByteString
 - toUtf8 :: Printable α => α -> ByteString
 - toLazyUtf8 :: Printable α => α -> ByteString
 - class Printable α => Textual α  where
- textual :: (Monad μ, CharParsing μ) => μ α
 
 - data Parsed α
 - isParsed :: Parsed α -> Bool
 - isMalformed :: Parsed α -> Bool
 - maybeParsed :: Parsed α -> Maybe α
 - builtInParser :: (forall μ. (Monad μ, CharParsing μ) => μ α) -> String -> Parsed α
 - parseString :: Textual α => String -> Parsed α
 - parseStringAs :: Textual α => p α -> String -> Parsed α
 - parseText :: Textual α => Text -> Parsed α
 - parseTextAs :: Textual α => p α -> Text -> Parsed α
 - parseLazyText :: Textual α => Text -> Parsed α
 - parseLazyTextAs :: Textual α => p α -> Text -> Parsed α
 - parseAscii :: Textual α => ByteString -> Parsed α
 - parseAsciiAs :: Textual α => p α -> ByteString -> Parsed α
 - parseLazyAscii :: Textual α => ByteString -> Parsed α
 - parseLazyAsciiAs :: Textual α => ByteString -> Parsed α
 - parseUtf8 :: Textual α => ByteString -> Parsed α
 - parseUtf8As :: Textual α => p α -> ByteString -> Parsed α
 - parseLazyUtf8 :: Textual α => ByteString -> Parsed α
 - parseLazyUtf8As :: Textual α => p α -> ByteString -> Parsed α
 - fromString :: Textual α => String -> Maybe α
 - fromStringAs :: Textual α => p α -> String -> Maybe α
 - fromText :: Textual α => Text -> Maybe α
 - fromTextAs :: Textual α => p α -> Text -> Maybe α
 - fromLazyText :: Textual α => Text -> Maybe α
 - fromLazyTextAs :: Textual α => p α -> Text -> Maybe α
 - fromAscii :: Textual α => ByteString -> Maybe α
 - fromAsciiAs :: Textual α => p α -> ByteString -> Maybe α
 - fromLazyAscii :: Textual α => ByteString -> Maybe α
 - fromLazyAsciiAs :: Textual α => p α -> ByteString -> Maybe α
 - fromUtf8 :: Textual α => ByteString -> Maybe α
 - fromUtf8As :: Textual α => p α -> ByteString -> Maybe α
 - fromLazyUtf8 :: Textual α => ByteString -> Maybe α
 - fromLazyUtf8As :: Textual α => p α -> ByteString -> Maybe α
 
Printing
The default printer for values of a type.
Instances
toLazyText :: Printable α => α -> TextSource
A shorthand for .
buildLazyText . print
toAscii :: Printable α => α -> ByteStringSource
A shorthand for .
buildAscii . print
toLazyAscii :: Printable α => α -> ByteStringSource
A shorthand for .
buildLazyAscii . print
toLazyUtf8 :: Printable α => α -> ByteStringSource
A shorthand for .
buildLazyUtf8 . print
Parsing
class Printable α => Textual α whereSource
The default parser for values of a type, must satisfy
   
     
fromString (toString x) = Just x
   
Methods
textual :: (Monad μ, CharParsing μ) => μ αSource
Built-in parser
Parsing result.
builtInParser :: (forall μ. (Monad μ, CharParsing μ) => μ α) -> String -> Parsed αSource
Use the built-in parser to parse a string. Intended for testing only.
parseStringAs :: Textual α => p α -> String -> Parsed αSource
Provide a hint for the type system when using parseString.
parseTextAs :: Textual α => p α -> Text -> Parsed αSource
Provide a hint for the type system when using parseText.
parseLazyTextAs :: Textual α => p α -> Text -> Parsed αSource
Provide a hint for the type system when using parseLazyText.
parseAscii :: Textual α => ByteString -> Parsed αSource
Decode and parse an ASCII ByteString to extract the Textual value.
parseAsciiAs :: Textual α => p α -> ByteString -> Parsed αSource
Provide a hint for the type system when using parseAscii.
parseLazyAscii :: Textual α => ByteString -> Parsed αSource
Decode and parse a lazy ASCII ByteString to extract
   the Textual value.
parseLazyAsciiAs :: Textual α => ByteString -> Parsed αSource
Provide a hint for the type system when using parseLazyAscii.
parseUtf8 :: Textual α => ByteString -> Parsed αSource
Decode and parse a UTF-8 ByteString to extract the Textual value.
parseUtf8As :: Textual α => p α -> ByteString -> Parsed αSource
Provide a hint for the type system when using parseUtf8.
parseLazyUtf8 :: Textual α => ByteString -> Parsed αSource
Decode and parse a lazy UTF-8 ByteString to extract
   the Textual value.
parseLazyUtf8As :: Textual α => p α -> ByteString -> Parsed αSource
Provide a hint for the type system when using parseLazyUtf8.
fromString :: Textual α => String -> Maybe αSource
A shorthand for maybeParsed . parseString
fromStringAs :: Textual α => p α -> String -> Maybe αSource
Provide a hint for the type system when using fromString.
fromTextAs :: Textual α => p α -> Text -> Maybe αSource
Provide a hint for the type system when using fromText.
fromLazyText :: Textual α => Text -> Maybe αSource
A shorthand for maybeParsed . parseLazyText
fromLazyTextAs :: Textual α => p α -> Text -> Maybe αSource
Provide a hint for the type system when using fromLazyText.
fromAscii :: Textual α => ByteString -> Maybe αSource
A shorthand for maybeParsed . parseAscii
fromAsciiAs :: Textual α => p α -> ByteString -> Maybe αSource
Provide a hint for the type system when using fromAscii.
fromLazyAscii :: Textual α => ByteString -> Maybe αSource
A shorthand for maybeParsed . parseLazyAscii
fromLazyAsciiAs :: Textual α => p α -> ByteString -> Maybe αSource
Provide a hint for the type system when using fromLazyAscii.
fromUtf8 :: Textual α => ByteString -> Maybe αSource
A shorthand for maybeParsed . parseUtf8
fromUtf8As :: Textual α => p α -> ByteString -> Maybe αSource
Provide a hint for the type system when using fromUtf8.
fromLazyUtf8 :: Textual α => ByteString -> Maybe αSource
A shorthand for maybeParsed . parseLazyUtf8
fromLazyUtf8As :: Textual α => p α -> ByteString -> Maybe αSource
Provide a hint for the type system when using fromLazyUtf8.