Safe Haskell | None |
---|---|
Language | Haskell98 |
A parser for RDF in N-Triples format http://www.w3.org/TR/rdf-testcases/#ntriples.
Synopsis
- data NTriplesParser = NTriplesParser
- newtype NTriplesParserCustom = NTriplesParserCustom Parser
- data ParseFailure
- nt_echar :: (CharParsing m, Monad m) => m Char
- nt_uchar :: (CharParsing m, Monad m) => m Char
- nt_langtag :: (CharParsing m, Monad m) => m Text
- string_literal_quote :: (CharParsing m, Monad m) => Char -> m Text
- nt_string_literal_quote :: (CharParsing m, Monad m) => m Text
- nt_pn_chars_base :: CharParsing m => m Char
- nt_comment :: CharParsing m => m ()
- readFile :: FilePath -> IO Text
Documentation
data NTriplesParser Source #
NTriplesParser is an RdfParser
implementation for parsing RDF in the
NTriples format. It requires no configuration options. To use this parser,
pass an NTriplesParser
value as the first argument to any of the
parseString
, parseFile
, or parseURL
methods of the RdfParser
type
class.
Instances
RdfParser NTriplesParser Source # |
|
Defined in Text.RDF.RDF4H.NTriplesParser parseString :: Rdf a => NTriplesParser -> Text -> Either ParseFailure (RDF a) Source # parseFile :: Rdf a => NTriplesParser -> String -> IO (Either ParseFailure (RDF a)) Source # parseURL :: Rdf a => NTriplesParser -> String -> IO (Either ParseFailure (RDF a)) Source # |
newtype NTriplesParserCustom Source #
Instances
RdfParser NTriplesParserCustom Source # |
|
Defined in Text.RDF.RDF4H.NTriplesParser parseString :: Rdf a => NTriplesParserCustom -> Text -> Either ParseFailure (RDF a) Source # parseFile :: Rdf a => NTriplesParserCustom -> String -> IO (Either ParseFailure (RDF a)) Source # parseURL :: Rdf a => NTriplesParserCustom -> String -> IO (Either ParseFailure (RDF a)) Source # |
data ParseFailure Source #
Represents a failure in parsing an N-Triples document, including an error message with information about the cause for the failure.
Instances
Eq ParseFailure Source # | |
Defined in Data.RDF.Types (==) :: ParseFailure -> ParseFailure -> Bool # (/=) :: ParseFailure -> ParseFailure -> Bool # | |
Show ParseFailure Source # | |
Defined in Data.RDF.Types showsPrec :: Int -> ParseFailure -> ShowS # show :: ParseFailure -> String # showList :: [ParseFailure] -> ShowS # |
nt_langtag :: (CharParsing m, Monad m) => m Text Source #
string_literal_quote :: (CharParsing m, Monad m) => Char -> m Text Source #
nt_string_literal_quote :: (CharParsing m, Monad m) => m Text Source #
nt_pn_chars_base :: CharParsing m => m Char Source #
nt_comment :: CharParsing m => m () Source #