{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LINE 1 "Quipper/Algorithms/TF/Main.hs" #-}
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ < 710
{-# OPTIONS -fcontext-stack=50 #-}
#else
{-# OPTIONS -freduction-depth=50 #-}
#endif
module Quipper.Algorithms.TF.Main where
import Quipper
import Quipper.Libraries.Arith
import Quipper.Libraries.Decompose
import Quipper.Algorithms.TF.Definitions
import Quipper.Algorithms.TF.Oracle
import Quipper.Algorithms.TF.QWTFP
import Quipper.Algorithms.TF.Simulate
import Quipper.Algorithms.TF.Alternatives
import Quipper.Utils.CommandLine
import System.Console.GetOpt
import System.Environment
import System.Exit
import System.IO
import Control.Monad
import Data.List
import Data.Char
import qualified Data.IntMap as IntMap
data WhatToShow =
Circuit
| Oracle
| Sub
| Arith
| OTest
deriving Show
data OracleSelect =
Orthodox
| Blackbox
deriving Show
data QRamSelect =
Standard_QRam
| Alt_QRam
deriving Show
data Subroutine =
A2
| A3
| A4
| A5
| A6
| A7
| A8
| A9
| A10
| A11
| A12
| A13
| A14
| A15
| A16
| A17
| A18
| A19
| A20
| O2
| O3
| O4
| O5
| O6
| O7
| O8
deriving Show
data Options = Options {
what :: WhatToShow,
s :: Subroutine,
format :: Format,
gatebase :: GateBase,
oracle :: OracleSelect,
qram :: QRamSelect,
l :: Int,
n :: Int,
r :: Int
} deriving Show
defaultOptions :: Options
defaultOptions = Options
{ what = Circuit,
s = O7,
format = Preview,
gatebase = Logical,
oracle = Blackbox,
qram = Standard_QRam,
l = 4,
n = 3,
r = 2
}
options :: [OptDescr (Options -> IO Options)]
options =
[
Option ['h'] ["help"] (NoArg help) "print usage info and exit",
Option ['f'] ["format"] (ReqArg format "<format>") "output format for circuits (default: preview)",
Option ['g'] ["gatebase"] (ReqArg gatebase "<gatebase>") "type of gates to decompose into (default: logical)",
Option ['l'] ["l"] (ReqArg lll "<l>") "parameter l (default: 4)",
Option ['n'] ["n"] (ReqArg nnn "<n>") "parameter n (default: 3)",
Option ['r'] ["r"] (ReqArg rrr "<r>") "parameter r (default: 2)",
Option ['C'] ["QWTFP"] (NoArg (what Circuit)) "output the whole circuit (default)",
Option ['O'] ["oracle"] (NoArg (what Oracle)) "output only the oracle",
Option ['s'] ["subroutine"] (ReqArg sub "<subroutine>") "output the chosen subroutine (default: adder)",
Option ['Q'] [] (NoArg (qram Alt_QRam)) "use alternative qRAM implementation",
Option ['o'] [] (ReqArg oracle "<oracle>") "select oracle to use (default: blackbox)",
Option ['A'] ["arith"] (NoArg (what Arith)) "test/simulate the arithmetic routines",
Option ['T'] ["oracletest"] (NoArg (what OTest)) "test/simulate the oracle"
]
where
what :: WhatToShow -> Options -> IO Options
what w o = return o { what = w }
sub :: String -> Options -> IO Options
sub str o = do
case match_enum subroutine_enum str of
[(_, f)] -> return o { what = Sub, s = f }
[] -> optfail ("Unknown subroutine -- " ++ str ++ "\n")
_ -> optfail ("Ambiguous subroutine -- " ++ str ++ "\n")
qram :: QRamSelect -> Options -> IO Options
qram q o = return o { qram = q }
lll :: String -> Options -> IO Options
lll string o =
case parse_int string of
Just l | l >= 1 -> return o { l = l }
_ -> optfail ("Invalid value for parameter l -- " ++ string ++ "\n")
nnn :: String -> Options -> IO Options
nnn string o =
case parse_int string of
Just n | n >= 1 -> return o { n = n }
_ -> optfail ("Invalid value for parameter n -- " ++ string ++ "\n")
rrr :: String -> Options -> IO Options
rrr string o =
case parse_int string of
Just r | r >= 1 -> return o { r = r }
_ -> optfail ("Invalid value for parameter r -- " ++ string ++ "\n")
format :: String -> Options -> IO Options
format str o = do
case match_enum format_enum str of
[(_, f)] -> return o { format = f }
[] -> optfail ("Unknown format -- " ++ str ++ "\n")
_ -> optfail ("Ambiguous format -- " ++ str ++ "\n")
gatebase :: String -> Options -> IO Options
gatebase str o = do
case match_enum gatebase_enum str of
[(_, f)] -> return o { gatebase = f }
[] -> optfail ("Unknown gate base -- " ++ str ++ "\n")
_ -> optfail ("Ambiguous gate base -- " ++ str ++ "\n")
oracle :: String -> Options -> IO Options
oracle str o = do
case match_enum oracle_enum str of
[(_, f)] -> return o { oracle = f }
[] -> optfail ("Unknown oracle -- " ++ str ++ "\n")
_ -> optfail ("Ambiguous oracle -- " ++ str ++ "\n")
help :: Options -> IO Options
help o = do
usage
exitSuccess
oracle_enum :: [(String, OracleSelect)]
oracle_enum = [
("orthodox", Orthodox),
("blackbox", Blackbox)
]
subroutine_enum :: [(String, Subroutine)]
subroutine_enum = [
("zero", A2),
("initialize", A3),
("hadamard", A4),
("setup", A5),
("qwsh", A6),
("diffuse", A7),
("fetcht", A8),
("storet", A9),
("fetchstoret", A10),
("fetche", A11),
("fetchstoree", A12),
("update", A13),
("swap", A14),
("a15", A15),
("a16", A16),
("a17", A17),
("a18", A18),
("gcqwalk", A19),
("gcqwstep", A20),
("convertnode", O2),
("testequal", O3),
("pow17", O4),
("mod3", O5),
("sub", O6),
("add", O7),
("mult", O8)
]
dopts :: [String] -> IO Options
dopts argv =
case getOpt Permute options argv of
(o, [], []) -> (foldM (flip id) defaultOptions o)
(_, _, []) -> optfail "Too many non-option arguments\n"
(_, _, errs) -> optfail (concat errs)
usage :: IO ()
usage = do
putStr (usageInfo header options)
putStr (show_enum "format" format_enum)
putStr (show_enum "gatebase" gatebase_enum)
putStr (show_enum "oracle" oracle_enum)
putStr (show_enum "subroutine" subroutine_enum)
where header = "Usage: tf [OPTION...]"
main :: IO()
main = do
argv <- getArgs
options <- dopts argv
let spec = spec_of_options options
let p = ceiling (logBase 2 (fromIntegral (2^9 `choose` 3)))
case options of
Options { oracle = oracle, what = what, format = format, gatebase = gatebase, n = n, r = r, l = l, s = s} ->
case what of
Circuit -> print_generic format $ decompose_generic gatebase $ a1_QWTFP spec
Oracle -> print_generic format (decompose_generic gatebase $ proj3 spec) node_shape node_shape qubit
Arith -> arithmetic_tests l
OTest -> oracle_tests n l
Sub -> case s of
A2 -> print_generic format (decompose_generic gatebase $ a2_ZERO (replicate n False))
A3 -> print_generic format (decompose_generic gatebase $ a3_INITIALIZE (replicate n False))
A4 -> print_generic format (decompose_generic gatebase $ a4_HADAMARD) (replicate n qubit)
A5 -> print_generic format (decompose_generic gatebase $ a5_SETUP spec) tt_shape
A6 -> print_generic format (decompose_generic gatebase $ a6_QWSH spec)
tt_shape (qdint_shape r) node_shape ee_shape
A7 -> print_generic format (decompose_generic gatebase $ a7_DIFFUSE) node_shape
A8 -> print_generic format (decompose_generic gatebase $ a8_FetchT)
(qdint_shape r) tt_shape node_shape
A9-> print_generic format (decompose_generic gatebase $ a9_StoreT)
(qdint_shape r) tt_shape node_shape
A10-> print_generic format (decompose_generic gatebase $ a10_FetchStoreT)
(qdint_shape r) tt_shape node_shape
A11-> print_generic format (decompose_generic gatebase $ a11_FetchE)
(qdint_shape r) ee_shape eed_shape
A12-> print_generic format (decompose_generic gatebase $ a12_FetchStoreE)
(qdint_shape r) ee_shape eed_shape
A13-> print_generic format (decompose_generic gatebase $ a13_UPDATE spec)
tt_shape node_shape eed_shape
A14-> print_generic format (decompose_generic gatebase $ a14_SWAP)
node_shape node_shape
A15 -> print_generic format (decompose_generic gatebase $ a15_TestTriangleEdges spec)
tt_shape ee_shape
A16 -> print_generic format (decompose_generic gatebase $ a16_TriangleTestT)
ee_shape
A17 -> print_generic format (decompose_generic gatebase $ a17_TriangleTestTw spec)
tt_shape ee_shape node_shape
A18 -> print_generic format (decompose_generic gatebase $ a18_TriangleEdgeSearch spec)
tt_shape ee_shape qubit
A19 -> print_generic format (decompose_generic gatebase $ a19_GCQWalk spec)
tt_shape ee_shape node_shape qubit
A20 -> print_generic format (decompose_generic gatebase $ a20_GCQWStep spec)
tt_shape ee_shape node_shape gcqw_shape
O2 -> print_generic format (decompose_generic gatebase $ \u -> o2_ConvertNode l u (2^(n-1))) node_shape
O3 -> print_generic format (decompose_generic gatebase $ o3_TestEqual) (qinttf_shape l) (qinttf_shape l)
O4 -> print_generic format (decompose_generic gatebase $ o4_POW17) (qinttf_shape l)
O5 -> print_generic format (decompose_generic gatebase $ o5_MOD3) (qinttf_shape l)
O6 -> print_generic format (decompose_generic gatebase $ \u -> o6_SUB u (2^(n-1))) (qinttf_shape l)
O7 -> print_generic format (decompose_generic gatebase $ o7_ADD) (qinttf_shape l) (qinttf_shape l)
O8 -> print_generic format (decompose_generic gatebase $ o8_MUL) (qinttf_shape l) (qinttf_shape l)
where
rbar = max ((2 * r) `div` 3) 1
proj3 (a,b,c,d) = c
node_shape = (replicate n qubit)
tt_shape = (intMap_replicate (2^r) node_shape)
ee_shape = (IntMap.fromList [(j,intMap_replicate j qubit) | j <- [0..((2^r)-1)]])
eed_shape = (intMap_replicate (2^r) qubit)
gcqw_shape = (intMap_replicate (2^rbar) (qdint_shape r),
(qdint_shape rbar),
(qdint_shape r),
(intMap_replicate (2^rbar) qubit),
(qdint_shape (2*rbar - 1)),
qubit)
spec_of_options :: Options -> QWTFP_spec
spec_of_options Options { oracle = Orthodox, n = n, r = r, l = l, qram = qram} =
(n,r,
(\u v edge -> do (u,v,edge) <- o1_ORACLE l u v edge; return edge),
qram_select qram)
spec_of_options Options { oracle = Blackbox, n = n, r = r, qram = qram} =
(n,r,placeholder_oracle,qram_select qram)
qram_select :: QRamSelect -> Qram
qram_select Standard_QRam = standard_qram
qram_select Alt_QRam = alt_qram