{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LINE 1 "Quipper/Algorithms/BF/Hex.hs" #-}
module Quipper.Algorithms.BF.Hex where
import Quipper
import Quipper.Internal.CircLifting
import Quipper.Libraries.Qram
import Quipper.Libraries.Arith hiding (template_symb_plus_)
import Prelude hiding (lookup)
qtrace :: [Bool] -> [Bool]
qtrace bs = bs
template_qtrace :: Circ ([Qubit] -> Circ [Qubit])
template_qtrace = return $ \qs -> do
named_gate_at "trace" qs
return qs
template_show :: Show a => Circ (a -> Circ String)
template_show = return $ \a -> return $ show a
template_head :: Circ ([a] -> Circ a)
template_head = return $ \q -> return (head q)
template_tail :: Circ ([a] -> Circ [a])
template_tail = return $ \q -> return (tail q)
template_length :: Circ ([a] -> Circ Int)
template_length = return $ \as -> return $ length as
template_take :: Circ (Int -> Circ ([Qubit] -> Circ [Qubit]))
template_take = return $ \n -> return $ \qs -> return (take n qs)
template_drop :: Circ (Int -> Circ ([Qubit] -> Circ [Qubit]))
template_drop = return $ \n -> return $ \qs -> return (drop n qs)
template_replicate :: Circ (Int -> Circ (BoolParam -> Circ [BoolParam]))
template_replicate = return $ \n -> return $ \bp -> return (replicate n bp)
template_map :: Circ ((a -> Circ a) -> Circ ([a] -> Circ [a]))
template_map = return $ \func -> return $ \qs -> mapM func qs
template_integer :: Int -> Circ Int
template_integer x = return x
template_symb_minus_ :: Circ (Int -> Circ (Int -> Circ Int))
template_symb_minus_ = return $ \x -> return $ \y -> return (x - y)
template_symb_plus_ :: Circ (Int -> Circ (Int -> Circ Int))
template_symb_plus_ = return $ \x -> return $ \y -> return (x + y)
template_symb_oangle_ :: Circ (Int -> Circ (Int -> Circ Bool))
template_symb_oangle_ = return $ \x -> return $ \y -> return (x < y)
template_symb_oangle_symb_equal_ :: Circ (Int -> Circ (Int -> Circ Bool))
template_symb_oangle_symb_equal_ = return $ \x -> return $ \y -> return (x <= y)
template_div :: Circ (Int -> Circ (Int -> Circ Int))
template_div = return $ \x -> return $ \y -> return (x `div` y)
cand :: Bool -> Bool -> Bool
cand = (&&)
template_cand :: Circ (Bool -> Circ (Bool -> Circ Bool))
template_cand = return $ \x -> return $ \y -> return (x && y)
template_symb_cangle_ :: Circ (Int -> Circ (Int -> Circ Bool))
template_symb_cangle_ = return $ \x -> return $ \y -> return (x > y)
template_symb_exclamation_symb_exclamation_ :: Circ ([a] -> Circ (Int -> Circ a))
template_symb_exclamation_symb_exclamation_ = return $ \as -> return $ \i -> return (as !! i)
template_mod :: Circ (Int -> Circ (Int -> Circ Int))
template_mod = return $ \x -> return $ \y -> return (x `mod` y)
template_zip :: Circ ([Qubit] -> Circ ([Qubit] -> Circ [(Qubit,Qubit)]))
template_zip = return $ \as -> return $ \bs -> return $ zip as bs
template_unzip :: Circ ([(Qubit,Qubit)] -> Circ ([Qubit],[Qubit]))
template_unzip = return $ \abs -> return $ unzip abs
template_or :: Circ ([Qubit] -> Circ Qubit)
template_or = return $ \bs -> do
q <- qinit True
qnot q `controlled` [ b .==. 0 | b <- bs ]
type HexBoardParam = ([BoolParam],[BoolParam])
newBools :: [BoolParam] -> [Bool]
newBools = map newBool
template_newBools :: Circ ([BoolParam] -> Circ [Qubit])
template_newBools = return $ \bps -> do
let bs = map newBool bps
mapM qinit bs
bools2int :: [Bool] -> Int
bools2int bs = bools2int' (reverse bs)
bools2int' :: [Bool] -> Int
bools2int' [] = 0
bools2int' (x:xs) = 2*(bools2int' xs) + (if x then 1 else 0)
int2bools :: Int -> Int -> [Bool]
int2bools n x = reverse (int2bools' n x)
int2bools' :: Int -> Int -> [Bool]
int2bools' n x = take n (int2bools'' x ++ repeat False)
int2bools'' :: Int -> [Bool]
int2bools'' 0 = [False]
int2bools'' 1 = [True]
int2bools'' x = (odd x):(int2bools'' (x `div` 2))
lookup :: [Bool] -> [Bool] -> Bool
lookup board address = board !! (bools2int address)
template_lookup :: Circ ([Qubit] -> Circ ([Qubit] -> Circ Qubit))
template_lookup = return $ \board -> return $ \address -> do
addressed_perform board address $ \q -> do
anc <- qinit False
qnot_at anc `controlled` q
return anc
update :: [Bool] -> [Bool] -> [Bool]
update board address = (take n board) ++ b:(drop (n+1) board)
where n = bools2int address
b = not (board !! n)
template_update :: Circ ([Qubit] -> Circ ([Qubit] -> Circ [Qubit]))
template_update = return $ \board -> return $ \address -> do
addressed_perform board address $ \q -> do
qnot_at q
return board
test_update :: [Qubit] -> [Qubit] -> Circ [Qubit]
test_update board address = do
qcqcq <- template_update
qqcq <- qcqcq board
qqcq address
addressed_perform :: QData qa =>
[qa]
-> [Qubit]
-> (qa -> Circ b)
-> Circ b
addressed_perform qs idx f = do
with_computed (indexed_access qs i) $ \x -> do
f x
where i = qdint_of_qulist_bh idx
update_pos :: Int -> [Bool] -> Bool -> [Bool]
update_pos n bs b = (take n bs) ++ b:(drop (n+1) bs)
{-# LINE 209 "Quipper/Algorithms/BF/Hex.hs" #-}
$( decToCircMonad [d| update_pos :: Int -> [Bool] -> Bool -> [Bool]
update_pos n bs b = (take n bs) ++ b:(drop (n+1) bs)
|] )
{-# LINE 210 "Quipper/Algorithms/BF/Hex.hs" #-}
testpos :: Int -> [Bool] -> [Bool] -> [Bool] -> Int -> [Bool]
testpos pos maskmap bitmap newmap xy_max = case (0 <= pos) `cand` (pos < xy_max) of
True -> if not (maskmap !! pos) && not (bitmap !! pos) && not (newmap !! pos)
then update_pos pos newmap True
else newmap
False -> newmap
{-# LINE 232 "Quipper/Algorithms/BF/Hex.hs" #-}
$( decToCircMonad [d| testpos :: Int -> [Bool] -> [Bool] -> [Bool] -> Int -> [Bool]
testpos pos maskmap bitmap newmap xy_max = case (0 <= pos) `cand` (pos < xy_max) of
True -> if not (maskmap !! pos) && not (bitmap !! pos) && not (newmap !! pos)
then update_pos pos newmap True
else newmap
False -> newmap
|] )
{-# LINE 233 "Quipper/Algorithms/BF/Hex.hs" #-}
test_positions :: Int -> Int -> Int -> [Bool] -> [Bool] -> [Bool] -> ([Bool],[Bool])
test_positions ii x_max xy_max bitmap newmap maskmap =
let bitmap' = update_pos ii bitmap True in
let newmap' = testpos (ii + x_max) maskmap bitmap' newmap xy_max in
let newmap'' = testpos (ii - x_max) maskmap bitmap' newmap' xy_max in
let newmap''' = case (ii `mod` x_max > 0) of
True -> testpos (ii - 1) maskmap bitmap' newmap'' xy_max
False -> newmap''
in
let newmap'''' = case (ii `mod` x_max > 0) of
True -> testpos (ii + x_max - 1) maskmap bitmap' newmap''' xy_max
False -> newmap'''
in
let newmap''''' = case (ii `mod` x_max < x_max - 1) of
True -> testpos (ii + 1) maskmap bitmap' newmap'''' xy_max
False -> newmap''''
in
let newmap'''''' = case (ii `mod` x_max < x_max - 1) of
True -> testpos (ii - x_max + 1) maskmap bitmap' newmap''''' xy_max
False -> newmap'''''
in
let newmap''''''' = update_pos ii newmap'''''' False in
(newmap''''''',bitmap')
{-# LINE 261 "Quipper/Algorithms/BF/Hex.hs" #-}
$( decToCircMonad [d| test_positions :: Int -> Int -> Int -> [Bool] -> [Bool] -> [Bool] -> ([Bool],[Bool])
test_positions ii x_max xy_max bitmap newmap maskmap =
let bitmap' = update_pos ii bitmap True in
let newmap' = testpos (ii + x_max) maskmap bitmap' newmap xy_max in
let newmap'' = testpos (ii - x_max) maskmap bitmap' newmap' xy_max in
let newmap''' = case (ii `mod` x_max > 0) of
True -> testpos (ii - 1) maskmap bitmap' newmap'' xy_max
False -> newmap''
in
let newmap'''' = case (ii `mod` x_max > 0) of
True -> testpos (ii + x_max - 1) maskmap bitmap' newmap''' xy_max
False -> newmap'''
in
let newmap''''' = case (ii `mod` x_max < x_max - 1) of
True -> testpos (ii + 1) maskmap bitmap' newmap'''' xy_max
False -> newmap''''
in
let newmap'''''' = case (ii `mod` x_max < x_max - 1) of
True -> testpos (ii - x_max + 1) maskmap bitmap' newmap''''' xy_max
False -> newmap'''''
in
let newmap''''''' = update_pos ii newmap'''''' False in
(newmap''''''',bitmap')
|] )
{-# LINE 262 "Quipper/Algorithms/BF/Hex.hs" #-}
while_for :: Int -> Int -> Int -> [Bool] -> [Bool] -> [Bool] -> ([Bool],[Bool])
while_for counter xy_max x_max bitmap newmap maskmap = case counter of
0 -> let bitmap' = qtrace bitmap in
(bitmap',newmap)
n -> let ii = xy_max - n in
let (newmap',bitmap') = if newmap !! ii
then test_positions ii x_max xy_max bitmap newmap maskmap
else (newmap,bitmap) in
while_for (n-1) xy_max x_max bitmap' newmap' maskmap
{-# LINE 274 "Quipper/Algorithms/BF/Hex.hs" #-}
$( decToCircMonad [d| while_for :: Int -> Int -> Int -> [Bool] -> [Bool] -> [Bool] -> ([Bool],[Bool])
while_for counter xy_max x_max bitmap newmap maskmap = case counter of
0 -> let bitmap' = qtrace bitmap in
(bitmap',newmap)
n -> let ii = xy_max - n in
let (newmap',bitmap') = if newmap !! ii
then test_positions ii x_max xy_max bitmap newmap maskmap
else (newmap,bitmap) in
while_for (n-1) xy_max x_max bitmap' newmap' maskmap
|] )
{-# LINE 275 "Quipper/Algorithms/BF/Hex.hs" #-}
while :: Int -> Int -> [Bool] -> [Bool] -> [Bool] -> [Bool]
while counter x_max bitmap newmap maskmap = case counter of
0 -> bitmap
n -> let counter' = length bitmap in
let (bitmap',newmap') = while_for counter' counter' x_max bitmap newmap maskmap in
while (n-1) x_max bitmap' newmap' maskmap
{-# LINE 288 "Quipper/Algorithms/BF/Hex.hs" #-}
$( decToCircMonad [d| while :: Int -> Int -> [Bool] -> [Bool] -> [Bool] -> [Bool]
while counter x_max bitmap newmap maskmap = case counter of
0 -> bitmap
n -> let counter' = length bitmap in
let (bitmap',newmap') = while_for counter' counter' x_max bitmap newmap maskmap in
while (n-1) x_max bitmap' newmap' maskmap
|] )
{-# LINE 289 "Quipper/Algorithms/BF/Hex.hs" #-}
swapBool :: (Bool,Bool) -> (Bool,Bool)
swapBool (a,b) = (b,a)
template_swapBool :: Circ ((Qubit,Qubit) -> Circ (Qubit,Qubit))
template_swapBool = return $ \(a,b) -> do
swap a b
return (a,b)
flood_fill :: Int -> [Bool] -> [Bool] -> [Bool]
flood_fill x_max bitmap maskmap =
let newmap = newBools (replicate (length bitmap) PFalse) in
let (bitmap',newmap') = unzip (map (\(a,b) -> if a then swapBool (a,b) else (a,b)) (zip bitmap newmap)) in
let newmap'' = qtrace newmap' in
let counter = ((length bitmap) `div` 4) + 1 in
while counter x_max bitmap' newmap'' maskmap
{-# LINE 312 "Quipper/Algorithms/BF/Hex.hs" #-}
$( decToCircMonad [d| flood_fill :: Int -> [Bool] -> [Bool] -> [Bool]
flood_fill x_max bitmap maskmap =
let newmap = newBools (replicate (length bitmap) PFalse) in
let (bitmap',newmap') = unzip (map (\(a,b) -> if a then swapBool (a,b) else (a,b)) (zip bitmap newmap)) in
let newmap'' = qtrace newmap' in
let counter = ((length bitmap) `div` 4) + 1 in
while counter x_max bitmap' newmap'' maskmap
|] )
{-# LINE 313 "Quipper/Algorithms/BF/Hex.hs" #-}
checkwin_red' :: [Bool] -> Bool
checkwin_red' bs = not (or bs)
{-# LINE 319 "Quipper/Algorithms/BF/Hex.hs" #-}
$( decToCircMonad [d| checkwin_red' :: [Bool] -> Bool
checkwin_red' bs = not (or bs)
|] )
{-# LINE 320 "Quipper/Algorithms/BF/Hex.hs" #-}
checkwin_red :: Int -> [Bool] -> Bool
checkwin_red x_max redboard =
let begin_blueboard = map not (take x_max redboard) in
let n = length redboard - x_max in
let tail_blueboard = newBools (replicate n PFalse) in
let blueboard = begin_blueboard ++ tail_blueboard in
let blueboard' = flood_fill x_max blueboard redboard in
checkwin_red' (drop n blueboard')
{-# LINE 332 "Quipper/Algorithms/BF/Hex.hs" #-}
$( decToCircMonad [d| checkwin_red :: Int -> [Bool] -> Bool
checkwin_red x_max redboard =
let begin_blueboard = map not (take x_max redboard) in
let n = length redboard - x_max in
let tail_blueboard = newBools (replicate n PFalse) in
let blueboard = begin_blueboard ++ tail_blueboard in
let blueboard' = flood_fill x_max blueboard redboard in
checkwin_red' (drop n blueboard')
|] )
{-# LINE 333 "Quipper/Algorithms/BF/Hex.hs" #-}
checkwin_red_c :: Int -> [Qubit] -> Circ Qubit
checkwin_red_c i qs = do
icqscq <- template_checkwin_red
cqscq <- icqscq i
cqscq qs
movesT :: Int -> [[Bool]] -> [Bool] -> [Bool] -> BoolParam -> Bool
movesT x_max pos redboard blueboard player =
case pos of
[] -> checkwin_red x_max redboard
(address:pos') ->
if lookup redboard address
then (newBool player)
else
( if lookup blueboard address
then (newBool player)
else
( case player of
PFalse -> movesT x_max pos' (update redboard address) blueboard PTrue
PTrue -> movesT x_max pos' redboard (update blueboard address) PFalse
)
)
{-# LINE 369 "Quipper/Algorithms/BF/Hex.hs" #-}
$( decToCircMonad [d| movesT :: Int -> [[Bool]] -> [Bool] -> [Bool] -> BoolParam -> Bool
movesT x_max pos redboard blueboard player =
case pos of
[] -> checkwin_red x_max redboard
(address:pos') ->
if lookup redboard address
then (newBool player)
else
( if lookup blueboard address
then (newBool player)
else
( case player of
PFalse -> movesT x_max pos' (update redboard address) blueboard PTrue
PTrue -> movesT x_max pos' redboard (update blueboard address) PFalse
)
)
|] )
{-# LINE 370 "Quipper/Algorithms/BF/Hex.hs" #-}
hexT :: HexBoardParam -> BoolParam -> Int -> [[Bool]] -> Bool
hexT (init_r,init_b) next_player x_max pos =
let redboard = newBools init_r in
let blueboard = newBools init_b in
let result = movesT x_max pos redboard blueboard next_player in
result
{-# LINE 382 "Quipper/Algorithms/BF/Hex.hs" #-}
$( decToCircMonad [d| hexT :: HexBoardParam -> BoolParam -> Int -> [[Bool]] -> Bool
hexT (init_r,init_b) next_player x_max pos =
let redboard = newBools init_r in
let blueboard = newBools init_b in
let result = movesT x_max pos redboard blueboard next_player in
result
|] )
{-# LINE 383 "Quipper/Algorithms/BF/Hex.hs" #-}
newBoolParam :: Bool -> BoolParam
newBoolParam x = if x then PTrue else PFalse
newBoolParams :: [Bool] -> [BoolParam]
newBoolParams = map newBoolParam
hex_oracle_c :: ([Bool],[Bool]) -> Int -> Int -> [[Qubit]] -> Circ Qubit
hex_oracle_c (init_r,init_b) s x_max pos = do
let params = (newBoolParams init_r,newBoolParams init_b)
let next_player = newBoolParam (even s)
template_hexT_bp <- template_hexT
template_hexT_int <- template_hexT_bp params
template_hexT_int' <- template_hexT_int next_player
template_hexT_qs <- template_hexT_int' x_max
template_hexT_qs pos
hex_oracle :: ([Bool],[Bool]) -> Int -> Int -> ([[Qubit]],Qubit) -> Circ ([[Qubit]],Qubit)
hex_oracle init s x_max pb = do
comment "HEX"
label pb ("pos","binary")
(classical_to_quantum . classical_to_reversible) (hex_oracle_c init s x_max) pb
hex_oracle_dummy :: ([[Qubit]],Qubit) -> Circ ([[Qubit]],Qubit)
hex_oracle_dummy qs = named_gate "HEX" qs
checkwin_red_circuit :: Int -> ([Qubit],Qubit) -> Circ ([Qubit],Qubit)
checkwin_red_circuit x_max = (classical_to_quantum . classical_to_reversible) (checkwin_red_c x_max)