{-# LANGUAGE CPP #-}
module Swish.RDF.Parser.NTriples
( ParseResult
, parseNT
)
where
import Swish.GraphClass (arc)
import Swish.Namespace (ScopedName, makeURIScopedName)
import Swish.RDF.Graph (RDFGraph, RDFLabel(..), addArc, emptyRDFGraph)
import Swish.RDF.Vocabulary (LanguageTag, toLangTag)
import Swish.RDF.Parser.Utils (ParseResult
, runParserWithError
, ignore
, skipMany
, noneOf
, char
, string
, eoln
, fullStop
, hex4
, hex8
)
import Control.Applicative
import Network.URI (parseURI)
import qualified Data.Text as T
import qualified Data.Text.Lazy as L
import Data.Char (isAsciiLower, isAsciiUpper, isDigit, ord)
#if MIN_VERSION_base(4, 7, 0)
import Data.Functor (($>))
#endif
import Data.Maybe (fromMaybe)
import Text.ParserCombinators.Poly.StateText
#if !MIN_VERSION_base(4, 7, 0)
($>) :: Functor f => f a -> b -> f b
($>) = flip (<$)
#endif
data NTState = NTState
{ NTState -> RDFGraph
graphState :: RDFGraph
}
emptyState :: NTState
emptyState :: NTState
emptyState = NTState { graphState :: RDFGraph
graphState = RDFGraph
emptyRDFGraph }
updateGraph :: (RDFGraph -> RDFGraph) -> NTState -> NTState
updateGraph :: (RDFGraph -> RDFGraph) -> NTState -> NTState
updateGraph RDFGraph -> RDFGraph
f NTState
s = NTState
s { graphState :: RDFGraph
graphState = RDFGraph -> RDFGraph
f (NTState -> RDFGraph
graphState NTState
s) }
type NTParser a = Parser NTState a
parseNT ::
L.Text
-> ParseResult
parseNT :: Text -> ParseResult
parseNT = forall a. NTParser a -> Text -> Either String a
parsefromText NTParser RDFGraph
ntripleDoc
parsefromText ::
NTParser a
-> L.Text
-> Either String a
parsefromText :: forall a. NTParser a -> Text -> Either String a
parsefromText NTParser a
parser = forall a b. Parser a b -> a -> Text -> Either String b
runParserWithError NTParser a
parser NTState
emptyState
addStatement :: RDFLabel -> RDFLabel -> RDFLabel -> NTParser ()
addStatement :: RDFLabel -> RDFLabel -> RDFLabel -> NTParser ()
addStatement RDFLabel
s RDFLabel
p RDFLabel
o = forall s. (s -> s) -> Parser s ()
stUpdate ((RDFGraph -> RDFGraph) -> NTState -> NTState
updateGraph (forall lb. Label lb => Arc lb -> NSGraph lb -> NSGraph lb
addArc (forall lb. lb -> lb -> lb -> Arc lb
arc RDFLabel
s RDFLabel
p RDFLabel
o) ))
ntripleDoc :: NTParser RDFGraph
ntripleDoc :: NTParser RDFGraph
ntripleDoc = NTState -> RDFGraph
graphState forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (p :: * -> *) a sep. PolyParse p => p a -> p sep -> p [a]
sepBy NTParser ()
line forall s. Parser s ()
eoln forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall s. Parser s ()
eoln forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NTParser ()
skipWS forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall s. Parser s ()
eof forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall s. Parser s s
stGet)
line :: NTParser ()
line :: NTParser ()
line = NTParser ()
skipWS forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (f :: * -> *) a. Applicative f => f a -> f ()
ignore (forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (NTParser ()
comment forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> NTParser ()
triple))
isWS :: Char -> Bool
isWS :: Char -> Bool
isWS = (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (String
" \t" :: String))
skipWS :: NTParser ()
skipWS :: NTParser ()
skipWS = forall (f :: * -> *) a. Applicative f => f a -> f ()
ignore forall a b. (a -> b) -> a -> b
$ forall s. (Char -> Bool) -> Parser s Text
manySatisfy Char -> Bool
isWS
skip1WS :: NTParser ()
skip1WS :: NTParser ()
skip1WS = forall (f :: * -> *) a. Applicative f => f a -> f ()
ignore forall a b. (a -> b) -> a -> b
$ forall s. (Char -> Bool) -> Parser s Text
many1Satisfy Char -> Bool
isWS
comment :: NTParser ()
= forall s. Char -> Parser s Char
char Char
'#' forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall s a. Parser s a -> Parser s ()
skipMany (forall s. String -> Parser s Char
noneOf String
"\r\n")
isaz, isAZ, is09 :: Char -> Bool
isaz :: Char -> Bool
isaz = Char -> Bool
isAsciiLower
isAZ :: Char -> Bool
isAZ = Char -> Bool
isAsciiUpper
is09 :: Char -> Bool
is09 = Char -> Bool
isDigit
isaZ, isaZ09 :: Char -> Bool
isaZ :: Char -> Bool
isaZ Char
c = Char -> Bool
isaz Char
c Bool -> Bool -> Bool
|| Char -> Bool
isAZ Char
c
isaZ09 :: Char -> Bool
isaZ09 Char
c = Char -> Bool
isaZ Char
c Bool -> Bool -> Bool
|| Char -> Bool
is09 Char
c
isHeadChar, isBodyChar :: Char -> Bool
isHeadChar :: Char -> Bool
isHeadChar = Char -> Bool
isaZ
isBodyChar :: Char -> Bool
isBodyChar = Char -> Bool
isaZ09
name :: NTParser L.Text
name :: NTParser Text
name = Char -> Text -> Text
L.cons forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. (Char -> Bool) -> Parser s Char
satisfy Char -> Bool
isHeadChar forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall s. (Char -> Bool) -> Parser s Text
manySatisfy Char -> Bool
isBodyChar
nameStr :: NTParser String
nameStr :: NTParser String
nameStr = Text -> String
L.unpack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NTParser Text
name
triple :: NTParser ()
triple :: NTParser ()
triple =
do
RDFLabel
s <- Parser NTState RDFLabel
subject forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* NTParser ()
skip1WS
RDFLabel
p <- Parser NTState RDFLabel
predicate forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* NTParser ()
skip1WS
RDFLabel
o <- Parser NTState RDFLabel
object forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (NTParser ()
skipWS forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall s. Parser s ()
fullStop forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> NTParser ()
skipWS)
RDFLabel -> RDFLabel -> RDFLabel -> NTParser ()
addStatement RDFLabel
s RDFLabel
p RDFLabel
o
subject :: NTParser RDFLabel
subject :: Parser NTState RDFLabel
subject = Parser NTState RDFLabel
urirefLbl forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser NTState RDFLabel
nodeID
predicate :: NTParser RDFLabel
predicate :: Parser NTState RDFLabel
predicate = Parser NTState RDFLabel
urirefLbl
object :: NTParser RDFLabel
object :: Parser NTState RDFLabel
object = Parser NTState RDFLabel
urirefLbl forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser NTState RDFLabel
nodeID forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser NTState RDFLabel
literal
uriref :: NTParser ScopedName
uriref :: NTParser ScopedName
uriref = do
forall (f :: * -> *) a. Applicative f => f a -> f ()
ignore forall a b. (a -> b) -> a -> b
$ forall s. Char -> Parser s Char
char Char
'<'
String
uri <- forall (p :: * -> *) a z.
(PolyParse p, Show a) =>
p a -> p z -> p [a]
manyFinally' NTParser Char
character (forall s. Char -> Parser s Char
char Char
'>')
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (p :: * -> *) a. PolyParse p => String -> p a
failBad (String
"Invalid URI: <" forall a. [a] -> [a] -> [a]
++ String
uri forall a. [a] -> [a] -> [a]
++ String
">"))
(forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. URI -> ScopedName
makeURIScopedName)
(String -> Maybe URI
parseURI String
uri)
urirefLbl :: NTParser RDFLabel
urirefLbl :: Parser NTState RDFLabel
urirefLbl = ScopedName -> RDFLabel
Res forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NTParser ScopedName
uriref
nodeID :: NTParser RDFLabel
nodeID :: Parser NTState RDFLabel
nodeID = String -> RDFLabel
Blank forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall s. String -> Parser s String
string String
"_:" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NTParser String
nameStr)
literal :: NTParser RDFLabel
literal :: Parser NTState RDFLabel
literal = do
Text
lit <- String -> Text
T.pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NTParser String
ntstring
Maybe (Either LanguageTag ScopedName)
opt <- forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional NTParser (Either LanguageTag ScopedName)
dtlang
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Maybe (Either LanguageTag ScopedName)
opt of
Just (Left LanguageTag
lcode) -> Text -> LanguageTag -> RDFLabel
LangLit Text
lit LanguageTag
lcode
Just (Right ScopedName
dtype) -> Text -> ScopedName -> RDFLabel
TypedLit Text
lit ScopedName
dtype
Maybe (Either LanguageTag ScopedName)
_ -> Text -> RDFLabel
Lit Text
lit
ntstring :: NTParser String
ntstring :: NTParser String
ntstring = forall (p :: * -> *) bra ket a.
PolyParse p =>
p bra -> p ket -> p a -> p a
bracket (forall s. Char -> Parser s Char
char Char
'"') (forall s. Char -> Parser s Char
char Char
'"') (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many NTParser Char
character)
dtlang :: NTParser (Either LanguageTag ScopedName)
dtlang :: NTParser (Either LanguageTag ScopedName)
dtlang =
(forall s. Char -> Parser s Char
char Char
'@' forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (p :: * -> *) a. Commitment p => p a -> p a
commit (forall a b. a -> Either a b
Left forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NTParser LanguageTag
language))
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (forall s. String -> Parser s String
string String
"^^" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (p :: * -> *) a. Commitment p => p a -> p a
commit (forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NTParser ScopedName
uriref))
language :: NTParser LanguageTag
language :: NTParser LanguageTag
language = do
Text
h <- forall s. (Char -> Bool) -> Parser s Text
many1Satisfy Char -> Bool
isaZ
Maybe Text
mt <- forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall a b. (a -> b) -> a -> b
$ Char -> Text -> Text
L.cons forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. Char -> Parser s Char
char Char
'-' forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall s. (Char -> Bool) -> Parser s Text
many1Satisfy Char -> Bool
isaZ09
let lbl :: Text
lbl = Text -> Text
L.toStrict forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
L.append Text
h forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe Text
L.empty Maybe Text
mt
case Text -> Maybe LanguageTag
toLangTag Text
lbl of
Just LanguageTag
lt -> forall (m :: * -> *) a. Monad m => a -> m a
return LanguageTag
lt
Maybe LanguageTag
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Invalid language tag: " forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
lbl)
isAsciiChar :: Char -> Bool
isAsciiChar :: Char -> Bool
isAsciiChar Char
c = let i :: Int
i = Char -> Int
ord Char
c
in Int
i forall a. Ord a => a -> a -> Bool
>= Int
0x20 Bool -> Bool -> Bool
&& Int
i forall a. Ord a => a -> a -> Bool
<= Int
0x21 Bool -> Bool -> Bool
||
Int
i forall a. Ord a => a -> a -> Bool
>= Int
0x23 Bool -> Bool -> Bool
&& Int
i forall a. Ord a => a -> a -> Bool
<= Int
0x5b Bool -> Bool -> Bool
||
Int
i forall a. Ord a => a -> a -> Bool
>= Int
0x5d Bool -> Bool -> Bool
&& Int
i forall a. Ord a => a -> a -> Bool
<= Int
0x7e
protectedChar :: NTParser Char
protectedChar :: NTParser Char
protectedChar =
(forall s. Char -> Parser s Char
char Char
't' forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Char
'\t')
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (forall s. Char -> Parser s Char
char Char
'n' forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Char
'\n')
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (forall s. Char -> Parser s Char
char Char
'r' forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Char
'\r')
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (forall s. Char -> Parser s Char
char Char
'"' forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Char
'"')
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (forall s. Char -> Parser s Char
char Char
'\\' forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Char
'\\')
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (forall s. Char -> Parser s Char
char Char
'u' forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall a. Parser a Char
hex4)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (forall s. Char -> Parser s Char
char Char
'U' forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall a. Parser a Char
hex8)
character :: NTParser Char
character :: NTParser Char
character =
(forall s. Char -> Parser s Char
char Char
'\\' forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NTParser Char
protectedChar)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall s. (Char -> Bool) -> Parser s Char
satisfy Char -> Bool
isAsciiChar