{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LINE 1 "Quipper/Algorithms/GSE/Main.hs" #-}
module Quipper.Algorithms.GSE.Main where
import Quipper
import Quipper.Libraries.Decompose
import Quipper.Algorithms.GSE.GSE
import Quipper.Algorithms.GSE.GSEData
import Quipper.Algorithms.GSE.JordanWigner
import Quipper.Utils.CommandLine
import System.Console.GetOpt
import System.Environment
import System.Exit
import Control.Monad
import Data.Bits
import qualified System.FilePath as FilePath
data WhatToShow =
Circuit
| Template [Int]
deriving Show
data Options = Options {
what :: WhatToShow,
format :: Format,
gatebase :: GateBase,
gse_orthodox :: Bool,
gse_b :: Int,
gse_m :: Int,
gse_occupied :: Int,
gse_delta_e :: Double,
gse_e_max :: Double,
gse_nfun :: Int -> Int,
gse_h1_file :: String,
gse_h2_file :: String,
gse_datadir :: String
}
defaultOptions :: Options
defaultOptions = Options {
what = Circuit,
format = Preview,
gatebase = Logical,
gse_orthodox = False,
gse_b = 3,
gse_m = 4,
gse_occupied = 2,
gse_delta_e = 6.5536,
gse_e_max = -3876.941,
gse_nfun = (\k -> 1),
gse_h1_file = "h_1e_ascii",
gse_h2_file = "h_2e_ascii",
gse_datadir = "."
}
showDefault :: (Show a) => (Options -> a) -> String
showDefault func = show (func defaultOptions)
options :: [OptDescr (Options -> IO Options)]
options = [
Option ['h'] ["help"] (NoArg help) $ "print usage info and exit",
Option ['C'] ["circuit"] (NoArg (what Circuit)) $ "output the whole circuit (default)",
Option ['T'] ["template"] (ReqArg read_template "<indices>") $ "output a particular circuit template",
Option ['f'] ["format"] (ReqArg read_format "<format>") $ "output format for circuits (default: " ++ showDefault format ++ ")",
Option ['g'] ["gatebase"] (ReqArg read_gatebase "<gatebase>") $ "gates to decompose into (default: " ++ showDefault gatebase ++ ")",
Option ['m'] ["orbitals"] (ReqArg read_m "<N>") $ "number of orbitals (default: " ++ showDefault gse_m ++ ")",
Option ['o'] ["occupied"] (ReqArg read_occupied "<N>") $ "number of occupied orbitals (default: " ++ showDefault gse_occupied ++ ")",
Option ['b'] ["precision"] (ReqArg read_b "<N>") $ "number of precision qubits (default: " ++ showDefault gse_b ++ ")",
Option ['D'] ["delta_e"] (ReqArg read_delta_e "<energy>") $ "energy range (default: " ++ showDefault gse_delta_e ++ ")",
Option ['E'] ["e_max"] (ReqArg read_e_max "<energy>") $ "maximum energy (default: " ++ showDefault gse_e_max ++ ")",
Option [] ["n0"] (ReqArg read_n0 "<N>") $ "use N_k = n0 * 2^k (default: N_k = 1)",
Option ['l'] ["large"] (NoArg large_parameters) $ "set large problem size (m=208, o=84, b=12, n0=100)",
Option ['x'] ["orthodox"] (NoArg orthodox) $ "use the Coulomb operator of Whitman et al.",
Option [] ["h1"] (ReqArg read_h1 "<file>") $ "filename for one-electron data (default: " ++ showDefault gse_h1_file ++ ")",
Option [] ["h2"] (ReqArg read_h2 "<file>") $ "filename for two-electron data (default: " ++ showDefault gse_h2_file ++ ")",
Option ['d'] ["datadir"] (ReqArg read_datadir "<file>") $ "directory for one- and two-electron data (default: current)"
]
where
what :: WhatToShow -> Options -> IO Options
what w o = return o { what = w }
large_parameters o =
return o {
gse_b = 12,
gse_m = 208,
gse_delta_e = 6.5536,
gse_e_max = -3876.941,
gse_occupied = 84,
gse_nfun = (\k -> 100 * (1 `shift` k))
}
orthodox o = return o {gse_orthodox = True }
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_b :: String -> Options -> IO Options
read_b string o =
case parse_int string of
Just n | n > 0 -> return o { gse_b = n }
_ -> optfail ("Invalid b (precision) -- " ++ string ++ "\n")
read_m :: String -> Options -> IO Options
read_m string o =
case parse_int string of
Just n | n > 0 -> return o { gse_m = n }
_ -> optfail ("Invalid m (orbitals) -- " ++ string ++ "\n")
read_n0 :: String -> Options -> IO Options
read_n0 string o =
case parse_int string of
Just n | n > 0 -> return o { gse_nfun = (\k -> n * (1 `shift` k)) }
_ -> optfail ("Invalid n0 -- " ++ string ++ "\n")
read_occupied :: String -> Options -> IO Options
read_occupied string o =
case parse_int string of
Just n | n > 0 -> return o { gse_occupied = n }
_ -> optfail ("Invalid o (occupied) -- " ++ string ++ "\n")
read_delta_e :: String -> Options -> IO Options
read_delta_e string o =
case parse_double string of
Just n | n >= 0 -> return o { gse_delta_e = n }
_ -> optfail ("Invalid Delta E -- " ++ string ++ "\n")
read_e_max :: String -> Options -> IO Options
read_e_max string o =
case parse_double string of
Just n | n >= 0 -> return o { gse_e_max = n }
_ -> optfail ("Invalid E_max -- " ++ string ++ "\n")
read_h1 :: String -> Options -> IO Options
read_h1 string o = return o { gse_h1_file = string }
read_h2 :: String -> Options -> IO Options
read_h2 string o = return o { gse_h2_file = string }
read_datadir :: String -> Options -> IO Options
read_datadir string o = return o { gse_datadir = string }
read_template :: String -> Options -> IO Options
read_template string o = do
ps <- sequence [ convert p | p <- split ',' string ]
let len = length ps
if len == 2 || len == 4 then
return o { what = Template ps }
else
optfail ("Must give 2 or 4 indices, not " ++ (show len) ++ "\n")
where
split c as = case break (== c) as of
(h,_:t) -> h : (split c t)
(h,[]) -> [h]
convert p = case parse_int p of
Just n | n >= 0 -> return n
_ -> optfail ("Invalid index -- '" ++ p ++ "'\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) 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 ("Indices can be specified as p,q or p,q,r,s (with no spaces)\n")
where header = "Usage: gse [OPTION...]"
main :: IO()
main = do
argv <- getArgs
options <- dopts argv
case what options of
Circuit -> main_circuit options
Template qs -> main_template options qs
main_circuit :: Options -> IO()
main_circuit options = do
let b = gse_b options
m = gse_m options
o = gse_occupied options
dE = gse_delta_e options
e_max = gse_e_max options
datadir = gse_datadir options
file1 = gse_h1_file options
file2 = gse_h2_file options
nfun = gse_nfun options
orth = gse_orthodox options
let tau = 2*pi / dE
path1 = FilePath.combine datadir file1
path2 = FilePath.combine datadir file2
gse_data <- load_gse_data m path1 path2
let circuit = gse b m o gse_data tau e_max nfun orth
print_simple (format options) (decompose_generic (gatebase options) circuit)
main_template :: Options -> [Int] -> IO()
main_template options [p,q] = do
show_one_electron (format options) (gatebase options) p q
main_template options [p,q,r,s] = do
if gse_orthodox options
then show_two_electron_orthodox (format options) (gatebase options) p q r s
else show_two_electron (format options) (gatebase options) p q r s
main_template options qs =
error "main_template: wrong number of indices given"