{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Swish.Script
(
parseScriptFromText
)
where
import Swish.Datatype (typeMkRules)
import Swish.Monad ( SwishStateIO, SwishStatus(..))
import Swish.Monad (modGraphs, findGraph, findFormula
, modRules, findRule
, modRulesets, findRuleset
, findOpenVarModify, findDatatype
, setInfo, setError, setStatus)
import Swish.Proof (explainProof, showsProof)
import Swish.Rule (Formula(..), Rule(..))
import Swish.Ruleset (makeRuleset, getRulesetRule, getRulesetNamespace, getMaybeContextRule)
import Swish.VarBinding (composeSequence)
import Swish.RDF.Datatype (RDFDatatype)
import Swish.RDF.Ruleset (RDFFormula, RDFRule, RDFRuleset)
import Swish.RDF.Ruleset (makeRDFClosureRule)
import Swish.RDF.Proof (RDFProofStep)
import Swish.RDF.Proof (makeRDFProof, makeRDFProofStep)
import Swish.RDF.VarBinding (RDFVarBindingModify)
import Swish.RDF.GraphShowLines ()
import Swish.RDF.Graph
( RDFGraph, RDFLabel(..)
, NamespaceMap
, setNamespaces
, merge, addGraphs
)
import Swish.RDF.Parser.Utils (whiteSpace, lexeme, symbol, eoln, manyTill)
import Swish.RDF.Parser.N3
( parseAnyfromText
, parseN3
, N3Parser, N3State(..)
, getPrefix
, subgraph
, n3symbol
, quickVariable
, lexUriRef
, newBlankNode
)
import Swish.Namespace (ScopedName, getScopeNamespace)
import Swish.QName (QName, qnameFromURI)
import Swish.RDF.Formatter.N3 (formatGraphAsBuilder)
import Swish.Utils.ListHelpers (flist)
import Text.ParserCombinators.Poly.StateText
import Control.Monad (unless, when, void)
import Control.Monad.State (modify, gets, lift)
#if (!defined(__GLASGOW_HASKELL__)) || (__GLASGOW_HASKELL__ < 710)
import Data.Monoid (Monoid(..))
#endif
#if MIN_VERSION_base(4, 7, 0)
import Data.Functor (($>))
#endif
import Network.URI (URI(..))
import qualified Control.Exception as CE
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Text.Lazy as L
import qualified Data.Text.Lazy.Builder as B
import qualified Data.Text.Lazy.IO as LIO
import qualified System.IO.Error as IO
#if !MIN_VERSION_base(4, 7, 0)
($>) :: Functor f => f a -> b -> f b
($>) = flip (<$)
#endif
parseScriptFromText ::
Maybe QName
-> L.Text
-> Either String [SwishStateIO ()]
parseScriptFromText :: Maybe QName -> Text -> Either [Char] [SwishStateIO ()]
parseScriptFromText = forall a. N3Parser a -> Maybe QName -> Text -> Either [Char] a
parseAnyfromText N3Parser [SwishStateIO ()]
script
between :: Parser s lbr -> Parser s rbr -> Parser s a -> Parser s a
between :: forall s lbr rbr a.
Parser s lbr -> Parser s rbr -> Parser s a -> Parser s a
between = forall (p :: * -> *) bra ket a.
PolyParse p =>
p bra -> p ket -> p a -> p a
bracket
n3SymLex :: N3Parser ScopedName
n3SymLex :: N3Parser ScopedName
n3SymLex = forall s a. Parser s a -> Parser s a
lexeme N3Parser ScopedName
n3symbol
setTo :: N3Parser ()
setTo :: N3Parser ()
setTo = [Char] -> N3Parser ()
isymbol [Char]
":-"
semicolon :: N3Parser ()
semicolon :: N3Parser ()
semicolon = [Char] -> N3Parser ()
isymbol [Char]
";"
comma :: N3Parser ()
comma :: N3Parser ()
comma = [Char] -> N3Parser ()
isymbol [Char]
","
commentText :: N3Parser String
= N3Parser ()
semicolon forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> N3Parser [Char]
restOfLine
script :: N3Parser [SwishStateIO ()]
script :: N3Parser [SwishStateIO ()]
script = do
forall s. Parser s ()
whiteSpace
[SwishStateIO ()]
scs <- forall (f :: * -> *) a. Alternative f => f a -> f [a]
many N3Parser (SwishStateIO ())
command
forall s. Parser s ()
eof
forall (m :: * -> *) a. Monad m => a -> m a
return [SwishStateIO ()]
scs
isymbol :: String -> N3Parser ()
isymbol :: [Char] -> N3Parser ()
isymbol = forall (f :: * -> *) a. Functor f => f a -> f ()
void forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. [Char] -> Parser s [Char]
symbol
command :: N3Parser (SwishStateIO ())
command :: N3Parser (SwishStateIO ())
command =
N3Parser (SwishStateIO ())
prefixLine
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> N3Parser (SwishStateIO ())
nameItem
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> N3Parser (SwishStateIO ())
readGraph
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> N3Parser (SwishStateIO ())
writeGraph
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> N3Parser (SwishStateIO ())
mergeGraphs
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> N3Parser (SwishStateIO ())
compareGraphs
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> N3Parser (SwishStateIO ())
assertEquiv
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> N3Parser (SwishStateIO ())
assertMember
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> N3Parser (SwishStateIO ())
defineRule
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> N3Parser (SwishStateIO ())
defineRuleset
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> N3Parser (SwishStateIO ())
defineConstraints
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> N3Parser (SwishStateIO ())
checkProofCmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> N3Parser (SwishStateIO ())
fwdChain
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> N3Parser (SwishStateIO ())
bwdChain
prefixLine :: N3Parser (SwishStateIO ())
prefixLine :: N3Parser (SwishStateIO ())
prefixLine = do
[Char] -> N3Parser ()
isymbol [Char]
"@prefix"
N3Parser ()
getPrefix
forall s. Parser s ()
whiteSpace
[Char] -> N3Parser ()
isymbol [Char]
"."
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return ()
nameItem :: N3Parser (SwishStateIO ())
nameItem :: N3Parser (SwishStateIO ())
nameItem =
ScopedName
-> [SwishStateIO (Either [Char] RDFGraph)] -> SwishStateIO ()
ssAddGraph forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser ScopedName
n3SymLex forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall s. [Char] -> Parser s [Char]
symbol [Char]
":-" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser N3State [SwishStateIO (Either [Char] RDFGraph)]
graphOrList)
maybeURI :: N3Parser (Maybe URI)
maybeURI :: N3Parser (Maybe URI)
maybeURI = (forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser URI
lexUriRef) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
readGraph :: N3Parser (SwishStateIO ())
readGraph :: N3Parser (SwishStateIO ())
readGraph = [Char] -> N3Parser ()
commandName [Char]
"@read" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ScopedName -> Maybe URI -> SwishStateIO ()
ssRead forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser ScopedName
n3SymLex forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> N3Parser (Maybe URI)
maybeURI)
writeGraph :: N3Parser (SwishStateIO ())
writeGraph :: N3Parser (SwishStateIO ())
writeGraph =
do { [Char] -> N3Parser ()
commandName [Char]
"@write"
; ScopedName
n <- N3Parser ScopedName
n3SymLex
; let gs :: SwishStateIO (Either [Char] [RDFGraph])
gs = ScopedName -> SwishStateIO (Either [Char] [RDFGraph])
ssGetList ScopedName
n :: SwishStateIO (Either String [RDFGraph])
; Maybe URI
muri <- N3Parser (Maybe URI)
maybeURI
; Maybe URI
-> SwishStateIO (Either [Char] [RDFGraph])
-> [Char]
-> SwishStateIO ()
ssWriteList Maybe URI
muri SwishStateIO (Either [Char] [RDFGraph])
gs forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser [Char]
commentText
}
mergeGraphs :: N3Parser (SwishStateIO ())
mergeGraphs :: N3Parser (SwishStateIO ())
mergeGraphs = do
[Char] -> N3Parser ()
commandName [Char]
"@merge"
[SwishStateIO (Either [Char] RDFGraph)]
gs <- Parser N3State [SwishStateIO (Either [Char] RDFGraph)]
graphList
[Char] -> N3Parser ()
isymbol [Char]
"=>"
ScopedName
n <- N3Parser ScopedName
n3SymLex
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ScopedName
-> [SwishStateIO (Either [Char] RDFGraph)] -> SwishStateIO ()
ssMerge ScopedName
n [SwishStateIO (Either [Char] RDFGraph)]
gs
compareGraphs :: N3Parser (SwishStateIO ())
compareGraphs :: N3Parser (SwishStateIO ())
compareGraphs =
[Char] -> N3Parser ()
commandName [Char]
"@compare" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ScopedName -> ScopedName -> SwishStateIO ()
ssCompare forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser ScopedName
n3SymLex forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> N3Parser ScopedName
n3SymLex)
assertArgs :: (ScopedName -> ScopedName -> String -> SwishStateIO ())
-> String -> N3Parser (SwishStateIO ())
assertArgs :: (ScopedName -> ScopedName -> [Char] -> SwishStateIO ())
-> [Char] -> N3Parser (SwishStateIO ())
assertArgs ScopedName -> ScopedName -> [Char] -> SwishStateIO ()
assertFunc [Char]
cName = do
[Char] -> N3Parser ()
commandName forall a b. (a -> b) -> a -> b
$ Char
'@'forall a. a -> [a] -> [a]
:[Char]
cName
ScopedName -> ScopedName -> [Char] -> SwishStateIO ()
assertFunc forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser ScopedName
n3SymLex forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> N3Parser ScopedName
n3SymLex forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> N3Parser [Char]
commentText
assertEquiv :: N3Parser (SwishStateIO ())
assertEquiv :: N3Parser (SwishStateIO ())
assertEquiv = (ScopedName -> ScopedName -> [Char] -> SwishStateIO ())
-> [Char] -> N3Parser (SwishStateIO ())
assertArgs ScopedName -> ScopedName -> [Char] -> SwishStateIO ()
ssAssertEq [Char]
"asserteq"
assertMember :: N3Parser (SwishStateIO ())
assertMember :: N3Parser (SwishStateIO ())
assertMember = (ScopedName -> ScopedName -> [Char] -> SwishStateIO ())
-> [Char] -> N3Parser (SwishStateIO ())
assertArgs ScopedName -> ScopedName -> [Char] -> SwishStateIO ()
ssAssertIn [Char]
"assertin"
defineRule :: N3Parser (SwishStateIO ())
defineRule :: N3Parser (SwishStateIO ())
defineRule =
do { [Char] -> N3Parser ()
commandName [Char]
"@rule"
; ScopedName
rn <- N3Parser ScopedName
n3SymLex
; N3Parser ()
setTo
; [SwishStateIO (Either [Char] RDFGraph)]
ags <- Parser N3State [SwishStateIO (Either [Char] RDFGraph)]
graphOrList
; [Char] -> N3Parser ()
isymbol [Char]
"=>"
; SwishStateIO (Either [Char] RDFGraph)
cg <- N3Parser (SwishStateIO (Either [Char] RDFGraph))
graphExpr
; [(ScopedName, [RDFLabel])]
vms <- Parser N3State [(ScopedName, [RDFLabel])]
varModifiers forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure []
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ScopedName
-> [SwishStateIO (Either [Char] RDFGraph)]
-> SwishStateIO (Either [Char] RDFGraph)
-> [(ScopedName, [RDFLabel])]
-> SwishStateIO ()
ssDefineRule ScopedName
rn [SwishStateIO (Either [Char] RDFGraph)]
ags SwishStateIO (Either [Char] RDFGraph)
cg [(ScopedName, [RDFLabel])]
vms
}
defineRuleset :: N3Parser (SwishStateIO ())
defineRuleset :: N3Parser (SwishStateIO ())
defineRuleset =
[Char] -> N3Parser ()
commandName [Char]
"@ruleset" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
(ScopedName -> [ScopedName] -> [ScopedName] -> SwishStateIO ()
ssDefineRuleset forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser ScopedName
n3SymLex forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (N3Parser ()
setTo forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser N3State [ScopedName]
nameList) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (N3Parser ()
semicolon forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser N3State [ScopedName]
nameList))
defineConstraints :: N3Parser (SwishStateIO ())
defineConstraints :: N3Parser (SwishStateIO ())
defineConstraints =
[Char] -> N3Parser ()
commandName [Char]
"@constraints" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
(ScopedName
-> [SwishStateIO (Either [Char] RDFGraph)]
-> [ScopedName]
-> SwishStateIO ()
ssDefineConstraints forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser ScopedName
n3SymLex forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (N3Parser ()
setTo forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser N3State [SwishStateIO (Either [Char] RDFGraph)]
graphOrList) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall s. [Char] -> Parser s [Char]
symbol [Char]
"|" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser N3State [ScopedName]
nameOrList))
checkProofCmd :: N3Parser (SwishStateIO ())
checkProofCmd :: N3Parser (SwishStateIO ())
checkProofCmd =
do { [Char] -> N3Parser ()
commandName [Char]
"@proof"
; ScopedName
pn <- N3Parser ScopedName
n3SymLex
; [ScopedName]
sns <- Parser N3State [ScopedName]
nameList
; [Char] -> N3Parser ()
commandName [Char]
"@input"
; SwishStateIO (Either [Char] RDFFormula)
igf <- N3Parser (SwishStateIO (Either [Char] RDFFormula))
formulaExpr
; [Either [Char] [RDFRuleset]
-> SwishStateIO (Either [Char] RDFProofStep)]
sts <- forall (f :: * -> *) a. Alternative f => f a -> f [a]
many N3Parser
(Either [Char] [RDFRuleset]
-> SwishStateIO (Either [Char] RDFProofStep))
checkStep
; [Char] -> N3Parser ()
commandName [Char]
"@result"
; ScopedName
-> [ScopedName]
-> SwishStateIO (Either [Char] RDFFormula)
-> [Either [Char] [RDFRuleset]
-> SwishStateIO (Either [Char] RDFProofStep)]
-> SwishStateIO (Either [Char] RDFFormula)
-> SwishStateIO ()
ssCheckProof ScopedName
pn [ScopedName]
sns SwishStateIO (Either [Char] RDFFormula)
igf [Either [Char] [RDFRuleset]
-> SwishStateIO (Either [Char] RDFProofStep)]
sts forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser (SwishStateIO (Either [Char] RDFFormula))
formulaExpr
}
checkStep ::
N3Parser (Either String [RDFRuleset]
-> SwishStateIO (Either String RDFProofStep))
checkStep :: N3Parser
(Either [Char] [RDFRuleset]
-> SwishStateIO (Either [Char] RDFProofStep))
checkStep =
[Char] -> N3Parser ()
commandName [Char]
"@step" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
(ScopedName
-> [SwishStateIO (Either [Char] RDFFormula)]
-> SwishStateIO (Either [Char] RDFFormula)
-> Either [Char] [RDFRuleset]
-> SwishStateIO (Either [Char] RDFProofStep)
ssCheckStep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser ScopedName
n3SymLex forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> N3Parser [SwishStateIO (Either [Char] RDFFormula)]
formulaList forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall s. [Char] -> Parser s [Char]
symbol [Char]
"=>" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> N3Parser (SwishStateIO (Either [Char] RDFFormula))
formulaExpr))
fwdChain :: N3Parser (SwishStateIO ())
fwdChain :: N3Parser (SwishStateIO ())
fwdChain =
do { [Char] -> N3Parser ()
commandName [Char]
"@fwdchain"
; ScopedName
sn <- N3Parser ScopedName
n3SymLex
; ScopedName
rn <- N3Parser ScopedName
n3SymLex
; [SwishStateIO (Either [Char] RDFGraph)]
ags <- Parser N3State [SwishStateIO (Either [Char] RDFGraph)]
graphOrList
; [Char] -> N3Parser ()
isymbol [Char]
"=>"
; ScopedName
cn <- N3Parser ScopedName
n3SymLex
; N3State
s <- forall s. Parser s s
stGet
; let prefs :: NamespaceMap
prefs = N3State -> NamespaceMap
prefixUris N3State
s
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ScopedName
-> ScopedName
-> [SwishStateIO (Either [Char] RDFGraph)]
-> ScopedName
-> NamespaceMap
-> SwishStateIO ()
ssFwdChain ScopedName
sn ScopedName
rn [SwishStateIO (Either [Char] RDFGraph)]
ags ScopedName
cn NamespaceMap
prefs
}
bwdChain :: N3Parser (SwishStateIO ())
bwdChain :: N3Parser (SwishStateIO ())
bwdChain =
do { [Char] -> N3Parser ()
commandName [Char]
"@bwdchain"
; ScopedName
sn <- N3Parser ScopedName
n3SymLex
; ScopedName
rn <- N3Parser ScopedName
n3SymLex
; SwishStateIO (Either [Char] RDFGraph)
cg <- N3Parser (SwishStateIO (Either [Char] RDFGraph))
graphExpr
; [Char] -> N3Parser ()
isymbol [Char]
"<="
; ScopedName
an <- N3Parser ScopedName
n3SymLex
; N3State
s <- forall s. Parser s s
stGet
; let prefs :: NamespaceMap
prefs = N3State -> NamespaceMap
prefixUris N3State
s
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ScopedName
-> ScopedName
-> SwishStateIO (Either [Char] RDFGraph)
-> ScopedName
-> NamespaceMap
-> SwishStateIO ()
ssBwdChain ScopedName
sn ScopedName
rn SwishStateIO (Either [Char] RDFGraph)
cg ScopedName
an NamespaceMap
prefs
}
commandName :: String -> N3Parser ()
commandName :: [Char] -> N3Parser ()
commandName [Char]
cmd = forall s. [Char] -> Parser s [Char]
symbol [Char]
cmd forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> ()
restOfLine :: N3Parser String
restOfLine :: N3Parser [Char]
restOfLine = forall s a b. Parser s a -> Parser s b -> Parser s [a]
manyTill (forall s. (Char -> Bool) -> Parser s Char
satisfy (forall a b. a -> b -> a
const Bool
True)) forall s. Parser s ()
eoln forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall s. Parser s ()
whiteSpace
br :: N3Parser a -> N3Parser a
br :: forall a. N3Parser a -> N3Parser a
br = forall s lbr rbr a.
Parser s lbr -> Parser s rbr -> Parser s a -> Parser s a
between (forall s. [Char] -> Parser s [Char]
symbol [Char]
"(") (forall s. [Char] -> Parser s [Char]
symbol [Char]
")")
nameList :: N3Parser [ScopedName]
nameList :: Parser N3State [ScopedName]
nameList = forall a. N3Parser a -> N3Parser a
br forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Alternative f => f a -> f [a]
many N3Parser ScopedName
n3SymLex
toList :: a -> [a]
toList :: forall a. a -> [a]
toList = (forall a. a -> [a] -> [a]
:[])
nameOrList :: N3Parser [ScopedName]
nameOrList :: Parser N3State [ScopedName]
nameOrList =
(forall a. a -> [a]
toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser ScopedName
n3SymLex)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser N3State [ScopedName]
nameList
graphExpr :: N3Parser (SwishStateIO (Either String RDFGraph))
graphExpr :: N3Parser (SwishStateIO (Either [Char] RDFGraph))
graphExpr =
N3Parser (SwishStateIO (Either [Char] RDFGraph))
graphOnly
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall ex. Formula ex -> ex
formExpr) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser (SwishStateIO (Either [Char] RDFFormula))
formulaExpr
graphOnly :: N3Parser (SwishStateIO (Either String RDFGraph))
graphOnly :: N3Parser (SwishStateIO (Either [Char] RDFGraph))
graphOnly =
do { [Char] -> N3Parser ()
isymbol [Char]
"{"
; RDFLabel
b <- N3Parser RDFLabel
newBlankNode
; RDFGraph
g <- RDFLabel -> N3Parser RDFGraph
subgraph RDFLabel
b
; [Char] -> N3Parser ()
isymbol [Char]
"}"
; N3State
s <- forall s. Parser s s
stGet
; let gp :: RDFGraph
gp = forall lb. NamespaceMap -> NSGraph lb -> NSGraph lb
setNamespaces (N3State -> NamespaceMap
prefixUris N3State
s) RDFGraph
g
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right RDFGraph
gp)
}
graphList :: N3Parser [SwishStateIO (Either String RDFGraph)]
graphList :: Parser N3State [SwishStateIO (Either [Char] RDFGraph)]
graphList = forall a. N3Parser a -> N3Parser a
br (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many N3Parser (SwishStateIO (Either [Char] RDFGraph))
graphExpr)
graphOrList :: N3Parser [SwishStateIO (Either String RDFGraph)]
graphOrList :: Parser N3State [SwishStateIO (Either [Char] RDFGraph)]
graphOrList =
(forall a. a -> [a]
toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser (SwishStateIO (Either [Char] RDFGraph))
graphExpr)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser N3State [SwishStateIO (Either [Char] RDFGraph)]
graphList
formulaExpr :: N3Parser (SwishStateIO (Either String RDFFormula))
formulaExpr :: N3Parser (SwishStateIO (Either [Char] RDFFormula))
formulaExpr = N3Parser ScopedName
n3SymLex forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ScopedName -> N3Parser (SwishStateIO (Either [Char] RDFFormula))
namedGraph
namedGraph :: ScopedName -> N3Parser (SwishStateIO (Either String RDFFormula))
namedGraph :: ScopedName -> N3Parser (SwishStateIO (Either [Char] RDFFormula))
namedGraph ScopedName
n =
(ScopedName
-> SwishStateIO (Either [Char] RDFGraph)
-> SwishStateIO (Either [Char] RDFFormula)
ssAddReturnFormula ScopedName
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (N3Parser ()
setTo forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> N3Parser (SwishStateIO (Either [Char] RDFGraph))
graphOnly))
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (m :: * -> *) a. Monad m => a -> m a
return (ScopedName -> SwishStateIO (Either [Char] RDFFormula)
ssGetFormula ScopedName
n)
formulaList :: N3Parser [SwishStateIO (Either String RDFFormula)]
formulaList :: N3Parser [SwishStateIO (Either [Char] RDFFormula)]
formulaList = forall s lbr rbr a.
Parser s lbr -> Parser s rbr -> Parser s a -> Parser s a
between (forall s. [Char] -> Parser s [Char]
symbol [Char]
"(") (forall s. [Char] -> Parser s [Char]
symbol [Char]
")") (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many N3Parser (SwishStateIO (Either [Char] RDFFormula))
formulaExpr)
varModifiers :: N3Parser [(ScopedName,[RDFLabel])]
varModifiers :: Parser N3State [(ScopedName, [RDFLabel])]
varModifiers = forall s. [Char] -> Parser s [Char]
symbol [Char]
"|" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser N3State [(ScopedName, [RDFLabel])]
varModList
varModList :: N3Parser [(ScopedName,[RDFLabel])]
varModList :: Parser N3State [(ScopedName, [RDFLabel])]
varModList =
forall a. N3Parser a -> N3Parser a
br (forall (p :: * -> *) a sep. PolyParse p => p a -> p sep -> p [a]
sepBy N3Parser (ScopedName, [RDFLabel])
varMod N3Parser ()
comma)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall a. a -> [a]
toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s a. Parser s a -> Parser s a
lexeme N3Parser (ScopedName, [RDFLabel])
varMod
varMod :: N3Parser (ScopedName,[RDFLabel])
varMod :: N3Parser (ScopedName, [RDFLabel])
varMod = (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> N3Parser ScopedName
n3SymLex forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (forall s a. Parser s a -> Parser s a
lexeme N3Parser RDFLabel
quickVariable)
ssReport ::
String
-> SwishStateIO ()
ssReport :: [Char] -> SwishStateIO ()
ssReport [Char]
msg = forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ [Char] -> SwishState -> SwishState
setInfo forall a b. (a -> b) -> a -> b
$ [Char]
"# " forall a. [a] -> [a] -> [a]
++ [Char]
msg
ssReportLabel ::
String
-> String
-> SwishStateIO ()
ssReportLabel :: [Char] -> [Char] -> SwishStateIO ()
ssReportLabel [Char]
lbl [Char]
msg = [Char] -> SwishStateIO ()
ssReport forall a b. (a -> b) -> a -> b
$ [Char]
lbl forall a. [a] -> [a] -> [a]
++ [Char]
": " forall a. [a] -> [a] -> [a]
++ [Char]
msg
ssAddReturnFormula ::
ScopedName -> SwishStateIO (Either String RDFGraph)
-> SwishStateIO (Either String RDFFormula)
ssAddReturnFormula :: ScopedName
-> SwishStateIO (Either [Char] RDFGraph)
-> SwishStateIO (Either [Char] RDFFormula)
ssAddReturnFormula ScopedName
nam SwishStateIO (Either [Char] RDFGraph)
gf =
do { Either [Char] RDFGraph
egr <- SwishStateIO (Either [Char] RDFGraph)
gf
; ScopedName
-> [SwishStateIO (Either [Char] RDFGraph)] -> SwishStateIO ()
ssAddGraph ScopedName
nam [forall (m :: * -> *) a. Monad m => a -> m a
return Either [Char] RDFGraph
egr]
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall ex. ScopedName -> ex -> Formula ex
Formula ScopedName
nam) Either [Char] RDFGraph
egr
}
ssAddGraph ::
ScopedName -> [SwishStateIO (Either String RDFGraph)]
-> SwishStateIO ()
ssAddGraph :: ScopedName
-> [SwishStateIO (Either [Char] RDFGraph)] -> SwishStateIO ()
ssAddGraph ScopedName
nam [SwishStateIO (Either [Char] RDFGraph)]
gf =
let errmsg :: [Char]
errmsg = [Char]
"Graph/list not added: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
nam forall a. [a] -> [a] -> [a]
++ [Char]
"; "
in
do { [Either [Char] RDFGraph]
esg <- forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [SwishStateIO (Either [Char] RDFGraph)]
gf
; let egs :: Either [Char] [RDFGraph]
egs = forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Either [Char] RDFGraph]
esg
; let fgs :: SwishState -> SwishState
fgs = case Either [Char] [RDFGraph]
egs of
Left [Char]
er -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg forall a. [a] -> [a] -> [a]
++ [Char]
er)
Right [RDFGraph]
gs -> (NamedGraphMap -> NamedGraphMap) -> SwishState -> SwishState
modGraphs (forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ScopedName
nam [RDFGraph]
gs)
; forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify SwishState -> SwishState
fgs
}
ssGetGraph :: ScopedName -> SwishStateIO (Either String RDFGraph)
ssGetGraph :: ScopedName -> SwishStateIO (Either [Char] RDFGraph)
ssGetGraph ScopedName
nam = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. [a] -> a
head forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ScopedName -> SwishStateIO (Either [Char] [RDFGraph])
ssGetList ScopedName
nam
ssGetFormula :: ScopedName -> SwishStateIO (Either String RDFFormula)
ssGetFormula :: ScopedName -> SwishStateIO (Either [Char] RDFFormula)
ssGetFormula ScopedName
nam = forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets SwishState -> Either [Char] RDFFormula
find
where
find :: SwishState -> Either [Char] RDFFormula
find SwishState
st = case ScopedName -> SwishState -> Maybe RDFFormula
findFormula ScopedName
nam SwishState
st of
Maybe RDFFormula
Nothing -> forall a b. a -> Either a b
Left ([Char]
"Formula not present: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
nam)
Just RDFFormula
gr -> forall a b. b -> Either a b
Right RDFFormula
gr
ssGetList :: ScopedName -> SwishStateIO (Either String [RDFGraph])
ssGetList :: ScopedName -> SwishStateIO (Either [Char] [RDFGraph])
ssGetList ScopedName
nam = forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets SwishState -> Either [Char] [RDFGraph]
find
where
find :: SwishState -> Either [Char] [RDFGraph]
find SwishState
st = case ScopedName -> SwishState -> Maybe [RDFGraph]
findGraph ScopedName
nam SwishState
st of
Maybe [RDFGraph]
Nothing -> forall a b. a -> Either a b
Left ([Char]
"Graph or list not present: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
nam)
Just [RDFGraph]
grs -> forall a b. b -> Either a b
Right [RDFGraph]
grs
ssRead :: ScopedName -> Maybe URI -> SwishStateIO ()
ssRead :: ScopedName -> Maybe URI -> SwishStateIO ()
ssRead ScopedName
nam Maybe URI
muri = ScopedName
-> [SwishStateIO (Either [Char] RDFGraph)] -> SwishStateIO ()
ssAddGraph ScopedName
nam [Maybe URI -> SwishStateIO (Either [Char] RDFGraph)
ssReadGraph Maybe URI
muri]
ssReadGraph :: Maybe URI -> SwishStateIO (Either String RDFGraph)
ssReadGraph :: Maybe URI -> SwishStateIO (Either [Char] RDFGraph)
ssReadGraph Maybe URI
muri =
let gf :: Either [Char] Text -> Either [Char] RDFGraph
gf Either [Char] Text
inp = case Either [Char] Text
inp of
Left [Char]
es -> forall a b. a -> Either a b
Left [Char]
es
Right Text
is -> Text -> Maybe QName -> Either [Char] RDFGraph
parseN3 Text
is (Maybe URI
muri forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= URI -> Maybe QName
qnameFromURI)
in Either [Char] Text -> Either [Char] RDFGraph
gf forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Maybe URI -> SwishStateIO (Either [Char] Text)
getResourceData Maybe URI
muri
ssWriteList ::
Maybe URI -> SwishStateIO (Either String [RDFGraph]) -> String
-> SwishStateIO ()
ssWriteList :: Maybe URI
-> SwishStateIO (Either [Char] [RDFGraph])
-> [Char]
-> SwishStateIO ()
ssWriteList Maybe URI
muri SwishStateIO (Either [Char] [RDFGraph])
gf [Char]
comment = do
Either [Char] [RDFGraph]
esgs <- SwishStateIO (Either [Char] [RDFGraph])
gf
case Either [Char] [RDFGraph]
esgs of
Left [Char]
er -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ [Char] -> SwishState -> SwishState
setError ([Char]
"Cannot write list: " forall a. [a] -> [a] -> [a]
++ [Char]
er)
Right [] -> Maybe URI -> Builder -> SwishStateIO ()
putResourceData forall a. Maybe a
Nothing (Text -> Builder
B.fromLazyText ([Text] -> Text
L.concat [Text
"# ", [Char] -> Text
L.pack [Char]
comment, Text
"\n+ Swish: Writing empty list"]))
Right [RDFGraph
gr] -> Maybe URI -> RDFGraph -> [Char] -> SwishStateIO ()
ssWriteGraph Maybe URI
muri RDFGraph
gr [Char]
comment
Right [RDFGraph]
grs -> forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ forall {a}. Show a => (a, RDFGraph) -> SwishStateIO ()
writegr (forall a b. [a] -> [b] -> [(a, b)]
zip [(Int
0::Int)..] [RDFGraph]
grs)
where
writegr :: (a, RDFGraph) -> SwishStateIO ()
writegr (a
n,RDFGraph
gr) = Maybe URI -> RDFGraph -> [Char] -> SwishStateIO ()
ssWriteGraph (forall {p}. Show p => Maybe URI -> p -> Maybe URI
murin Maybe URI
muri a
n) RDFGraph
gr
([Char]
"[" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show a
n forall a. [a] -> [a] -> [a]
++ [Char]
"] " forall a. [a] -> [a] -> [a]
++ [Char]
comment)
murin :: Maybe URI -> p -> Maybe URI
murin Maybe URI
Nothing p
_ = forall a. Maybe a
Nothing
murin (Just URI
uri) p
n =
let rp :: [Char]
rp = forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ URI -> [Char]
uriPath URI
uri
([Char]
rLastSet, [Char]
rRest) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
== Char
'/') [Char]
rp
([Char]
before, [Char]
after) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
== Char
'.') forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse [Char]
rLastSet
newPath :: [Char]
newPath = forall a. [a] -> [a]
reverse [Char]
rRest forall a. [a] -> [a] -> [a]
++ [Char]
"/" forall a. [a] -> [a] -> [a]
++ [Char]
before forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show p
n forall a. [a] -> [a] -> [a]
++ [Char]
after
in case [Char]
rLastSet of
[Char]
"" -> forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Invalid URI (path ends in /): " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show URI
uri
[Char]
_ -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ URI
uri { uriPath :: [Char]
uriPath = [Char]
newPath }
ssWriteGraph :: Maybe URI -> RDFGraph -> String -> SwishStateIO ()
ssWriteGraph :: Maybe URI -> RDFGraph -> [Char] -> SwishStateIO ()
ssWriteGraph Maybe URI
muri RDFGraph
gr [Char]
comment =
Maybe URI -> Builder -> SwishStateIO ()
putResourceData Maybe URI
muri (Builder
c forall a. Monoid a => a -> a -> a
`mappend` RDFGraph -> Builder
formatGraphAsBuilder RDFGraph
gr)
where
c :: Builder
c = Text -> Builder
B.fromLazyText forall a b. (a -> b) -> a -> b
$ [Text] -> Text
L.concat [Text
"# ", [Char] -> Text
L.pack [Char]
comment, Text
"\n"]
ssMerge ::
ScopedName -> [SwishStateIO (Either String RDFGraph)]
-> SwishStateIO ()
ssMerge :: ScopedName
-> [SwishStateIO (Either [Char] RDFGraph)] -> SwishStateIO ()
ssMerge ScopedName
nam [SwishStateIO (Either [Char] RDFGraph)]
gfs =
let errmsg :: [Char]
errmsg = [Char]
"Graph merge not defined: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
nam forall a. [a] -> [a] -> [a]
++ [Char]
"; "
in
do { [Char] -> [Char] -> SwishStateIO ()
ssReportLabel [Char]
"Merge" (forall a. Show a => a -> [Char]
show ScopedName
nam)
; [Either [Char] RDFGraph]
esg <- forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [SwishStateIO (Either [Char] RDFGraph)]
gfs
; let egs :: Either [Char] [RDFGraph]
egs = forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Either [Char] RDFGraph]
esg
; let fgs :: SwishState -> SwishState
fgs = case Either [Char] [RDFGraph]
egs of
Left [Char]
er -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg forall a. [a] -> [a] -> [a]
++ [Char]
er)
Right [] -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg forall a. [a] -> [a] -> [a]
++ [Char]
"No graphs to merge")
Right [RDFGraph]
gs -> (NamedGraphMap -> NamedGraphMap) -> SwishState -> SwishState
modGraphs (forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ScopedName
nam [RDFGraph
g])
where g :: RDFGraph
g = forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 forall lb. Label lb => NSGraph lb -> NSGraph lb -> NSGraph lb
merge [RDFGraph]
gs
; forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify SwishState -> SwishState
fgs
}
ssCompare :: ScopedName -> ScopedName -> SwishStateIO ()
ssCompare :: ScopedName -> ScopedName -> SwishStateIO ()
ssCompare ScopedName
n1 ScopedName
n2 =
do { [Char] -> [Char] -> SwishStateIO ()
ssReportLabel [Char]
"Compare" (forall a. Show a => a -> [Char]
show ScopedName
n1 forall a. [a] -> [a] -> [a]
++ [Char]
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
n2)
; Either [Char] RDFGraph
g1 <- ScopedName -> SwishStateIO (Either [Char] RDFGraph)
ssGetGraph ScopedName
n1
; Either [Char] RDFGraph
g2 <- ScopedName -> SwishStateIO (Either [Char] RDFGraph)
ssGetGraph ScopedName
n2
; forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Either [Char] RDFGraph
g1 forall a. Eq a => a -> a -> Bool
/= Either [Char] RDFGraph
g2) (forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ SwishStatus -> SwishState -> SwishState
setStatus SwishStatus
SwishGraphCompareError)
}
ssAssertEq :: ScopedName -> ScopedName -> String -> SwishStateIO ()
ssAssertEq :: ScopedName -> ScopedName -> [Char] -> SwishStateIO ()
ssAssertEq ScopedName
n1 ScopedName
n2 [Char]
comment =
let er1 :: [Char]
er1 = [Char]
":\n Graph or list compare not performed: invalid graph/list."
in
do { [Char] -> [Char] -> SwishStateIO ()
ssReportLabel [Char]
"AssertEq" [Char]
comment
; Either [Char] [RDFGraph]
g1 <- ScopedName -> SwishStateIO (Either [Char] [RDFGraph])
ssGetList ScopedName
n1
; Either [Char] [RDFGraph]
g2 <- ScopedName -> SwishStateIO (Either [Char] [RDFGraph])
ssGetList ScopedName
n2
; case (Either [Char] [RDFGraph]
g1,Either [Char] [RDFGraph]
g2) of
(Left [Char]
er,Either [Char] [RDFGraph]
_) -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ [Char] -> SwishState -> SwishState
setError ([Char]
comment forall a. [a] -> [a] -> [a]
++ [Char]
er1 forall a. [a] -> [a] -> [a]
++ [Char]
"\n " forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Either [Char] [RDFGraph]
_,Left [Char]
er) -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ [Char] -> SwishState -> SwishState
setError ([Char]
comment forall a. [a] -> [a] -> [a]
++ [Char]
er1 forall a. [a] -> [a] -> [a]
++ [Char]
"\n " forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Right [RDFGraph]
gr1,Right [RDFGraph]
gr2) ->
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall a. Ord a => [a] -> Set a
S.fromList [RDFGraph]
gr1 forall a. Eq a => a -> a -> Bool
/= forall a. Ord a => [a] -> Set a
S.fromList [RDFGraph]
gr2) forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$
[Char] -> SwishState -> SwishState
setError ([Char]
comment forall a. [a] -> [a] -> [a]
++ [Char]
":\n Graph " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
n1
forall a. [a] -> [a] -> [a]
++ [Char]
" differs from " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
n2 forall a. [a] -> [a] -> [a]
++ [Char]
".")
}
ssAssertIn :: ScopedName -> ScopedName -> String -> SwishStateIO ()
ssAssertIn :: ScopedName -> ScopedName -> [Char] -> SwishStateIO ()
ssAssertIn ScopedName
n1 ScopedName
n2 [Char]
comment =
let er1 :: [Char]
er1 = [Char]
":\n Membership test not performed: invalid graph."
er2 :: [Char]
er2 = [Char]
":\n Membership test not performed: invalid list."
in
do { [Char] -> [Char] -> SwishStateIO ()
ssReportLabel [Char]
"AssertIn" [Char]
comment
; Either [Char] RDFGraph
g1 <- ScopedName -> SwishStateIO (Either [Char] RDFGraph)
ssGetGraph ScopedName
n1
; Either [Char] [RDFGraph]
g2 <- ScopedName -> SwishStateIO (Either [Char] [RDFGraph])
ssGetList ScopedName
n2
; case (Either [Char] RDFGraph
g1,Either [Char] [RDFGraph]
g2) of
(Left [Char]
er,Either [Char] [RDFGraph]
_) -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ [Char] -> SwishState -> SwishState
setError ([Char]
comment forall a. [a] -> [a] -> [a]
++ [Char]
er1 forall a. [a] -> [a] -> [a]
++ [Char]
"\n " forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Either [Char] RDFGraph
_,Left [Char]
er) -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ [Char] -> SwishState -> SwishState
setError ([Char]
comment forall a. [a] -> [a] -> [a]
++ [Char]
er2 forall a. [a] -> [a] -> [a]
++ [Char]
"\n " forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Right RDFGraph
gr,Right [RDFGraph]
gs) ->
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (RDFGraph
gr forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [RDFGraph]
gs) forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$
[Char] -> SwishState -> SwishState
setError ([Char]
comment forall a. [a] -> [a] -> [a]
++ [Char]
":\n Graph " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
n1
forall a. [a] -> [a] -> [a]
++ [Char]
" not a member of " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
n2)
}
ssDefineRule ::
ScopedName
-> [SwishStateIO (Either String RDFGraph)]
-> SwishStateIO (Either String RDFGraph)
-> [(ScopedName,[RDFLabel])]
-> SwishStateIO ()
ssDefineRule :: ScopedName
-> [SwishStateIO (Either [Char] RDFGraph)]
-> SwishStateIO (Either [Char] RDFGraph)
-> [(ScopedName, [RDFLabel])]
-> SwishStateIO ()
ssDefineRule ScopedName
rn [SwishStateIO (Either [Char] RDFGraph)]
agfs SwishStateIO (Either [Char] RDFGraph)
cgf [(ScopedName, [RDFLabel])]
vmds =
let errmsg1 :: [Char]
errmsg1 = [Char]
"Rule definition error in antecedent graph(s): "
errmsg2 :: [Char]
errmsg2 = [Char]
"Rule definition error in consequent graph: "
errmsg3 :: [Char]
errmsg3 = [Char]
"Rule definition error in variable modifier(s): "
errmsg4 :: [Char]
errmsg4 = [Char]
"Incompatible variable binding modifier sequence"
in
do { [Either [Char] RDFGraph]
aesg <- forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [SwishStateIO (Either [Char] RDFGraph)]
agfs
; let ags :: Either [Char] [RDFGraph]
ags = forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Either [Char] RDFGraph]
aesg :: Either String [RDFGraph]
; Either [Char] RDFGraph
cg <- SwishStateIO (Either [Char] RDFGraph)
cgf
; let vmfs :: [SwishStateIO (Either [Char] RDFVarBindingModify)]
vmfs = forall a b. (a -> b) -> [a] -> [b]
map (ScopedName, [RDFLabel])
-> SwishStateIO (Either [Char] RDFVarBindingModify)
ssFindVarModify [(ScopedName, [RDFLabel])]
vmds
; [Either [Char] RDFVarBindingModify]
evms <- forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [SwishStateIO (Either [Char] RDFVarBindingModify)]
vmfs
; let vms :: Either [Char] [RDFVarBindingModify]
vms = forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Either [Char] RDFVarBindingModify]
evms :: Either String [RDFVarBindingModify]
; let frl :: SwishState -> SwishState
frl = case (Either [Char] [RDFGraph]
ags,Either [Char] RDFGraph
cg,Either [Char] [RDFVarBindingModify]
vms) of
(Left [Char]
er,Either [Char] RDFGraph
_,Either [Char] [RDFVarBindingModify]
_) -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg1 forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Either [Char] [RDFGraph]
_,Left [Char]
er,Either [Char] [RDFVarBindingModify]
_) -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg2 forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Either [Char] [RDFGraph]
_,Either [Char] RDFGraph
_,Left [Char]
er) -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg3 forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Right [RDFGraph]
agrs,Right RDFGraph
cgr,Right [RDFVarBindingModify]
vbms) ->
let
newRule :: RDFVarBindingModify -> RDFRule
newRule = ScopedName
-> [RDFGraph] -> RDFGraph -> RDFVarBindingModify -> RDFRule
makeRDFClosureRule ScopedName
rn [RDFGraph]
agrs RDFGraph
cgr
in
case forall a b.
Eq a =>
[VarBindingModify a b] -> Maybe (VarBindingModify a b)
composeSequence [RDFVarBindingModify]
vbms of
Just RDFVarBindingModify
vm -> let nr :: RDFRule
nr = RDFVarBindingModify -> RDFRule
newRule RDFVarBindingModify
vm in (RDFRuleMap -> RDFRuleMap) -> SwishState -> SwishState
modRules (forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (forall ex. Rule ex -> ScopedName
ruleName RDFRule
nr) RDFRule
nr)
Maybe RDFVarBindingModify
Nothing -> [Char] -> SwishState -> SwishState
setError [Char]
errmsg4
; forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify SwishState -> SwishState
frl
}
ssFindVarModify ::
(ScopedName,[RDFLabel]) -> SwishStateIO (Either String RDFVarBindingModify)
ssFindVarModify :: (ScopedName, [RDFLabel])
-> SwishStateIO (Either [Char] RDFVarBindingModify)
ssFindVarModify (ScopedName
nam,[RDFLabel]
lbs) = forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets forall a b. (a -> b) -> a -> b
$ \SwishState
st ->
case ScopedName -> SwishState -> Maybe RDFOpenVarBindingModify
findOpenVarModify ScopedName
nam SwishState
st of
Just RDFOpenVarBindingModify
ovbm -> forall a b. b -> Either a b
Right (RDFOpenVarBindingModify
ovbm [RDFLabel]
lbs)
Maybe RDFOpenVarBindingModify
Nothing -> forall a b. a -> Either a b
Left ([Char]
"Undefined modifier: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
nam)
ssDefineRuleset ::
ScopedName
-> [ScopedName]
-> [ScopedName]
-> SwishStateIO ()
ssDefineRuleset :: ScopedName -> [ScopedName] -> [ScopedName] -> SwishStateIO ()
ssDefineRuleset ScopedName
sn [ScopedName]
ans [ScopedName]
rns =
let errmsg1 :: [Char]
errmsg1 = [Char]
"Error in ruleset axiom(s): "
errmsg2 :: [Char]
errmsg2 = [Char]
"Error in ruleset rule(s): "
in
do { let agfs :: SwishStateIO [Either [Char] RDFFormula]
agfs = forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ScopedName -> SwishStateIO (Either [Char] RDFFormula)
ssGetFormula [ScopedName]
ans
:: SwishStateIO [Either String RDFFormula]
; [Either [Char] RDFFormula]
aesg <- SwishStateIO [Either [Char] RDFFormula]
agfs
; let eags :: Either [Char] [RDFFormula]
eags = forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Either [Char] RDFFormula]
aesg :: Either String [RDFFormula]
; let erlf :: SwishStateIO [Either [Char] RDFRule]
erlf = forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ScopedName -> SwishStateIO (Either [Char] RDFRule)
ssFindRule [ScopedName]
rns
:: SwishStateIO [Either String RDFRule]
; [Either [Char] RDFRule]
rles <- SwishStateIO [Either [Char] RDFRule]
erlf
; let erls :: Either [Char] [RDFRule]
erls = forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Either [Char] RDFRule]
rles :: Either String [RDFRule]
; let frs :: SwishState -> SwishState
frs = case (Either [Char] [RDFFormula]
eags,Either [Char] [RDFRule]
erls) of
(Left [Char]
er,Either [Char] [RDFRule]
_) -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg1 forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Either [Char] [RDFFormula]
_,Left [Char]
er) -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg2 forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Right [RDFFormula]
ags,Right [RDFRule]
rls) ->
(RDFRulesetMap -> RDFRulesetMap) -> SwishState -> SwishState
modRulesets (forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (forall ex. Ruleset ex -> Namespace
getRulesetNamespace RDFRuleset
rs) RDFRuleset
rs)
where
rs :: RDFRuleset
rs = forall ex. Namespace -> [Formula ex] -> [Rule ex] -> Ruleset ex
makeRuleset (ScopedName -> Namespace
getScopeNamespace ScopedName
sn) [RDFFormula]
ags [RDFRule]
rls
; forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify SwishState -> SwishState
frs
}
ssFindRule :: ScopedName -> SwishStateIO (Either String RDFRule)
ssFindRule :: ScopedName -> SwishStateIO (Either [Char] RDFRule)
ssFindRule ScopedName
nam = forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets SwishState -> Either [Char] RDFRule
find
where
find :: SwishState -> Either [Char] RDFRule
find SwishState
st = case ScopedName -> SwishState -> Maybe RDFRule
findRule ScopedName
nam SwishState
st of
Maybe RDFRule
Nothing -> forall a b. a -> Either a b
Left ([Char]
"Rule not found: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
nam)
Just RDFRule
rl -> forall a b. b -> Either a b
Right RDFRule
rl
ssDefineConstraints ::
ScopedName
-> [SwishStateIO (Either String RDFGraph)]
-> [ScopedName]
-> SwishStateIO ()
ssDefineConstraints :: ScopedName
-> [SwishStateIO (Either [Char] RDFGraph)]
-> [ScopedName]
-> SwishStateIO ()
ssDefineConstraints ScopedName
sn [SwishStateIO (Either [Char] RDFGraph)]
cgfs [ScopedName]
dtns =
let errmsg1 :: [Char]
errmsg1 = [Char]
"Error in constraint graph(s): "
errmsg2 :: [Char]
errmsg2 = [Char]
"Error in datatype(s): "
in
do { [Either [Char] RDFGraph]
cges <- forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [SwishStateIO (Either [Char] RDFGraph)]
cgfs
; let ecgs :: Either [Char] [RDFGraph]
ecgs = forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Either [Char] RDFGraph]
cges :: Either String [RDFGraph]
; let ecgr :: Either [Char] RDFGraph
ecgr = case Either [Char] [RDFGraph]
ecgs of
Left [Char]
er -> forall a b. a -> Either a b
Left [Char]
er
Right [] -> forall a b. b -> Either a b
Right forall a. Monoid a => a
mempty
Right [RDFGraph]
grs -> forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 forall lb. Label lb => NSGraph lb -> NSGraph lb -> NSGraph lb
merge [RDFGraph]
grs
; [Either [Char] RDFDatatype]
edtf <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ScopedName -> SwishStateIO (Either [Char] RDFDatatype)
ssFindDatatype [ScopedName]
dtns
; let edts :: Either [Char] [RDFDatatype]
edts = forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Either [Char] RDFDatatype]
edtf :: Either String [RDFDatatype]
; let frs :: SwishState -> SwishState
frs = case (Either [Char] RDFGraph
ecgr,Either [Char] [RDFDatatype]
edts) of
(Left [Char]
er,Either [Char] [RDFDatatype]
_) -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg1 forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Either [Char] RDFGraph
_,Left [Char]
er) -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg2 forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Right RDFGraph
cgr,Right [RDFDatatype]
dts) ->
(RDFRulesetMap -> RDFRulesetMap) -> SwishState -> SwishState
modRulesets (forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (forall ex. Ruleset ex -> Namespace
getRulesetNamespace RDFRuleset
rs) RDFRuleset
rs)
where
rs :: RDFRuleset
rs = forall ex. Namespace -> [Formula ex] -> [Rule ex] -> Ruleset ex
makeRuleset (ScopedName -> Namespace
getScopeNamespace ScopedName
sn) [] [RDFRule]
rls
rls :: [RDFRule]
rls = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (forall ex lb vn. Datatype ex lb vn -> ex -> [Rule ex]
`typeMkRules` RDFGraph
cgr) [RDFDatatype]
dts
; forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify SwishState -> SwishState
frs
}
ssFindDatatype :: ScopedName -> SwishStateIO (Either String RDFDatatype)
ssFindDatatype :: ScopedName -> SwishStateIO (Either [Char] RDFDatatype)
ssFindDatatype ScopedName
nam = forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets SwishState -> Either [Char] RDFDatatype
find
where
find :: SwishState -> Either [Char] RDFDatatype
find SwishState
st = case ScopedName -> SwishState -> Maybe RDFDatatype
findDatatype ScopedName
nam SwishState
st of
Maybe RDFDatatype
Nothing -> forall a b. a -> Either a b
Left ([Char]
"Datatype not found: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
nam)
Just RDFDatatype
dt -> forall a b. b -> Either a b
Right RDFDatatype
dt
ssCheckProof ::
ScopedName
-> [ScopedName]
-> SwishStateIO (Either String RDFFormula)
-> [Either String [RDFRuleset]
-> SwishStateIO (Either String RDFProofStep)]
-> SwishStateIO (Either String RDFFormula)
-> SwishStateIO ()
ssCheckProof :: ScopedName
-> [ScopedName]
-> SwishStateIO (Either [Char] RDFFormula)
-> [Either [Char] [RDFRuleset]
-> SwishStateIO (Either [Char] RDFProofStep)]
-> SwishStateIO (Either [Char] RDFFormula)
-> SwishStateIO ()
ssCheckProof ScopedName
pn [ScopedName]
sns SwishStateIO (Either [Char] RDFFormula)
igf [Either [Char] [RDFRuleset]
-> SwishStateIO (Either [Char] RDFProofStep)]
stfs SwishStateIO (Either [Char] RDFFormula)
rgf =
let
infmsg1 :: [Char]
infmsg1 = [Char]
"Proof satisfied: "
errmsg1 :: [Char]
errmsg1 = [Char]
"Error in proof ruleset(s): "
errmsg2 :: [Char]
errmsg2 = [Char]
"Error in proof input: "
errmsg3 :: [Char]
errmsg3 = [Char]
"Error in proof step(s): "
errmsg4 :: [Char]
errmsg4 = [Char]
"Error in proof goal: "
errmsg5 :: [Char]
errmsg5 = [Char]
"Proof not satisfied: "
proofname :: [Char]
proofname = [Char]
" (Proof " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
pn forall a. [a] -> [a] -> [a]
++ [Char]
")"
in
do { let rs1 :: [SwishStateIO (Either [Char] RDFRuleset)]
rs1 = forall a b. (a -> b) -> [a] -> [b]
map ScopedName -> SwishStateIO (Either [Char] RDFRuleset)
ssFindRuleset [ScopedName]
sns :: [SwishStateIO (Either String RDFRuleset)]
; [Either [Char] RDFRuleset]
rs2 <- forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [SwishStateIO (Either [Char] RDFRuleset)]
rs1
; let erss :: Either [Char] [RDFRuleset]
erss = forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Either [Char] RDFRuleset]
rs2 :: Either String [RDFRuleset]
; Either [Char] RDFFormula
eig <- SwishStateIO (Either [Char] RDFFormula)
igf
; let st1 :: SwishStateIO [Either [Char] RDFProofStep]
st1 = forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence forall a b. (a -> b) -> a -> b
$ forall a b. [a -> b] -> a -> [b]
flist [Either [Char] [RDFRuleset]
-> SwishStateIO (Either [Char] RDFProofStep)]
stfs Either [Char] [RDFRuleset]
erss :: SwishStateIO [Either String RDFProofStep]
; [Either [Char] RDFProofStep]
st2 <- SwishStateIO [Either [Char] RDFProofStep]
st1
; let ests :: Either [Char] [RDFProofStep]
ests = forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Either [Char] RDFProofStep]
st2 :: Either String [RDFProofStep]
; Either [Char] RDFFormula
erg <- SwishStateIO (Either [Char] RDFFormula)
rgf
; let proof :: Either [Char] RDFProof
proof = case (Either [Char] [RDFRuleset]
erss,Either [Char] RDFFormula
eig,Either [Char] [RDFProofStep]
ests,Either [Char] RDFFormula
erg) of
(Left [Char]
er,Either [Char] RDFFormula
_,Either [Char] [RDFProofStep]
_,Either [Char] RDFFormula
_) -> forall a b. a -> Either a b
Left ([Char]
errmsg1 forall a. [a] -> [a] -> [a]
++ [Char]
er forall a. [a] -> [a] -> [a]
++ [Char]
proofname)
(Either [Char] [RDFRuleset]
_,Left [Char]
er,Either [Char] [RDFProofStep]
_,Either [Char] RDFFormula
_) -> forall a b. a -> Either a b
Left ([Char]
errmsg2 forall a. [a] -> [a] -> [a]
++ [Char]
er forall a. [a] -> [a] -> [a]
++ [Char]
proofname)
(Either [Char] [RDFRuleset]
_,Either [Char] RDFFormula
_,Left [Char]
er,Either [Char] RDFFormula
_) -> forall a b. a -> Either a b
Left ([Char]
errmsg3 forall a. [a] -> [a] -> [a]
++ [Char]
er forall a. [a] -> [a] -> [a]
++ [Char]
proofname)
(Either [Char] [RDFRuleset]
_,Either [Char] RDFFormula
_,Either [Char] [RDFProofStep]
_,Left [Char]
er) -> forall a b. a -> Either a b
Left ([Char]
errmsg4 forall a. [a] -> [a] -> [a]
++ [Char]
er forall a. [a] -> [a] -> [a]
++ [Char]
proofname)
(Right [RDFRuleset]
rss, Right RDFFormula
ig, Right [RDFProofStep]
sts, Right RDFFormula
rg) ->
forall a b. b -> Either a b
Right ([RDFRuleset]
-> RDFFormula -> RDFFormula -> [RDFProofStep] -> RDFProof
makeRDFProof [RDFRuleset]
rss RDFFormula
ig RDFFormula
rg [RDFProofStep]
sts)
; forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
False forall a b. (a -> b) -> a -> b
$ case Either [Char] RDFProof
proof of
(Left [Char]
_) -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
(Right RDFProof
pr) -> Maybe URI -> Builder -> SwishStateIO ()
putResourceData forall a. Maybe a
Nothing forall a b. (a -> b) -> a -> b
$
Text -> Builder
B.fromLazyText ([Text] -> Text
L.concat [Text
"Proof ", [Char] -> Text
L.pack (forall a. Show a => a -> [Char]
show ScopedName
pn), Text
"\n"])
forall a. Monoid a => a -> a -> a
`mappend`
[Char] -> Builder
B.fromString (forall ex. ShowLines ex => [Char] -> Proof ex -> ShowS
showsProof [Char]
"\n" RDFProof
pr [Char]
"\n")
; let checkproof :: SwishState -> SwishState
checkproof = case Either [Char] RDFProof
proof of
(Left [Char]
er) -> [Char] -> SwishState -> SwishState
setError [Char]
er
(Right RDFProof
pr) ->
case forall ex. (Expression ex, Ord ex) => Proof ex -> Maybe [Char]
explainProof RDFProof
pr of
Maybe [Char]
Nothing -> [Char] -> SwishState -> SwishState
setInfo ([Char]
infmsg1 forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
pn)
Just [Char]
ex -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg5 forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
pn forall a. [a] -> [a] -> [a]
++ [Char]
", " forall a. [a] -> [a] -> [a]
++ [Char]
ex)
; forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify SwishState -> SwishState
checkproof
}
ssCheckStep ::
ScopedName
-> [SwishStateIO (Either String RDFFormula)]
-> SwishStateIO (Either String RDFFormula)
-> Either String [RDFRuleset]
-> SwishStateIO (Either String RDFProofStep)
ssCheckStep :: ScopedName
-> [SwishStateIO (Either [Char] RDFFormula)]
-> SwishStateIO (Either [Char] RDFFormula)
-> Either [Char] [RDFRuleset]
-> SwishStateIO (Either [Char] RDFProofStep)
ssCheckStep ScopedName
_ [SwishStateIO (Either [Char] RDFFormula)]
_ SwishStateIO (Either [Char] RDFFormula)
_ (Left [Char]
er) = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left [Char]
er
ssCheckStep ScopedName
rn [SwishStateIO (Either [Char] RDFFormula)]
eagf SwishStateIO (Either [Char] RDFFormula)
ecgf (Right [RDFRuleset]
rss) =
let
errmsg1 :: [Char]
errmsg1 = [Char]
"Rule not in proof step ruleset(s): "
errmsg2 :: [Char]
errmsg2 = [Char]
"Error in proof step antecedent graph(s): "
errmsg3 :: [Char]
errmsg3 = [Char]
"Error in proof step consequent graph: "
in
do { let mrul :: Maybe RDFRule
mrul = forall ex. ScopedName -> [Ruleset ex] -> Maybe (Rule ex)
getMaybeContextRule ScopedName
rn [RDFRuleset]
rss :: Maybe RDFRule
; [Either [Char] RDFFormula]
esag <- forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [SwishStateIO (Either [Char] RDFFormula)]
eagf
; let eags :: Either [Char] [RDFFormula]
eags = forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Either [Char] RDFFormula]
esag :: Either String [RDFFormula]
; Either [Char] RDFFormula
ecg <- SwishStateIO (Either [Char] RDFFormula)
ecgf
; let est :: Either [Char] RDFProofStep
est = case (Maybe RDFRule
mrul,Either [Char] [RDFFormula]
eags,Either [Char] RDFFormula
ecg) of
(Maybe RDFRule
Nothing,Either [Char] [RDFFormula]
_,Either [Char] RDFFormula
_) -> forall a b. a -> Either a b
Left ([Char]
errmsg1 forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
rn)
(Maybe RDFRule
_,Left [Char]
er,Either [Char] RDFFormula
_) -> forall a b. a -> Either a b
Left ([Char]
errmsg2 forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Maybe RDFRule
_,Either [Char] [RDFFormula]
_,Left [Char]
er) -> forall a b. a -> Either a b
Left ([Char]
errmsg3 forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Just RDFRule
rul,Right [RDFFormula]
ags,Right RDFFormula
cg) ->
forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ RDFRule -> [RDFFormula] -> RDFFormula -> RDFProofStep
makeRDFProofStep RDFRule
rul [RDFFormula]
ags RDFFormula
cg
; forall (m :: * -> *) a. Monad m => a -> m a
return Either [Char] RDFProofStep
est
}
ssFwdChain ::
ScopedName
-> ScopedName
-> [SwishStateIO (Either String RDFGraph)]
-> ScopedName
-> NamespaceMap
-> SwishStateIO ()
ssFwdChain :: ScopedName
-> ScopedName
-> [SwishStateIO (Either [Char] RDFGraph)]
-> ScopedName
-> NamespaceMap
-> SwishStateIO ()
ssFwdChain ScopedName
sn ScopedName
rn [SwishStateIO (Either [Char] RDFGraph)]
agfs ScopedName
cn NamespaceMap
prefs =
let
errmsg1 :: [Char]
errmsg1 = [Char]
"FwdChain rule error: "
errmsg2 :: [Char]
errmsg2 = [Char]
"FwdChain antecedent error: "
in
do { Either [Char] RDFRule
erl <- ScopedName -> ScopedName -> SwishStateIO (Either [Char] RDFRule)
ssFindRulesetRule ScopedName
sn ScopedName
rn
; [Either [Char] RDFGraph]
aesg <- forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [SwishStateIO (Either [Char] RDFGraph)]
agfs
; let eags :: Either [Char] [RDFGraph]
eags = forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Either [Char] RDFGraph]
aesg :: Either String [RDFGraph]
; let fcr :: SwishState -> SwishState
fcr = case (Either [Char] RDFRule
erl,Either [Char] [RDFGraph]
eags) of
(Left [Char]
er,Either [Char] [RDFGraph]
_) -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg1 forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Either [Char] RDFRule
_,Left [Char]
er) -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg2 forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Right RDFRule
rl,Right [RDFGraph]
ags) ->
(NamedGraphMap -> NamedGraphMap) -> SwishState -> SwishState
modGraphs (forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ScopedName
cn [RDFGraph
cg])
where
cg :: RDFGraph
cg = case forall ex. Rule ex -> [ex] -> [ex]
fwdApply RDFRule
rl [RDFGraph]
ags of
[] -> forall a. Monoid a => a
mempty
[RDFGraph]
grs -> forall lb. NamespaceMap -> NSGraph lb -> NSGraph lb
setNamespaces NamespaceMap
prefs forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 forall (lg :: * -> *) lb.
(LDGraph lg lb, Ord lb) =>
lg lb -> lg lb -> lg lb
addGraphs [RDFGraph]
grs
; forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify SwishState -> SwishState
fcr
}
ssFindRulesetRule ::
ScopedName -> ScopedName -> SwishStateIO (Either String RDFRule)
ssFindRulesetRule :: ScopedName -> ScopedName -> SwishStateIO (Either [Char] RDFRule)
ssFindRulesetRule ScopedName
sn ScopedName
rn = forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets SwishState -> Either [Char] RDFRule
find
where
find :: SwishState -> Either [Char] RDFRule
find SwishState
st = case ScopedName -> SwishState -> Maybe RDFRuleset
findRuleset ScopedName
sn SwishState
st of
Maybe RDFRuleset
Nothing -> forall a b. a -> Either a b
Left ([Char]
"Ruleset not found: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
sn)
Just RDFRuleset
rs -> forall {ex}. Ruleset ex -> Either [Char] (Rule ex)
find1 RDFRuleset
rs
find1 :: Ruleset ex -> Either [Char] (Rule ex)
find1 Ruleset ex
rs = case forall ex. ScopedName -> Ruleset ex -> Maybe (Rule ex)
getRulesetRule ScopedName
rn Ruleset ex
rs of
Maybe (Rule ex)
Nothing -> forall a b. a -> Either a b
Left ([Char]
"Rule not in ruleset: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
sn forall a. [a] -> [a] -> [a]
++ [Char]
": " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
rn)
Just Rule ex
rl -> forall a b. b -> Either a b
Right Rule ex
rl
ssFindRuleset ::
ScopedName -> SwishStateIO (Either String RDFRuleset)
ssFindRuleset :: ScopedName -> SwishStateIO (Either [Char] RDFRuleset)
ssFindRuleset ScopedName
sn = forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets SwishState -> Either [Char] RDFRuleset
find
where
find :: SwishState -> Either [Char] RDFRuleset
find SwishState
st = case ScopedName -> SwishState -> Maybe RDFRuleset
findRuleset ScopedName
sn SwishState
st of
Maybe RDFRuleset
Nothing -> forall a b. a -> Either a b
Left ([Char]
"Ruleset not found: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show ScopedName
sn)
Just RDFRuleset
rs -> forall a b. b -> Either a b
Right RDFRuleset
rs
ssBwdChain ::
ScopedName
-> ScopedName
-> SwishStateIO (Either String RDFGraph)
-> ScopedName
-> NamespaceMap
-> SwishStateIO ()
ssBwdChain :: ScopedName
-> ScopedName
-> SwishStateIO (Either [Char] RDFGraph)
-> ScopedName
-> NamespaceMap
-> SwishStateIO ()
ssBwdChain ScopedName
sn ScopedName
rn SwishStateIO (Either [Char] RDFGraph)
cgf ScopedName
an NamespaceMap
prefs =
let
errmsg1 :: [Char]
errmsg1 = [Char]
"BwdChain rule error: "
errmsg2 :: [Char]
errmsg2 = [Char]
"BwdChain goal error: "
in
do { Either [Char] RDFRule
erl <- ScopedName -> ScopedName -> SwishStateIO (Either [Char] RDFRule)
ssFindRulesetRule ScopedName
sn ScopedName
rn
; Either [Char] RDFGraph
ecg <- SwishStateIO (Either [Char] RDFGraph)
cgf
; let fcr :: SwishState -> SwishState
fcr = case (Either [Char] RDFRule
erl,Either [Char] RDFGraph
ecg) of
(Left [Char]
er,Either [Char] RDFGraph
_) -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg1 forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Either [Char] RDFRule
_,Left [Char]
er) -> [Char] -> SwishState -> SwishState
setError ([Char]
errmsg2 forall a. [a] -> [a] -> [a]
++ [Char]
er)
(Right RDFRule
rl,Right RDFGraph
cg) ->
(NamedGraphMap -> NamedGraphMap) -> SwishState -> SwishState
modGraphs (forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ScopedName
an [RDFGraph]
ags)
where
ags :: [RDFGraph]
ags = forall a b. (a -> b) -> [a] -> [b]
map forall {lb}. Label lb => [NSGraph lb] -> NSGraph lb
mergegr (forall ex. Rule ex -> ex -> [[ex]]
bwdApply RDFRule
rl RDFGraph
cg)
mergegr :: [NSGraph lb] -> NSGraph lb
mergegr [NSGraph lb]
grs = case [NSGraph lb]
grs of
[] -> forall a. Monoid a => a
mempty
[NSGraph lb]
_ -> forall lb. NamespaceMap -> NSGraph lb -> NSGraph lb
setNamespaces NamespaceMap
prefs forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 forall (lg :: * -> *) lb.
(LDGraph lg lb, Ord lb) =>
lg lb -> lg lb -> lg lb
addGraphs [NSGraph lb]
grs
; forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify SwishState -> SwishState
fcr
}
getResourceData :: Maybe URI -> SwishStateIO (Either String L.Text)
getResourceData :: Maybe URI -> SwishStateIO (Either [Char] Text)
getResourceData = forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall {a}. StateT SwishState IO (Either a Text)
fromStdin forall {a}. URI -> StateT SwishState IO (Either a Text)
fromUri
where
fromStdin :: StateT SwishState IO (Either a Text)
fromStdin = forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift IO Text
LIO.getContents
fromUri :: URI -> StateT SwishState IO (Either a Text)
fromUri = forall {t :: (* -> *) -> * -> *} {a}.
(Functor (t IO), MonadTrans t) =>
URI -> t IO (Either a Text)
fromFile
fromFile :: URI -> t IO (Either a Text)
fromFile URI
uri | URI -> [Char]
uriScheme URI
uri forall a. Eq a => a -> a -> Bool
== [Char]
"file:" = forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ([Char] -> IO Text
LIO.readFile forall a b. (a -> b) -> a -> b
$ URI -> [Char]
uriPath URI
uri)
| Bool
otherwise = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Unsupported file name for read: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show URI
uri
putResourceData :: Maybe URI -> B.Builder -> SwishStateIO ()
putResourceData :: Maybe URI -> Builder -> SwishStateIO ()
putResourceData Maybe URI
muri Builder
gsh = do
Either IOError ()
ios <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a. Exception e => IO a -> IO (Either e a)
CE.try forall a b. (a -> b) -> a -> b
$ forall b a. b -> (a -> b) -> Maybe a -> b
maybe IO ()
toStdout URI -> IO ()
toUri Maybe URI
muri
case Either IOError ()
ios of
Left IOError
ioe -> forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify forall a b. (a -> b) -> a -> b
$ [Char] -> SwishState -> SwishState
setError
([Char]
"Error writing graph: " forall a. [a] -> [a] -> [a]
++
IOError -> [Char]
IO.ioeGetErrorString IOError
ioe)
Right ()
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
where
toStdout :: IO ()
toStdout = Text -> IO ()
LIO.putStrLn Text
gstr
toUri :: URI -> IO ()
toUri URI
uri | URI -> [Char]
uriScheme URI
uri forall a. Eq a => a -> a -> Bool
== [Char]
"file:" = [Char] -> Text -> IO ()
LIO.writeFile (URI -> [Char]
uriPath URI
uri) Text
gstr
| Bool
otherwise = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Unsupported scheme for write: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show URI
uri
gstr :: Text
gstr = Builder -> Text
B.toLazyText Builder
gsh