{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LINE 1 "Quipper/Algorithms/BF/BooleanFormula.hs" #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Quipper.Algorithms.BF.BooleanFormula where
import Quipper
import Quipper.Internal
import Quipper.Algorithms.BF.Hex
import Quipper.Libraries.QFT
import Quipper.Libraries.QuantumIf
import Quipper.Libraries.Simulation
import Quipper.Libraries.Decompose
import Quipper.Utils.Auxiliary (mmap)
import Data.Typeable
data BooleanFormulaOracle = BFO {
oracle_x_max :: Int,
oracle_y_max :: Int,
oracle_t :: Int,
oracle_s :: Int,
oracle_m :: Int,
start_board :: HexBoard,
oracle_hex :: HexCircuit
}
data HexCircuit = Hex
| Dummy
| EmptyHex
createOracle :: Int -> Int -> Int -> BooleanFormulaOracle
createOracle x y t = BFO {
oracle_x_max = x,
oracle_y_max = y,
oracle_t = t,
oracle_s = s,
oracle_m = m,
start_board = (empty,empty),
oracle_hex = Hex
} where s = x * y
m = ceiling (log (fromIntegral (s+1)) / log 2)
empty = replicate s False
update_hex :: BooleanFormulaOracle -> HexCircuit -> BooleanFormulaOracle
update_hex bfo hex = bfo {oracle_hex = hex}
update_start_board :: BooleanFormulaOracle -> HexBoard -> BooleanFormulaOracle
update_start_board bfo start = bfo {
oracle_s = s,
start_board = start
} where
x = oracle_x_max bfo
y = oracle_y_max bfo
s = (x*y) - (moves_made start)
full_oracle :: BooleanFormulaOracle
full_oracle = createOracle 9 7 189
test_oracle :: BooleanFormulaOracle
test_oracle = createOracle 5 3 4
type HexBoard = ([Bool],[Bool])
moves_made :: HexBoard -> Int
moves_made (blue,red) = moves blue + moves red
where moves color = length (filter id color)
empty_spaces :: HexBoard -> [Int]
empty_spaces (blue,red) = empty_spaces' blue red 0
where
empty_spaces' [] [] _ = []
empty_spaces' [] _ _ = error "empty_spaces: Red and Blue boards of different length"
empty_spaces' _ [] _ = error "empty_spaces: Red and Blue boards of different length"
empty_spaces' (b:bs) (r:rs) n = if (b || r) then rest else (n:rest)
where rest = empty_spaces' bs rs (n+1)
type PhaseEstimationRegister = [Qubit]
type GenericDirectionRegister a = [a]
type DirectionRegister = GenericDirectionRegister Qubit
data GenericBooleanFormulaRegister a = BFR {
position_flags :: (a,a),
position :: [GenericDirectionRegister a],
work_leaf :: a,
work_paraleaf :: a,
work_binary :: a,
work_height :: a,
work_r :: a,
work_rp :: a,
work_rpp :: a,
direction :: GenericDirectionRegister a
}
deriving (Typeable, Show)
type BooleanFormulaRegister = GenericBooleanFormulaRegister Qubit
labelBFR :: BooleanFormulaRegister -> Circ ()
labelBFR reg = do
let tuple = toTuple reg
label tuple (("pos-leaf","pos-paraleaf"),
"pos",
("leaf","paraleaf","binary","height","r","rp","rpp"),
"dir")
type BoolRegister = GenericBooleanFormulaRegister Bool
toTuple :: GenericBooleanFormulaRegister a -> ((a,a),[[a]],(a,a,a,a,a,a,a),[a])
toTuple r = (position_flags r,position r,(work_leaf r,work_paraleaf r,work_binary r,work_height r,work_r r,work_rp r,work_rpp r),direction r)
fromTuple :: ((a,a),[[a]],(a,a,a,a,a,a,a),[a]) -> GenericBooleanFormulaRegister a
fromTuple (pf,p,(wl,wp,wb,wh,wr,wrp,wrpp),d) = BFR {
position_flags = pf,
position = p,
work_leaf = wl,
work_paraleaf = wp,
work_binary = wb,
work_height = wh,
work_r = wr,
work_rp = wrp,
work_rpp = wrpp,
direction = d
}
type instance QCType x y (GenericBooleanFormulaRegister a) = GenericBooleanFormulaRegister (QCType x y a)
type instance QTypeB (GenericBooleanFormulaRegister a) = GenericBooleanFormulaRegister (QTypeB a)
instance QCData a => QCData (GenericBooleanFormulaRegister a) where
qcdata_mapM s f g xs = mmap fromTuple $ qcdata_mapM (toTuple s) f g (toTuple xs)
qcdata_zip s q c q' c' xs ys e = fromTuple $ qcdata_zip (toTuple s) q c q' c' (toTuple xs) (toTuple ys) e
qcdata_promote a x s = fromTuple $ qcdata_promote (toTuple a) (toTuple x) s
instance (Labelable a String) => Labelable (GenericBooleanFormulaRegister a) String where
label_rec r s = do
label_rec (position_flags r) s `dotted_indexed` "posflag"
label_rec (position r) s `dotted_indexed` "pos"
label_rec (work_leaf r) s `dotted_indexed` "leaf"
label_rec (work_paraleaf r) s `dotted_indexed` "paraleaf"
label_rec (work_binary r) s `dotted_indexed` "binary"
label_rec (work_height r) s `dotted_indexed` "height"
label_rec (work_r r) s `dotted_indexed` "r"
label_rec (work_rp r) s `dotted_indexed` "rp"
label_rec (work_rpp r) s `dotted_indexed` "rpp"
label_rec (direction r) s `dotted_indexed` "dir"
createRegister :: BooleanFormulaOracle -> BoolRegister
createRegister oracle = BFR {
position_flags = (False,False),
position = replicate s (replicate m False),
work_leaf = False,
work_paraleaf = False,
work_binary = False,
work_height = False,
work_r = False,
work_rp = False,
work_rpp = False,
direction = replicate m False
} where
s = oracle_s oracle
m = oracle_m oracle
registerShape :: BooleanFormulaOracle -> BooleanFormulaRegister
registerShape oracle = qshape (createRegister oracle)
initializeRegister :: BooleanFormulaOracle -> Circ BooleanFormulaRegister
initializeRegister oracle = qinit (createRegister oracle)
qw_bf :: BooleanFormulaOracle -> Circ [Bit]
qw_bf oracle = do
let t = oracle_t oracle
a <- qinit (replicate t False)
label a "a"
a <- mapUnary hadamard a
b <- initializeRegister oracle
labelBFR b
let t = oracle_t oracle
map_exp_u oracle a b (t-1)
a <- (subroutine_inverse_qft oracle) a
qdiscard b
measure a
subroutine_inverse_qft :: BooleanFormulaOracle -> [Qubit] -> Circ [Qubit]
subroutine_inverse_qft o = box "QFT*" (reverse_generic_endo qft_little_endian)
map_exp_u :: BooleanFormulaOracle -> [Qubit] -> BooleanFormulaRegister -> Int -> Circ ()
map_exp_u _ [] _ _ = return ()
map_exp_u o (a:as) b l = do
let x_max = oracle_x_max o
exp_u o (2^(l-(length as))) b `controlled` a
map_exp_u o as b l
exp_u :: BooleanFormulaOracle -> Integer -> BooleanFormulaRegister -> Circ ()
exp_u _ 0 _ = return ()
exp_u o n_steps b = do
(subroutine_u o) b
exp_u o (n_steps-1) b
u :: BooleanFormulaOracle -> BooleanFormulaRegister -> Circ ()
u o b = do
comment "U"
labelBFR b
(subroutine_oracle o) b
(subroutine_diffuse o) b
(subroutine_walk o) b
(subroutine_undo_oracle o) b
subroutine_u :: BooleanFormulaOracle -> BooleanFormulaRegister -> Circ ()
subroutine_u o = box "U" (u o)
oracle :: BooleanFormulaOracle -> BooleanFormulaRegister -> Circ ()
oracle o register = do
comment "ORACLE"
labelBFR register
let init = start_board o
let x_max = oracle_x_max o
let (is_leaf,is_paraleaf) = position_flags register
with_controls (is_leaf)
(
do
let leaf = work_leaf register
qnot_at leaf
)
with_controls (is_leaf .==. False .&&. is_paraleaf .==. True)
(
do
let paraleaf = work_paraleaf register
qnot_at paraleaf
let binary = work_binary register
qnot_at binary
let pos = position register
let hex_subroutine = case oracle_hex o of
Hex -> box "HEX" (hex_oracle init (oracle_s o) x_max)
Dummy -> hex_oracle_dummy
EmptyHex -> \x -> return x
hex_subroutine (pos,binary)
return ()
)
with_controls (is_leaf .==. False .&&. is_paraleaf .==. False)
(
do
let pos = position register
with_controls (controls is_paraleaf pos)
(
do
let pos'' = pos !! (length pos - 2)
let pos_m = last pos''
with_controls pos_m
(
do
let height = work_height register
qnot_at height
)
let pos' = last pos
let pos_1 = pos' !! (length pos' - 2)
with_controls (pos_m .==. False .&&. pos_1 .==. True)
(
do
let r = work_r register
qnot_at r
)
let pos_0 = last pos'
with_controls (pos_m .==. False .&&. pos_1 .==. False .&&. pos_0 .==. True)
(
do
let rp = work_rp register
qnot_at rp
let binary = work_binary register
qnot_at binary
)
with_controls (pos_m .==. False .&&. pos_1 .==. False .&&. pos_0 .==. False)
(
do
let rpp = work_rpp register
qnot_at rpp
)
)
)
subroutine_oracle :: BooleanFormulaOracle -> BooleanFormulaRegister -> Circ ()
subroutine_oracle o = box "Oracle" (oracle o)
controls :: Qubit -> [DirectionRegister] -> [ControlList]
controls is_paraleaf pos = (is_paraleaf .==. False) : ctrls pos
where ctrls [] = []
ctrls [p] = []
ctrls [p,q] = []
ctrls (p:ps) = (last p .==. False) : ctrls ps
diffuse :: BooleanFormulaRegister -> Circ ()
diffuse register = do
comment "DIFFUSE"
labelBFR register
let binary = work_binary register
let dir = direction register
with_controls binary
(
do
let dir_0 = last dir
hadamard_at dir_0
)
let leaf = work_leaf register
let rpp = work_rpp register
with_controls (binary .==. False .&&. leaf .==. False .&&. rpp .==. False)
(
do
mapUnary hadamard dir
)
return ()
subroutine_diffuse :: BooleanFormulaOracle -> BooleanFormulaRegister -> Circ ()
subroutine_diffuse o = box "Diffuse" diffuse
data Where = Width
| M
| M2
deriving Eq
walk :: BooleanFormulaRegister -> Circ ()
walk register = do
comment "WALK"
labelBFR register
let leaf = work_leaf register
let paraleaf = work_paraleaf register
let dir = direction register
let dir_0 = last dir
let (is_leaf,is_paraleaf) = position_flags register
let pos = position register
let pos_0 = last (last pos)
let pos_1 = last (init (last pos))
let height_1 = work_height register
let rpp = work_rpp register
let rp = work_rp register
let r = work_r register
let dir_all_1 = foldr1 (\x y -> And x y) (map A dir)
let boolean_statement_in = Or (A leaf) (And (A paraleaf) (Not (A dir_0)))
let boolean_statement_out = Or (A leaf) (And (A paraleaf) (A is_leaf))
if_then_elseQinv boolean_statement_in
(
do
qnot_at is_leaf
)
(
do
let boolean_statement_in = And (A paraleaf) (A dir_0)
let boolean_statement_out = And (A paraleaf) (Not (dir_all_1))
if_then_elseQinv boolean_statement_in
(
toParent Width register
)
(
do
let boolean_statement_in = Or (A rpp) (And (A rp) (A dir_0))
let boolean_statement_out = Or (A rpp) (And (A rp) (Not (A dir_0)))
if_then_elseQinv boolean_statement_in
(
do
qnot_at pos_0
qnot_at dir_0
)
(
do
let boolean_statement_in = Or (And (A rp) (Not (A dir_0))) (And (A r) dir_all_1)
let pos_m = last (last (init pos))
let boolean_statement_out = Or (And (A rp) dir_all_1) (And (A r) (And (Not dir_all_1) (Not (A pos_m))))
if_then_elseQinv boolean_statement_in
(
do
qnot_at pos_1
mapUnary qnot dir
return ()
)
(
do
let boolean_statement = A r
if_then_elseQ boolean_statement
(
do
qnot_at pos_1
toChild M register
)
(
do
let boolean_statement_in = And (A height_1) (dir_all_1)
let boolean_statement_out = And (A height_1) (Not dir_all_1)
if_then_elseQinv boolean_statement_in
(
do
toParent M register
qnot_at pos_1
)
(
do
let boolean_statement = A height_1
if_then_elseQ boolean_statement
(
do
toChild M2 register
)
(
do
let boolean_statement_in = dir_all_1
let boolean_statement_out = Not dir_all_1
if_then_elseQinv boolean_statement_in
(
do
toParent Width register
)
(
do
toChild Width register
) boolean_statement_out
)
) boolean_statement_out
)
) boolean_statement_out
) boolean_statement_out
) boolean_statement_out
) boolean_statement_out
return ()
subroutine_walk :: BooleanFormulaOracle -> BooleanFormulaRegister -> Circ ()
subroutine_walk o = box "Walk" walk
undo_oracle :: BooleanFormulaOracle -> BooleanFormulaRegister -> Circ ()
undo_oracle o register = do
comment "UNDO_ORACLE"
labelBFR register
let initHB = start_board o
let x_max = oracle_x_max o
let paraleaf = work_paraleaf register
let (is_leaf,is_paraleaf) = position_flags register
with_controls paraleaf
( do
let binary = work_binary register
let pos = position register
let dir = direction register
let hex_subroutine = case oracle_hex o of
Hex -> box "HEX" (hex_oracle initHB (oracle_s o) x_max)
Dummy -> hex_oracle_dummy
EmptyHex -> \x -> return x
hex_subroutine (pos,binary)
return ()
)
let leaf = work_leaf register
let dir = direction register
let dir_0 = last dir
let boolean_statement = And (Not (A is_leaf)) (And (A is_paraleaf) (Not (A dir_0)))
if_then_elseQ boolean_statement
(
do
qnot_at leaf
)
(
do
let binary = work_binary register
let pos = position register
let pos_w_2_m = last (head pos)
let dir_all_1 = foldr1 (\x y -> And x y) (map A dir)
let boolean_statement = Or (A is_leaf) (And (Not (A is_leaf)) (And (Not (A is_paraleaf)) (And (A pos_w_2_m) (Not (dir_all_1)))))
if_then_elseQ boolean_statement
(
do
qnot_at binary
qnot_at paraleaf
)
(
do
with_controls (init (controls is_paraleaf pos))
(
do
let height = work_height register
let r = work_r register
let rp = work_rp register
let pos_0 = last (last pos)
let pos_1 = last (init (last pos))
let pos_m = last (last (init pos))
let pos_2m = last (last (init (init pos)))
let boolean_statement = dir_all_1
if_then_elseQ boolean_statement
(
do
qnot_at height `controlled` pos_2m
qnot_at r `controlled` (pos_2m .==. False .&&. pos_m .==. True)
with_controls (pos_2m .==. False .&&. pos_m .==. False .&&. pos_1 .==. True)
(
do
qnot_at rp
qnot_at binary
)
)
(
with_controls (pos_2m .==. False .&&. pos_m .==. False)
(
do
let rpp = work_rpp register
qnot_at height `controlled` pos_1
qnot_at rpp `controlled` (pos_1 .==. False .&&. dir_0 .==. True)
qnot_at r `controlled` (pos_1 .==. False .&&. dir_0 .==. False .&&. pos_0 .==. True)
with_controls (pos_1 .==. False .&&. dir_0 .==. False .&&. pos_0 .==. False)
(
do
qnot_at rp
qnot_at binary
)
)
)
)
)
)
return ()
subroutine_undo_oracle :: BooleanFormulaOracle -> BooleanFormulaRegister -> Circ ()
subroutine_undo_oracle o = box "Undo Oracle" (undo_oracle o)
toParent :: Where -> BooleanFormulaRegister -> Circ ()
toParent M2 _ = error "TOPARENT should never be called with 2m+1 as width"
toParent w register = do
let pos = position register :: [[Qubit]]
let pos_firstM = last pos :: [Qubit]
let pos_secondM = last (init pos) :: [Qubit]
let pos_0 = last pos_firstM :: Qubit
let pos_m = last pos_secondM :: Qubit
let dir = direction register :: [Qubit]
let (_,is_paraleaf) = position_flags register :: (Qubit,Qubit)
mapUnary qnot dir
mapBinary copy_from_to (reverse pos_firstM) (reverse dir)
if (w == Width) then
( do
shift_right pos
copy_from_to is_paraleaf (last (head pos))
return ()
) else return ()
if (w == M) then
( do
copy_from_to pos_m pos_0
return ()
) else return ()
copy_from_to :: Qubit -> Qubit -> Circ (Qubit,Qubit)
copy_from_to from to = do
qnot_at to `controlled` from
qnot_at from `controlled` to
return (from,to)
toChild :: Where -> BooleanFormulaRegister -> Circ ()
toChild w register = do
let pos = position register :: [[Qubit]]
let pos_firstM = last pos :: [Qubit]
let pos_secondM = last (init pos) :: [Qubit]
let pos_thirdM = last (init (init pos)) :: [Qubit]
let pos_0 = last pos_firstM :: Qubit
let pos_m = last pos_secondM :: Qubit
let pos_2m = last pos_thirdM :: Qubit
let dir = direction register :: [Qubit]
let (_,is_paraleaf) = position_flags register :: (Qubit,Qubit)
if (w == Width) then
( do
copy_from_to (last (head pos)) is_paraleaf
shift_left pos
) else return ()
if (w == M2) then
( do
copy_from_to pos_m pos_2m
shift_left [pos_secondM,pos_firstM]
) else return ()
if (w == M) then
( do
copy_from_to pos_0 pos_m
return ()
) else return ()
mapBinary copy_from_to dir pos_firstM
mapUnary qnot dir
return ()
shift_left :: [DirectionRegister] -> Circ ()
shift_left [] = return ()
shift_left [d] = return ()
shift_left (d:d':ds) = do
mapBinary copy_from_to d' d
shift_left (d':ds)
shift_right :: [DirectionRegister] -> Circ ()
shift_right [] = return ()
shift_right [d] = return ()
shift_right (d:d':ds) = do
shift_right (d':ds)
mapBinary copy_from_to (reverse d) (reverse d')
return ()
main_circuit :: Format -> GateBase -> BooleanFormulaOracle -> IO ()
main_circuit f g oracle = print_simple f (decompose_generic g (qw_bf oracle))
main_u :: Format -> GateBase -> BooleanFormulaOracle -> IO ()
main_u f g o = print_generic f (decompose_generic g (u o)) (registerShape o)
main_walk :: Format -> GateBase -> BooleanFormulaOracle -> IO ()
main_walk f g o = print_generic f (decompose_generic g walk) (registerShape o)
main_diffuse :: Format -> GateBase -> BooleanFormulaOracle -> IO ()
main_diffuse f g o = print_generic f (decompose_generic g diffuse) (registerShape o)
main_oracle :: Format -> GateBase -> BooleanFormulaOracle -> IO ()
main_oracle f g o = print_generic f (decompose_generic g (oracle o)) (registerShape o)
main_undo_oracle :: Format -> GateBase -> BooleanFormulaOracle -> IO ()
main_undo_oracle f g o = print_generic f (decompose_generic g (undo_oracle o)) (registerShape o)
main_hex :: Format -> GateBase -> BooleanFormulaOracle -> IO ()
main_hex f g o = print_generic f (decompose_generic g (hex_oracle init s x_max)) (pos,binary)
where
init = start_board o
s = oracle_s o
x_max = oracle_x_max o
reg = registerShape o
pos = position reg
binary = work_binary reg
main_checkwin_red :: Format -> GateBase -> BooleanFormulaOracle -> IO ()
main_checkwin_red f g o = print_generic f (decompose_generic g (checkwin_red_circuit x_max)) (qshape redboard,qubit)
where
(redboard,_) = start_board o
x_max = oracle_x_max o
main_bf :: BooleanFormulaOracle -> IO Bool
main_bf oracle = do
output <- run_generic_io (undefined :: Double) (qw_bf oracle)
let result = if (or output) then True
else False
return result
whoWins :: BooleanFormulaOracle -> IO ()
whoWins oracle = do
result <- main_bf oracle
if result then putStrLn "Red Wins"
else putStrLn "Blue Wins"
main_whoWins :: BooleanFormulaOracle -> IO ()
main_whoWins o = whoWins o