{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LINE 1 "Quipper/Libraries/QFTAdd.hs" #-}
module Quipper.Libraries.QFTAdd
(
qft_add_in_place
)
where
import Quipper
import Quipper.Libraries.Arith
import Quipper.Libraries.QFT
qft_add_in_place :: QDInt -> QDInt -> Circ (QDInt,QDInt)
qft_add_in_place x y = do
let x' = list_of_xint_bh x
let y' = list_of_xint_bh y
(x', y') <- qft_add_in_place_qulist x' y'
let x = xint_of_list_bh x'
let y = xint_of_list_bh y'
return (x, y)
qft_add_in_place_qulist :: [Qubit] -> [Qubit] -> Circ ([Qubit], [Qubit])
qft_add_in_place_qulist a b = do
label (a,b) ("a","b")
with_computed (box "QFT" qft_big_endian b) $ \b' -> do
qft_adder a (reverse b')
label (a,b) ("a","b")
return (a,b)
qft_adder :: [Qubit] -> [Qubit] -> Circ ()
qft_adder _ [] = return ()
qft_adder as (b:bs) = do
qft_adder' as b 1
qft_adder (tail as) bs
where
qft_adder' :: [Qubit] -> Qubit -> Int -> Circ [Qubit]
qft_adder' [] _ _ = return []
qft_adder' (a:as) b n = do
b <- rGate n b `controlled` a
qft_adder' as b (n+1)