Safe Haskell | None |
---|
This module provides some testing facilities for the Boolean Formula algorithm, as well as some auxiliary function definitions. See Quipper.Algorithms.BF.Main for an overview of the boolean formula algorithm.
Synopsis
- moves_to_hex :: BooleanFormulaOracle -> [Int] -> HexBoard
- moves_to_pos :: BooleanFormulaOracle -> [Int] -> [[Bool]]
- set_bool :: [Bool] -> [Bool] -> Bool -> [Bool]
- fromPos :: BooleanFormulaOracle -> [[Bool]] -> HexBoard
- double :: Double
- oracle_with_input :: BooleanFormulaOracle -> BoolRegister -> Circ BooleanFormulaRegister
- run_oracle_with_input :: BooleanFormulaOracle -> BoolRegister -> IO BoolRegister
- diffuse_with_input :: BoolRegister -> Circ BooleanFormulaRegister
- run_diffuse_with_input :: BoolRegister -> IO BoolRegister
- walk_with_input :: BoolRegister -> Circ BooleanFormulaRegister
- run_walk_with_input :: BoolRegister -> IO BoolRegister
- undo_oracle_with_input :: BooleanFormulaOracle -> BoolRegister -> Circ BooleanFormulaRegister
- run_undo_oracle_with_input :: BooleanFormulaOracle -> BoolRegister -> IO BoolRegister
- run_odwu_with_input :: BooleanFormulaOracle -> BoolRegister -> IO BoolRegister
- repeat_odwu_n :: Int -> BooleanFormulaOracle -> BoolRegister -> IO [HexBoard]
- repeat_odwu_infinite :: BooleanFormulaOracle -> BoolRegister -> IO ()
- tidy :: (Bool, Bool) -> [[Bool]] -> [[Bool]]
- hex_with_input :: BooleanFormulaOracle -> BoolRegister -> Circ Qubit
- run_hex_with_input :: BooleanFormulaOracle -> BoolRegister -> IO Bool
- checkwin_trace :: BooleanFormulaOracle -> IO [[Bool]]
Auxiliary definitions
moves_to_hex :: BooleanFormulaOracle -> [Int] -> HexBoard Source #
Convert list of moves, into a HexBoard
.
moves_to_pos :: BooleanFormulaOracle -> [Int] -> [[Bool]] Source #
Convert a list of moves, into a list of positions.
set_bool :: [Bool] -> [Bool] -> Bool -> [Bool] Source #
Set the position in board, at the given address, to the given boolean.
fromPos :: BooleanFormulaOracle -> [[Bool]] -> HexBoard Source #
Create the description of a Hex board, from the given classical state of a position register from the Boolean Formula algorithm.
Testing various circuits
oracle_with_input :: BooleanFormulaOracle -> BoolRegister -> Circ BooleanFormulaRegister Source #
Construct the oracle circuit, initialized with the given boolean inputs.
run_oracle_with_input :: BooleanFormulaOracle -> BoolRegister -> IO BoolRegister Source #
Simulate the oracle circuit with the given boolean inputs, to give boolean outputs.
diffuse_with_input :: BoolRegister -> Circ BooleanFormulaRegister Source #
Return the diffuse circuit, initialized with the given boolean inputs.
run_diffuse_with_input :: BoolRegister -> IO BoolRegister Source #
Simulate the diffuse circuit with the given boolean inputs, to give boolean outputs.
walk_with_input :: BoolRegister -> Circ BooleanFormulaRegister Source #
Return the walk circuit, initialized with the given boolean inputs.
run_walk_with_input :: BoolRegister -> IO BoolRegister Source #
Simulate the walk circuit with the given boolean inputs, to give boolean outputs.
undo_oracle_with_input :: BooleanFormulaOracle -> BoolRegister -> Circ BooleanFormulaRegister Source #
Return the undo_oracle
circuit, initialized with the given
boolean inputs.
run_undo_oracle_with_input :: BooleanFormulaOracle -> BoolRegister -> IO BoolRegister Source #
Simulate the undo_oracle
circuit with the given boolean inputs,
to give boolean outputs.
Oracle, diffuse, walk, and undo_oracle
run_odwu_with_input :: BooleanFormulaOracle -> BoolRegister -> IO BoolRegister Source #
Create a register from the given boolean inputs,
and then run the oracle circuit, followed by the diffusion step,
followed by the walk step, and finally the undo_oracle
circuit.
This is really a test of all four parts. The return values when
running this step can be fed forward into the next iteration, and
the undo_oracle
step should have returned the eight work qubits
back to the initial False
states.
We break the simulation into the four separate steps, so that we are not trying to simulate the walk/undo_oracle steps over a quantum state, as this gives us an overhead.
repeat_odwu_n :: Int -> BooleanFormulaOracle -> BoolRegister -> IO [HexBoard] Source #
Simulate the odwu circuit, running it n times and passing the output of each iteration as inputs to the next iteration. The overall return value is a representation of the HexBoard at each step of the simulation.
repeat_odwu_infinite :: BooleanFormulaOracle -> BoolRegister -> IO () Source #
Simulate the odwu circuit, running it repeatedly and passing the output of each iteration as inputs to the next iteration. Outputs an ASCII representation of the position register/board after each step.
tidy :: (Bool, Bool) -> [[Bool]] -> [[Bool]] Source #
Trim any leading zeroes from a pos register, and a single leading 1, if we're not at a paraleaf, and a 3, if we're at the root.
hex_with_input :: BooleanFormulaOracle -> BoolRegister -> Circ Qubit Source #
Return the Hex
circuit, initialized for the given oracle, with the given
boolean inputs.
run_hex_with_input :: BooleanFormulaOracle -> BoolRegister -> IO Bool Source #
Simulate the running of the Hex
circuit, initialized for the given oracle,
with the given boolean inputs.
checkwin_trace :: BooleanFormulaOracle -> IO [[Bool]] Source #
Simulate the running of the checkwin_red
subroutine for the
given oracle, and keep track of the state of certain "traced" qubits within that
subroutine, which represent the Hex board at each iteration of the while loop in
the flood_fill
algorithm.