module Data.DAWG.Node
(
ID
, Sym
, Node (..)
, onSym
, trans
, edges
, subst
, toGeneric
, Edge
, to
, label
, annotate
, labeled
) where
import Control.Applicative ((<$>), (<*>))
import Control.Arrow (second)
import Data.Binary (Binary, Get, put, get)
import Data.Vector.Unboxed (Unbox)
import qualified Data.DAWG.VMap as M
import qualified Data.DAWG.Node.Specialized as N
type ID = Int
type Sym = Int
type Edge a = (ID, a)
to :: Edge a -> ID
to = fst
label :: Edge a -> a
label = snd
annotate :: a -> Edge b -> Edge a
annotate x (i, _) = (i, x)
labeled :: a -> ID -> Edge a
labeled x i = (i, x)
data Node a b
= Branch {
eps :: !ID
, edgeMap :: !(M.VMap b) }
| Leaf { value :: !a }
deriving (Show, Eq, Ord)
instance (Unbox b, Binary a, Binary b) => Binary (Node a b) where
put Branch{..} = put (1 :: Int) >> put eps >> put edgeMap
put Leaf{..} = put (2 :: Int) >> put value
get = do
x <- get :: Get Int
case x of
1 -> Branch <$> get <*> get
_ -> Leaf <$> get
onSym :: Unbox b => Sym -> Node a b -> Maybe b
onSym x (Branch _ es) = M.lookup x es
onSym _ (Leaf _) = Nothing
trans :: Unbox b => Node a b -> [(Sym, b)]
trans (Branch _ es) = M.toList es
trans (Leaf _) = []
edges :: Unbox b => Node a b -> [b]
edges = map snd . trans
subst :: Unbox b => Sym -> b -> Node a b -> Node a b
subst x e (Branch w es) = Branch w (M.insert x e es)
subst _ _ l = l
toGeneric :: N.Node a -> Node a (Edge ())
toGeneric N.Leaf{..} = Leaf value
toGeneric N.Branch{..} = Branch eps (annEdges edgeMap) where
annEdges = M.fromList . map annEdge . M.toList
annEdge = second (labeled ())