module Swish.RDF.Formatter.N3
( NodeGenLookupMap
, formatGraphAsText
, formatGraphAsLazyText
, formatGraphAsBuilder
, formatGraphIndent
, formatGraphDiag
)
where
import Swish.RDF.Formatter.Internal (NodeGenLookupMap, SubjTree, PredTree
, SLens(..)
, LabelContext(..)
, NodeGenState(..)
, changeState
, hasMore
, emptyNgs
, findMaxBnode
, processArcs
, quoteB
, formatScopedName
, formatPlainLit
, formatLangLit
, formatTypedLit
, insertList
, nextLine_
, mapBlankNode_
, formatPrefixes_
, formatGraph_
, formatSubjects_
, formatProperties_
, formatObjects_
, insertBnode_
, extractList_
)
import Swish.Namespace (ScopedName)
import Swish.RDF.Graph (
RDFGraph, RDFLabel(..),
NamespaceMap,
emptyNamespaceMap,
FormulaMap, emptyFormulaMap,
setNamespaces, getNamespaces,
getFormulae,
emptyRDFGraph
)
import Swish.RDF.Vocabulary (
rdfType,
rdfNil,
owlSameAs, logImplies
)
import Control.Monad (liftM, void)
import Control.Monad.State (State, modify, get, gets, put, runState)
import Data.Char (isDigit)
import Data.Monoid (Monoid(..))
import Data.Word (Word32)
import qualified Data.Map as M
import qualified Data.Text as T
import qualified Data.Text.Lazy as L
import qualified Data.Text.Lazy.Builder as B
data N3FormatterState = N3FS
{ indent :: B.Builder
, lineBreak :: Bool
, graph :: RDFGraph
, subjs :: SubjTree RDFLabel
, props :: PredTree RDFLabel
, objs :: [RDFLabel]
, formAvail :: FormulaMap RDFLabel
, formQueue :: [(RDFLabel,RDFGraph)]
, prefixes :: NamespaceMap
, nodeGenSt :: NodeGenState
, bNodesCheck :: [RDFLabel]
, traceBuf :: [String]
}
type SL a = SLens N3FormatterState a
_lineBreak :: SL Bool
_lineBreak = SLens lineBreak $ \a b -> a { lineBreak = b }
_nodeGen :: SL NodeGenState
_nodeGen = SLens nodeGenSt $ \a b -> a { nodeGenSt = b }
type Formatter a = State N3FormatterState a
updateState :: N3FormatterState -> SubjTree RDFLabel -> PredTree RDFLabel -> [RDFLabel] -> N3FormatterState
updateState ost nsubjs nprops nobjs = ost { subjs = nsubjs, props = nprops, objs = nobjs }
emptyN3FS :: NamespaceMap -> NodeGenState -> N3FormatterState
emptyN3FS pmap ngs = N3FS
{ indent = "\n"
, lineBreak = False
, graph = emptyRDFGraph
, subjs = []
, props = []
, objs = []
, formAvail = emptyFormulaMap
, formQueue = []
, prefixes = pmap
, nodeGenSt = ngs
, bNodesCheck = []
, traceBuf = []
}
setIndent :: B.Builder -> Formatter ()
setIndent ind = modify $ \st -> st { indent = ind }
setLineBreak :: Bool -> Formatter ()
setLineBreak brk = modify $ \st -> st { lineBreak = brk }
setSubjs :: SubjTree RDFLabel -> Formatter ()
setSubjs sl = modify $ \st -> st { subjs = sl }
setProps :: PredTree RDFLabel -> Formatter ()
setProps ps = modify $ \st -> st { props = ps }
queueFormula :: RDFLabel -> Formatter ()
queueFormula fn = do
st <- get
let fa = formAvail st
_newState fv = st {
formAvail = M.delete fn fa,
formQueue = (fn,fv) : formQueue st
}
case M.lookup fn fa of
Nothing -> return ()
Just v -> void $ put $ _newState v
extractFormula :: RDFLabel -> Formatter (Maybe RDFGraph)
extractFormula fn = do
st <- get
let (rval, nform) = M.updateLookupWithKey (\_ _ -> Nothing) fn $ formAvail st
put $ st { formAvail = nform }
return rval
extractList :: LabelContext -> RDFLabel -> Formatter (Maybe [RDFLabel])
extractList = extractList_ subjs props setSubjs setProps
formatGraphAsText :: RDFGraph -> T.Text
formatGraphAsText = L.toStrict . formatGraphAsLazyText
formatGraphAsLazyText :: RDFGraph -> L.Text
formatGraphAsLazyText = B.toLazyText . formatGraphAsBuilder
formatGraphAsBuilder :: RDFGraph -> B.Builder
formatGraphAsBuilder = formatGraphIndent "\n" True
formatGraphIndent ::
B.Builder
-> Bool
-> RDFGraph
-> B.Builder
formatGraphIndent indnt flag gr =
let (res, _, _, _) = formatGraphDiag indnt flag gr
in res
formatGraphDiag ::
B.Builder
-> Bool
-> RDFGraph
-> (B.Builder, NodeGenLookupMap, Word32, [String])
formatGraphDiag indnt flag gr =
let fg = formatGraph indnt " .\n" False flag gr
ngs = emptyNgs { nodeGen = findMaxBnode gr }
(out, fgs) = runState fg (emptyN3FS emptyNamespaceMap ngs)
ogs = nodeGenSt fgs
in (out, nodeMap ogs, nodeGen ogs, traceBuf fgs)
formatGraph ::
B.Builder
-> B.Builder
-> Bool
-> Bool
-> RDFGraph
-> Formatter B.Builder
formatGraph = formatGraph_ setIndent setLineBreak newState formatPrefixes subjs formatSubjects
formatPrefixes :: NamespaceMap -> Formatter B.Builder
formatPrefixes = formatPrefixes_ nextLine
formatSubjects :: Formatter B.Builder
formatSubjects = formatSubjects_ nextSubject formatLabel props formatProperties subjs nextLine
formatProperties :: RDFLabel -> B.Builder -> Formatter B.Builder
formatProperties = formatProperties_ nextProperty formatLabel formatObjects props nextLine
formatObjects :: RDFLabel -> RDFLabel -> B.Builder -> Formatter B.Builder
formatObjects = formatObjects_ nextObject formatLabel objs nextLine
insertFormula :: RDFGraph -> Formatter B.Builder
insertFormula gr = do
pmap0 <- gets prefixes
ngs0 <- gets nodeGenSt
ind <- gets indent
let grm = formatGraph (ind `mappend` " ") "" True False
(setNamespaces emptyNamespaceMap gr)
(f3str, fgs') = runState grm (emptyN3FS pmap0 ngs0)
modify $ \st -> st { nodeGenSt = nodeGenSt fgs'
, prefixes = prefixes fgs' }
f4str <- nextLine " } "
return $ mconcat [" { ",f3str, f4str]
insertBnode :: LabelContext -> RDFLabel -> Formatter B.Builder
insertBnode SubjContext lbl = do
flag <- hasMore props
txt <- if flag
then (`mappend` "\n") `liftM` formatProperties lbl ""
else return ""
return $ mconcat ["[", txt, "]"]
insertBnode _ lbl = insertBnode_ subjs props objs updateState formatProperties lbl
newState :: RDFGraph -> N3FormatterState -> N3FormatterState
newState gr st =
let pre' = prefixes st `M.union` getNamespaces gr
(arcSubjs, bNodes) = processArcs gr
in st { graph = gr
, subjs = arcSubjs
, props = []
, objs = []
, formAvail = getFormulae gr
, prefixes = pre'
, bNodesCheck = bNodes
}
nextSubject :: Formatter RDFLabel
nextSubject =
changeState $ \st ->
let (a,b):sbs = subjs st
nst = st { subjs = sbs
, props = b
, objs = []
}
in (a, nst)
nextProperty :: RDFLabel -> Formatter RDFLabel
nextProperty _ =
changeState $ \st ->
let (a,b):prs = props st
nst = st { props = prs
, objs = b
}
in (a, nst)
nextObject :: RDFLabel -> RDFLabel -> Formatter RDFLabel
nextObject _ _ =
changeState $ \st ->
let ob:obs = objs st
nst = st { objs = obs }
in (ob, nst)
nextLine :: B.Builder -> Formatter B.Builder
nextLine = nextLine_ indent _lineBreak
specialTable :: [(ScopedName, String)]
specialTable =
[ (rdfType, "a")
, (owlSameAs, "=")
, (logImplies, "=>")
, (rdfNil, "()")
]
formatLabel :: LabelContext -> RDFLabel -> Formatter B.Builder
formatLabel lctxt lab@(Blank (_:_)) = do
mlst <- extractList lctxt lab
case mlst of
Just lst -> insertList (formatLabel ObjContext) lst
Nothing -> do
mfml <- extractFormula lab
case mfml of
Just fml -> insertFormula fml
Nothing -> do
nb1 <- gets bNodesCheck
if lctxt /= PredContext && lab `notElem` nb1
then insertBnode lctxt lab
else formatNodeId lab
formatLabel _ lab@(Res sn) =
case lookup sn specialTable of
Just txt -> return $ quoteB True txt
Nothing -> do
pr <- gets prefixes
queueFormula lab
return $ formatScopedName sn pr
formatLabel _ (Lit lit) = return $ formatPlainLit lit
formatLabel _ (LangLit lit lcode) = return $ formatLangLit lit lcode
formatLabel _ (TypedLit lit dtype) = return $ formatTypedLit True lit dtype
formatLabel _ lab = return $ B.fromString $ show lab
formatNodeId :: RDFLabel -> Formatter B.Builder
formatNodeId lab@(Blank (lnc:_)) =
if isDigit lnc then mapBlankNode lab else return $ B.fromString $ show lab
formatNodeId other = error $ "formatNodeId not expecting a " ++ show other
mapBlankNode :: RDFLabel -> Formatter B.Builder
mapBlankNode = mapBlankNode_ _nodeGen