{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LINE 1 "Quipper/Algorithms/QLS/CircLiftingImport.hs" #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
module Quipper.Algorithms.QLS.CircLiftingImport where
import Data.Typeable
import Quipper
import Quipper.Internal
import Quipper.Libraries.Arith
import Quipper.Libraries.Decompose
import Quipper.Algorithms.QLS.QDouble
import Quipper.Algorithms.QLS.QSignedInt
import Quipper.Algorithms.QLS.Utils
grepn :: (Eq a) => [a] -> [a] -> Int
grepn regexp l =
if (length regexp > length l) then 0
else if ((take (length regexp) l) == regexp) then 1 + (grepn regexp $ tail l)
else grepn regexp $ tail l
template_symb_slash_symb_equal_ :: (Typeable qa, QOrd qa) => Circ (qa -> Circ (qa -> Circ Qubit))
template_symb_slash_symb_equal_ = return $ \x -> return $ \y -> do
(_,_,r) <- box "/=" (decompose_generic Toffoli $ uncurry q_is_not_equal) (x,y)
return r
template_symb_oangle_ :: (Typeable qa, QOrd qa) => Circ (qa -> Circ (qa -> Circ Qubit))
template_symb_oangle_ = return $ \x -> return $ \y -> box "<" (uncurry q_less) (x,y)
template_symb_oangle_symb_equal_ :: (Typeable qa, QOrd qa) => Circ (qa -> Circ (qa -> Circ Qubit))
template_symb_oangle_symb_equal_ = return $ \x -> return $ \y -> box "<=" (uncurry q_leq) (x,y)
template_symb_cangle_ :: (Typeable qa, QOrd qa) => Circ (qa -> Circ (qa -> Circ Qubit))
template_symb_cangle_ = return $ \x -> return $ \y -> box ">" (uncurry q_greater) (x,y)
template_symb_cangle_symb_equal_ :: (Typeable qa, QOrd qa) => Circ (qa -> Circ (qa -> Circ Qubit))
template_symb_cangle_symb_equal_ = return $ \x -> return $ \y -> box ">=" (uncurry q_geq) (x,y)
template_symb_minus_ :: (Typeable qa, QNum qa) => Circ (qa -> Circ (qa -> Circ qa))
template_symb_minus_ = return $ \qx -> return $ \qy -> do (qx,qy,qz) <- box "-" (uncurry q_sub) (qx,qy); return qz
template_symb_plus_ :: (Typeable qa, QNum qa) => Circ (qa -> Circ (qa -> Circ qa))
template_symb_plus_ = return $ \qx -> return $ \qy -> do (qx,qy,qz) <- box "+" (uncurry q_add) (qx,qy); return qz
template_symb_star_ :: (Typeable qa, QNum qa) => Circ (qa -> Circ (qa -> Circ qa))
template_symb_star_ = return $ \qx -> return $ \qy -> do (qx,qy,qz) <- box "*" (uncurry q_mult) (qx,qy); return qz
template_negate :: (Typeable qa, QNum qa) => Circ (qa -> Circ qa)
template_negate = return $ \qx -> do (_,qz) <- box "neg" q_negate qx; return qz
template_abs :: (Typeable qa, QNum qa) => Circ (qa -> Circ qa)
template_abs = return $ \x -> do
(_,r) <- box "abs" q_abs x
return r
template_mod :: Circ (QSignedInt -> Circ (QSignedInt -> Circ QSignedInt))
template_mod = return $ \x -> return $ \y -> box "mod" (decompose_generic Toffoli $ uncurry q_mod) (x,y)
template_symb_slash_:: Circ (QDouble -> Circ (QDouble -> Circ QDouble))
template_symb_slash_ = return $ \x -> return $ \y -> box "/" (decompose_generic Toffoli $ uncurry q_div_real) (x,y)
local_pi :: FDouble
local_pi = fdouble pi
template_local_pi :: Circ QDouble
template_local_pi = qinit (fdouble pi)
id_fdouble :: FDouble -> FDouble
id_fdouble x = x
template_id_fdouble :: Circ (QDouble -> Circ QDouble)
template_id_fdouble = return $ \x -> return x
template_floor :: Circ (QDouble -> Circ QSignedInt)
template_floor = return $ \(XDouble k (SInt x b)) ->
return $ SInt (reverse . drop k . reverse $ x) b
template_ceiling :: Circ (QDouble -> Circ QSignedInt)
template_ceiling = return $ \x -> q_ceiling x
template_fromIntegral :: Circ (QSignedInt -> Circ QDouble)
template_fromIntegral = return $ \x -> q_fromIntegral x
template_rational :: Double -> Circ QDouble
template_rational x = qinit $ fdouble x
template_integer :: Int -> Circ QSignedInt
template_integer x = qinit $ fromIntegral x
getIntFromParam :: Int -> Int
getIntFromParam x = fromIntegral x
template_getIntFromParam :: Circ (Int -> Circ QSignedInt)
template_getIntFromParam = return $ \x -> qinit $ fromIntegral x
paramZero :: Int
paramZero = 0
template_paramZero :: Circ Int
template_paramZero = return 0
paramTen :: Int
paramTen = 10
template_paramTen :: Circ Int
template_paramTen = return paramTen
paramSucc :: Int -> Int
paramSucc x = x+1
template_paramSucc :: Circ (Int -> Circ Int)
template_paramSucc = return $ \x -> return (x+1)
paramPred :: Int -> Int
paramPred x = x - 1
template_paramPred :: Circ (Int -> Circ Int)
template_paramPred = return $ \x -> return (x-1)
paramMinus :: Int -> Int -> Int
paramMinus x y = x - y
template_paramMinus :: Circ (Int -> Circ (Int -> Circ Int))
template_paramMinus = return $ \x -> return $ \y -> return (x-y)
template_length :: Circ ([a] -> Circ QSignedInt)
template_length = return $ \l -> qinit $ fromIntegral $ length l
take_half :: [a] -> [a]
take_half l = take (1 + (length l) `div` 2) l
template_take_half :: Circ ([a] -> Circ [a])
template_take_half = return $ \l -> return $ take_half l