{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LINE 1 "Quipper/Algorithms/CL/Main.hs" #-}
module Quipper.Algorithms.CL.Main where
import Quipper
import Quipper.Utils.CommandLine
import Quipper.Libraries.Arith
import Quipper.Libraries.FPReal
import Quipper.Libraries.Decompose
import Quipper.Libraries.Unboxing
import Quipper.Algorithms.CL.Auxiliary
import Quipper.Algorithms.CL.Types
import Quipper.Algorithms.CL.RegulatorClassical
import Quipper.Algorithms.CL.RegulatorQuantum
import Quipper.Algorithms.CL.CL
import Quipper.Algorithms.CL.Test
import System.Console.GetOpt
import System.Environment
import System.Exit
import System.Random
import Control.Monad
import Data.Bits
import Data.Maybe
import Data.List
import Data.Char
data WhatToShow =
Stage1
| Stage4
| Sub
| Regulator
| FundamentalUnit
| PellSolution
deriving Show
data Subroutine =
Rho
| RhoInv
| Normalize
| DotProd
| StarProd
| FN
deriving (Show, Enum, Bounded)
subroutine_enum :: [(String, Subroutine)]
subroutine_enum = map (\x -> (map toLower (show x),x)) [minBound..maxBound]
data Options = Options {
what :: WhatToShow,
format :: Format,
gatebase :: GateBase,
sub :: Subroutine,
cl_delta :: CLIntP,
cl_i :: Int,
cl_r :: CLReal,
cl_q :: CLIntP,
cl_k :: CLIntP,
cl_n :: CLIntP,
cl_m :: CLIntP,
cl_generators :: [IdealRed],
cl_seed :: Int
} deriving (Show)
default_options :: Options
default_options = Options {
what = Stage1,
format = ASCII,
gatebase = Logical,
sub = FN,
cl_delta = 28,
cl_i = 1,
cl_r = 12.345,
cl_q = 4,
cl_k = 3,
cl_n = 3,
cl_m = 5,
cl_generators = [],
cl_seed = 1
}
show_default :: (Show a) => (Options -> a) -> String
show_default func = show (func default_options)
options :: [OptDescr (Options -> IO Options)]
options = [
Option ['h'] ["help"] (NoArg help) $ "print usage info and exit",
Option ['f'] ["format"] (ReqArg read_format "<format>") $ "output format for circuits (default: " ++ show_default format ++ ")",
Option ['g'] ["gatebase"] (ReqArg read_gatebase "<gatebase>") $ "gates to decompose into (default: " ++ show_default gatebase ++ ")",
Option ['1'] [] (NoArg (what Stage1)) $ "output the circuit for stage 1 of the algorithm (default)",
Option ['4'] [] (NoArg (what Stage4)) $ "output the circuit for stage 4 of the algorithm",
Option ['S'] ["sub"] (ReqArg read_subroutine "<subroutine>") $ "output the circuit for a specific subroutine",
Option ['R'] ["regulator"] (NoArg (what Regulator)) $ "classically, find the regulator, given Δ",
Option ['F'] [] (NoArg (what FundamentalUnit)) $ "classically, find the fundamental unit, given Δ",
Option ['P'] [] (NoArg (what PellSolution)) $ "classically, find the fundamental solution of Pell’s equation, given Δ",
Option ['d'] ["delta"] (ReqArg read_delta "<N>") $ "discriminant Δ (a.k.a. D) (default: " ++ show_default cl_delta ++ ")",
Option ['s'] ["ss"] (ReqArg read_s "<N>") $ "estimated bound on period S, for stage 1 (default: " ++ show (2^(cl_i default_options)) ++ ")",
Option ['i'] [] (ReqArg read_i "<N>") $ "estimated bound on log_2 S, for stage 1 (default: " ++ show (cl_i default_options) ++ ")",
Option ['r'] ["rr"] (ReqArg read_r "<N>") $ "approximate regulator R, for stage 4 (default: " ++ show_default cl_r ++ ")",
Option ['q'] [] (ReqArg read_q "<N>") $ "The parameter q, for stage 4 (default: " ++ show_default cl_q ++ ")",
Option ['k'] [] (ReqArg read_k "<N>") $ "The parameter k, for stage 4 (default: " ++ show_default cl_k ++ ")",
Option ['n'] [] (ReqArg read_n "<N>") $ "The parameter n, for stage 4 (default: " ++ show_default cl_n ++ ")",
Option ['m'] [] (ReqArg read_m "<N>") $ "The parameter m, for stage 4 (default: " ++ show_default cl_m ++ ")",
Option [] ["seed"] (ReqArg read_seed "<N>") $ "Random seed (0 for seed from time)(default: " ++ show_default cl_seed ++ ")"
]
where
what :: WhatToShow -> Options -> IO Options
what w o = return o { what = w }
read_format :: String -> Options -> IO Options
read_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")
read_gatebase :: String -> Options -> IO Options
read_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")
read_subroutine :: String -> Options -> IO Options
read_subroutine str o = do
case match_enum subroutine_enum str of
[(_, f)] -> return o { sub = f, what = Sub }
[] -> optfail ("Unknown subroutine -- " ++ str ++ "\n")
_ -> optfail ("Ambiguous subroutine -- " ++ str ++ "\n")
read_delta = read_arg parse_int (>0) (\n o -> o { cl_delta = fromIntegral n }) "Invalid Δ"
read_seed = read_arg parse_int (>=0) (\n o -> o { cl_seed = fromIntegral n }) "Invalid seed"
read_i = read_arg parse_int (>=0) (\n o -> o { cl_i = fromIntegral n }) "Invalid i"
read_s = read_arg parse_int (>0) (\n o -> o { cl_i = ceiling $ logBase 2 $ fromIntegral n }) "Invalid s"
read_r = read_arg parse_double (>0) (\n o -> o { cl_r = fromRational $ toRational n }) "Invalid r"
read_q = read_arg parse_int (>0) (\n o -> o { cl_q = fromIntegral n }) "Invalid q"
read_k = read_arg parse_int (>0) (\n o -> o { cl_k = fromIntegral n }) "Invalid k"
read_n = read_arg parse_int (>0) (\n o -> o { cl_n = fromIntegral n }) "Invalid n"
read_m = read_arg parse_int (>0) (\n o -> o { cl_m = fromIntegral n }) "Invalid m"
read_arg :: (String -> Maybe a) -> (a -> Bool) -> (a -> Options -> Options) -> String -> String -> Options -> IO Options
read_arg parse cond func err string o =
case parse string of
Just n | cond n -> return $ func n o
_ -> optfail (err ++ " -- " ++ string ++ "\n")
help :: Options -> IO Options
help o = do
usage
exitSuccess
dopts :: [String] -> IO Options
dopts argv =
case getOpt Permute options argv of
(o, [], []) -> (foldM (flip id) default_options 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 "subroutine" subroutine_enum)
where header = "Usage: cl [OPTION...]"
main :: IO()
main = do
argv <- getArgs
options <- dopts argv
let bigD = cl_delta options
assertM (is_valid_bigD bigD) $
"Δ = " ++ (show $ cl_delta options) ++ " not valid discriminant"
let d = d_of_bigD bigD
case what options of
Stage1 -> main_stage1 options
Stage4 -> main_stage4 options
Sub -> main_sub options
Regulator -> do
putStrLn $ "Regulator (by classical period-finding):"
putStrLn $ "Δ = " ++ show bigD
putStrLn $ "d = " ++ show d
putStrLn $ "R = " ++ show (regulator bigD)
FundamentalUnit -> do
putStrLn $ "Fundamental unit (by classical period-finding):"
putStrLn $ "Δ = " ++ show bigD
putStrLn $ "d = " ++ show d
putStrLn $ "ε_0 = " ++ pretty_show_AlgNum (fundamental_unit bigD)
PellSolution -> do
putStrLn $ "Fundamental solution of Pell’s equation x^2 − d y^2 = 1 (by classical period-finding):"
let (x,y) = fundamental_solution d
putStrLn $ "Δ = " ++ show bigD
putStrLn $ "d = " ++ show d
putStrLn $ "x = " ++ show x
putStrLn $ "y = " ++ show y
main_stage1 :: Options -> IO()
main_stage1 options = do
let bigD = cl_delta options
assertM (is_valid_bigD bigD) $
"Δ = " ++ (show $ cl_delta options) ++ " not valid discriminant"
let i = cl_i options
ss_bound = 2^i
q = 2 + 2 * i
t = 2 * (ceiling (logBase 2 (sqrt $ fromIntegral bigD))) + i
putStrLn $ "Generating circuit for stage 1 with args: "
putStrLn $ show options
putStrLn $ ""
putStrLn $ "Computed values: "
putStrLn $ "Δ: " ++ show bigD
putStrLn $ "i: " ++ show i
putStrLn $ "S_bound: " ++ show ss_bound
putStrLn $ "q: " ++ show q
putStrLn $ "t: " ++ show t
let rand = 0
let circuit = approximate_regulator_circuit bigD i rand
print_simple (format options) (decompose_generic (gatebase options) circuit)
main_stage4 :: Options -> IO()
main_stage4 options = do
putStrLn $ "Generating circuit for stage 4 with args: " ++ show options
main_sub :: Options -> IO()
main_sub options =
let fmt = format options
gtb = gatebase options
bigD = cl_delta options
in case sub options of
Rho -> do
print_generic fmt (unbox q_rho_d) (sample_IdDistQ bigD)
RhoInv -> do
print_generic fmt (unbox q_rho_inv_d) (sample_IdDistQ bigD)
Normalize -> do
print_generic fmt (unbox q_normalize) (sample_IdDistQ bigD)
DotProd -> do
print_generic fmt (unbox q_dot_prod) iirq iirq
where iirq = sample_IdealRedQ bigD
StarProd -> do
print_generic fmt (unbox q_star_prod) iirdq iirdq
where iirdq = sample_IdRedDistQ bigD
FN -> do
print_generic fmt (unbox $ \qi -> q_fN bigD n 0 qi j) iq
where
i = cl_i options
q = 2 + 2 * i
n = n_of_bigD bigD
iq = qshape (intm q 0)
j = (intm (q + 4) 0)