Expose Vertex to access label of a node from a Transducer and implement running a Transducer on some input
This commit is contained in:
parent
916fde61ae
commit
174912bb5a
2 changed files with 14 additions and 4 deletions
|
@ -2,6 +2,7 @@
|
|||
{-# LANGUAGE DeriveFunctor #-}
|
||||
module Graph (
|
||||
Graph(..)
|
||||
, Vertex(..)
|
||||
, editLabel
|
||||
, follow
|
||||
, open
|
||||
|
|
|
@ -1,11 +1,13 @@
|
|||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
module Transducer (
|
||||
Transducer
|
||||
, fromList
|
||||
, run
|
||||
) where
|
||||
|
||||
import Stream (Stream)
|
||||
import Graph (Graph, editLabel, open, rewind, singleton, weave)
|
||||
import Stream (Stream(..), merge)
|
||||
import qualified Stream (empty)
|
||||
import Graph (Graph(..), Vertex(..), editLabel, follow, open, rewind, singleton, weave)
|
||||
|
||||
type Transducer input output = Graph input [output]
|
||||
|
||||
|
@ -19,5 +21,12 @@ add transducer (path, output) =
|
|||
fromList :: Ord input => [([input], output)] -> Transducer input output
|
||||
fromList = foldl add empty
|
||||
|
||||
run :: Ord input => Transducer input output -> Stream input -> Stream output
|
||||
run = undefined
|
||||
run :: (Ord input, Eq output) => Transducer input output -> Stream input -> Stream output
|
||||
run transducer (Stream inputs) = foldl (\(Stream outputs) (input, stream) ->
|
||||
case follow transducer input of
|
||||
Nothing -> Stream.empty
|
||||
Just newState@(Graph {focus}) ->
|
||||
Stream ((emit stream <$> label focus) ++ outputs) `merge` run newState stream
|
||||
) Stream.empty inputs
|
||||
where
|
||||
emit stream output = (output, run (rewind transducer) stream)
|
||||
|
|
Loading…
Reference in a new issue