Safe Haskell | None |
---|
This module uses a state monad to track certain circuit information that is collected during parsing. This information contains the inputs and outputs of a circuit, as well as an entry for each subroutine that is defined within a circuit, and all the gates that make up the circuit.
Synopsis
- data Sub = Sub {}
- new_subroutine :: String -> Sub
- data CircInfoState = CircInfoState {
- used_wires :: Map Wire (Maybe Wiretype)
- defined_inputs :: [(Wire, Wiretype)]
- undefined_inputs :: [(Wire, Maybe Wiretype)]
- defined_outputs :: Maybe [(Wire, Wiretype)]
- current_subroutine :: [Sub]
- empty_circinfostate :: CircInfoState
- type CircInfo a = State CircInfoState a
- add_wire_inputs :: [(Wire, Wiretype)] -> CircInfo ()
- add_wire_outputs :: [(Wire, Wiretype)] -> CircInfo ()
- check_input :: Map Wire (Maybe Wiretype) -> (Wire, Maybe Wiretype) -> Bool
- check_inputs :: [(Wire, Maybe Wiretype)] -> Map Wire (Maybe Wiretype) -> [(Wire, Maybe Wiretype)]
- add_gate :: Gate -> [(Wire, Wiretype)] -> CircInfo CircInfoOut
- enter_subroutine :: String -> CircInfo ()
- add_subroutine_shape :: String -> CircInfo ()
- set_controllable :: ControllableFlag -> CircInfo ()
- data CircInfoOut
- isGate :: CircInfoOut -> Bool
- isSub :: CircInfoOut -> Bool
- exit_subroutine :: CircInfo CircInfoOut
- do_gate :: GatePlus -> CircInfo CircInfoOut
- run_ascii_line :: String -> CircInfo CircInfoOut
- run_ascii_lines :: [String] -> (Maybe [(Wire, Wiretype)], CircInfo [CircInfoOut])
- run :: CircInfo [CircInfoOut] -> ([Gate], Map BoxId Sub, CircInfoState)
Data-types for the State
Information collected about the current subroutine
new_subroutine :: String -> Sub Source #
An initial subroutine, with only a name
data CircInfoState Source #
A CircInfoState
is a record containing a list of input wires, along with their
types, and a list of output wires, along with their types. We also keep track of
whether we're in a subroutine definition, and all the subroutines that have been
defined.
CircInfoState | |
|
empty_circinfostate :: CircInfoState Source #
An initial, empty CircInfoState
type CircInfo a = State CircInfoState a Source #
The CircInfo
monad is used to track a CircInfoState
during
parsing.
add_wire_inputs :: [(Wire, Wiretype)] -> CircInfo () Source #
The CircInfo
monad tracks wires that are inputs. These can only
be given in an "Input" line in the parsed ASCII, so we assume
that duplicate wires don't occur, and we add input wires to the
state without checking.
add_wire_outputs :: [(Wire, Wiretype)] -> CircInfo () Source #
The CircInfo
monad tracks wires that are outputs. These can
only be given in an "Output" line in the parsed ASCII, so we
assume that duplicate wires don't occur, and we add output wires to
the state without checking.
check_input :: Map Wire (Maybe Wiretype) -> (Wire, Maybe Wiretype) -> Bool Source #
Given a a wire, check whether it is already in scope.
check_inputs :: [(Wire, Maybe Wiretype)] -> Map Wire (Maybe Wiretype) -> [(Wire, Maybe Wiretype)] Source #
Given a list of wires that are inputs to a gate, check whether they are already in scope. The returned wires are not in scope, when used by a gate, and must be declared as undefined inputs.
add_gate :: Gate -> [(Wire, Wiretype)] -> CircInfo CircInfoOut Source #
The CircInfo Monad keeps track of all the gates that have been parsed and adds them to the relevant part of the state.
enter_subroutine :: String -> CircInfo () Source #
The CircInfo Monad tracks whether we are in a subroutine, and collects info about that subroutine. The entrance to the subroutine contains its name.
add_subroutine_shape :: String -> CircInfo () Source #
We can add the shape to the current subroutine
set_controllable :: ControllableFlag -> CircInfo () Source #
The CircInfo Monad tracks whether we are in a subroutine, and collects info about that subroutine. The subroutine might be controllable.
data CircInfoOut Source #
A datatype to represent the various outputs a CircInfo computation may require.
isGate :: CircInfoOut -> Bool Source #
This function returns True if the given input defines a Gate
isSub :: CircInfoOut -> Bool Source #
This function returns True if the given inputs defines a SubDef
exit_subroutine :: CircInfo CircInfoOut Source #
The CircInfo Monad tracks whether we are in a subroutine, and collects info about that subroutine. At the end of the subroutine, it stores the subroutine for later use.
do_gate :: GatePlus -> CircInfo CircInfoOut Source #
Take a GatePlus and execute it in the CircInfo
monad.
Again, the executed computation may depend upon whether we're in a subroutine
definition.
run_ascii_line :: String -> CircInfo CircInfoOut Source #
Monad version of parse_ascii_line
: parse a string and execute the
resulting gate directly in the CircInfo
monad.
run_ascii_lines :: [String] -> (Maybe [(Wire, Wiretype)], CircInfo [CircInfoOut]) Source #
Parse a stream consisting of many lines of ASCII output and execute
the parsed gates in the CircInfo
monad, checking to see if the first
line defines the inputs to the circuit.