{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Text.XML.Cursor
( Tag(..), getTag, setTag, fromTag
, Cursor, Cursor'(..), Path
, fromRootElement
, fromRoot
, toRootElement
, toRoot
, upCast
, downCast
, parent
, root
, getChild
, firstChild
, lastChild
, left
, right
, nextDF
, findChild
, findLeft
, findRight
, findRec
, isRoot
, isFirst
, isLast
, isLeaf
, isChild
, hasChildren
, getNodeIndex
, insertLeft
, insertRight
, insertGoLeft
, insertGoRight
, removeLeft
, removeRight
, removeGoLeft
, removeGoRight
, removeGoUp
) where
import Common
import Text.XML.Types
import Text.XML.Types.Internal
data Tag = Tag
{ tagName :: QName
, tagAttribs :: [Attr]
} deriving (Show,Generic,Typeable,Data)
instance NFData Tag
getTag :: Element -> Tag
getTag e = Tag { tagName = elName e
, tagAttribs = elAttribs e
}
setTag :: Tag -> Element -> Element
setTag t e = fromTag t (elContent e)
fromTag :: Tag -> [Content] -> Element
fromTag t cs = Element { elName = tagName t
, elAttribs = tagAttribs t
, elContent = cs
}
type Path = [([Content],Tag,[Content])]
type Cursor = Cursor' Content
data Cursor' content = Cur
{ current :: content
, lefts :: [Content]
, rights :: [Content]
, parents :: Path
} deriving (Show,Generic,Typeable,Data,Functor,Foldable,Traversable)
instance NFData content => NFData (Cursor' content)
parent :: IsContent content => Cursor' content -> Maybe (Cursor' Element)
parent loc =
case parents loc of
(pls,v,prs) : ps -> Just
Cur { current = fromTag v $
combChildren (lefts loc) (toContent (current loc)) (rights loc)
, lefts = pls
, rights = prs
, parents = ps
}
[] -> Nothing
root :: IsContent content => Cursor' content -> Cursor' Element
root loc = maybe loc' root (parent loc :: Maybe (Cursor' Element))
where
loc' :: Cursor' Element
loc' = case traverse toElem loc of
Nothing -> error "root: invalid cursor"
Just x -> x
left :: IsContent content => Cursor' content -> Maybe Cursor
left loc =
case lefts loc of
t : ts -> Just loc { current = t
, lefts = ts
, rights = toContent (current loc) : rights loc
}
[] -> Nothing
right :: IsContent content => Cursor' content -> Maybe Cursor
right loc =
case rights loc of
t : ts -> Just loc { current = t
, lefts = toContent (current loc) : lefts loc
, rights = ts }
[] -> Nothing
firstChild :: IsContent content => Cursor' content -> Maybe Cursor
firstChild loc =
do (t : ts, ps) <- downParents loc
return Cur { current = t, lefts = [], rights = ts , parents = ps }
lastChild :: IsContent content => Cursor' content -> Maybe Cursor
lastChild loc =
do (ts, ps) <- downParents loc
case reverse ts of
l : ls -> return Cur { current = l, lefts = ls, rights = []
, parents = ps }
[] -> Nothing
findLeft :: (Cursor -> Bool) -> Cursor -> Maybe Cursor
findLeft p loc = do loc1 <- left loc
if p loc1 then return loc1 else findLeft p loc1
findRight :: (Cursor -> Bool) -> Cursor -> Maybe Cursor
findRight p loc = do loc1 <- right loc
if p loc1 then return loc1 else findRight p loc1
findChild :: (Cursor -> Bool) -> Cursor -> Maybe Cursor
findChild p loc =
do loc1 <- firstChild loc
if p loc1 then return loc1 else findRight p loc1
nextDF :: IsContent content => Cursor' content -> Maybe Cursor
nextDF c = firstChild c <|> up (toContent <$> c)
where
up :: Cursor -> Maybe Cursor
up x = right x <|> (up =<< y)
where
y = fmap Elem <$> parent x
findRec :: (Cursor -> Bool) -> Cursor -> Maybe Cursor
findRec p c = if p c then Just c else findRec p =<< nextDF c
getChild :: IsContent content => Word -> Cursor' content -> Maybe Cursor
getChild n loc =
do (ts,ps) <- downParents loc
(ls,t,rs) <- splitChildren ts n
return Cur { current = t, lefts = ls, rights = rs, parents = ps }
downParents :: IsContent content => Cursor' content -> Maybe ([Content], Path)
downParents loc =
case toElem (current loc) of
Just e -> Just ( elContent e
, (lefts loc, getTag e, rights loc) : parents loc
)
Nothing -> Nothing
upCast :: IsContent content => Cursor' content -> Cursor
upCast = fmap toContent
downCast :: IsContent content => Cursor -> Maybe (Cursor' content)
downCast = traverse fromContent
fromRootElement :: Element -> Cursor' Element
fromRootElement e = Cur { current = e, lefts = [], rights = [], parents = [] }
fromRoot :: Root -> Cursor' Element
fromRoot r = Cur { current = rootElement r
, lefts = map toContent (rootPreElem r ++ maybe [] snd (rootDoctype r))
, rights = map toContent (rootPostElem r)
, parents = []
}
toRootElement :: IsContent content => Cursor' content -> Element
toRootElement loc = current (root loc)
toRoot :: IsContent content => Cursor' content -> Maybe Root
toRoot loc = do
rootPreElem <- traverse fromContent l
rootPostElem <- traverse fromContent r
pure Root{..}
where
Cur rootElement l r [] = root loc
rootXmlDeclaration = Nothing
rootDoctype = Nothing
isRoot :: Cursor' content -> Bool
isRoot loc = null (parents loc)
isFirst :: Cursor' content -> Bool
isFirst loc = null (lefts loc)
isLast :: Cursor' content -> Bool
isLast loc = null (rights loc)
isLeaf :: IsContent content => Cursor' content -> Bool
isLeaf loc = isNothing (downParents loc)
isChild :: Cursor' content -> Bool
isChild loc = not (isRoot loc)
getNodeIndex :: Cursor' content -> Word
getNodeIndex loc = fromIntegral (length (lefts loc))
hasChildren :: IsContent content => Cursor' content -> Bool
hasChildren loc = not (isLeaf loc)
insertLeft :: IsContent c => c -> Cursor' content -> Cursor' content
insertLeft t loc = loc { lefts = toContent t : lefts loc }
insertRight :: Content -> Cursor' content -> Cursor' content
insertRight t loc = loc { rights = t : rights loc }
removeLeft :: Cursor -> Maybe (Content,Cursor)
removeLeft loc = case lefts loc of
l : ls -> return (l,loc { lefts = ls })
[] -> Nothing
removeRight :: Cursor -> Maybe (Content,Cursor)
removeRight loc = case rights loc of
l : ls -> return (l,loc { rights = ls })
[] -> Nothing
insertGoLeft :: Content -> Cursor -> Cursor
insertGoLeft t loc = loc { current = t, rights = current loc : rights loc }
insertGoRight :: Content -> Cursor -> Cursor
insertGoRight t loc = loc { current = t, lefts = current loc : lefts loc }
removeGoLeft :: Cursor' content -> Maybe Cursor
removeGoLeft loc = case lefts loc of
l : ls -> Just loc { current = l, lefts = ls }
[] -> Nothing
removeGoRight :: Cursor' content -> Maybe Cursor
removeGoRight loc = case rights loc of
l : ls -> Just loc { current = l, rights = ls }
[] -> Nothing
removeGoUp :: Cursor' content -> Maybe Cursor
removeGoUp loc =
case parents loc of
(pls,v,prs) : ps -> Just
Cur { current = Elem (fromTag v (reverse (lefts loc) ++ rights loc))
, lefts = pls, rights = prs, parents = ps
}
[] -> Nothing
splitChildren :: [a] -> Word -> Maybe ([a],a,[a])
splitChildren = go []
where
go acc (x:xs) 0 = Just (acc,x,xs)
go acc (x:xs) n = go (x:acc) xs $! n-1
go _ [] _ = Nothing
combChildren :: [a] -> a -> [a] -> [a]
combChildren ls t rs = foldl (flip (:)) (t:rs) ls