{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LINE 1 "Quipper/Libraries/QuipperASCIIParser/Parse.hs" #-}
module Quipper.Libraries.QuipperASCIIParser.Parse where
import Quipper.Internal.Circuit
import Data.IntMap hiding (map)
import Text.ParserCombinators.ReadP
import Data.Char (isDigit)
import qualified Data.Map as Map
data GatePlus = G Gate [(Wire,Wiretype)]
| I [(Wire,Wiretype)]
| O [(Wire,Wiretype)]
| EmptyLine
| CommentLine String
| SubroutineName String
| SubroutineShape String
| Controllable ControllableFlag
deriving Show
string_literal :: ReadP String
string_literal = do
char '"'
s <- string_with_escaped_chars ""
char '"'
return s
where
string_with_escaped_chars :: String -> ReadP String
string_with_escaped_chars input = do
s <- munch (\x -> x /= '\\' && x /= '"')
let s' = input ++ s
rest <- look
case rest of
'"' : _ -> return s'
'\\' : _ -> do
e <- escaped_char
string_with_escaped_chars (s' ++ [e])
_ -> do
pfail
escaped_char :: ReadP Char
escaped_char = do
char '\\'
c <- get
return (Map.findWithDefault c c map)
where
map = Map.fromList [
('0', '\0'),
('a', '\a'),
('b', '\b'),
('f', '\f'),
('n', '\n'),
('r', '\r'),
('t', '\t'),
('v', '\v'),
('"', '\"'),
('\'', '\''),
('\\', '\\')
]
int :: ReadP Int
int = do
s <- munch1 isDigit
return $ (read s :: Int)
double :: ReadP Double
double = do
(s, _) <- gather parse_double
return $ (read s :: Double)
where
parse_double = do
option '+' (char '+' +++ char '-')
munch isDigit
optional (char '.' >> munch1 isDigit)
optional (char 'e' >> option '+' (char '+' +++ char '-') >> int)
commalist :: ReadP a -> ReadP [a]
commalist elt = sepBy elt (skipSpaces >> char ',' >> skipSpaces)
control :: ReadP (Signed Wire,Wiretype)
control = do
val <- choice [char '+',char '-']
skipSpaces
w <- int
c <- option 'q' (char 'c')
let wt = case c of
'c' -> Cbit
_ -> Qbit
return (Signed w (val == '+'),wt)
controls :: ReadP ([Signed Wire],[(Wire,Wiretype)])
controls = do
skipSpaces
string "with controls=["
cwts <- commalist control
char ']'
let cs = map fst cwts
let wts = map (\(Signed w _,wt) -> (w,wt)) cwts
return (cs,wts)
wiretype :: ReadP Wiretype
wiretype = do
c <- choice [string "Qbit",string "Cbit"]
case c of
"Qbit" -> return Qbit
"Cbit" -> return Cbit
_ -> error "The impossible has happened"
wire :: ReadP (Int,Wiretype)
wire = do
skipSpaces
w <- int
char ':'
t <- wiretype
return (w,t)
wires :: ReadP [(Int,Wiretype)]
wires = do
skipSpaces
ws <- commalist wire
return ws
none :: ReadP [(Int,Wiretype)]
none = do
skipSpaces
string "none"
return []
inversechar :: ReadP Bool
inversechar = do
c <- option '+' (char '*')
return (c == '*')
label' :: ReadP (Int,String)
label' = do
w <- int
char ':'
lab <- string_literal
return (w,lab)
labelchar :: ReadP String
labelchar = do
c <- satisfy (\x -> not (x `elem` ")],"))
return [c]
labelbracket :: ReadP String
labelbracket = do
char '['
s <- munch (\x -> not (x `elem` "[]"))
char ']'
return ("[" ++ s ++ "]")
labels :: ReadP [(Int,String)]
labels = do
skipSpaces
char '('
ls <- commalist label'
char ')'
return ls
box_id :: ReadP BoxId
box_id = do
name <- string_literal
skipSpaces
char ','
skipSpaces
string "shape"
skipSpaces
shape <- string_literal
return (BoxId name shape)
nocontrolflag :: ReadP NoControlFlag
nocontrolflag = do
skipSpaces
ncf <- option "" (string "with nocontrol")
return (ncf == "with nocontrol")
ascii_line :: ReadP GatePlus
ascii_line = choice [
do
string "Inputs:"
ws <- choice [wires,none]
eof
return (I ws),
do
string "Outputs:"
ws <- choice [wires,none]
eof
return (O ws),
do
skipSpaces
eof
return EmptyLine,
do
skipSpaces
char '#'
skipSpaces
comment <- manyTill (satisfy (\_ -> True)) eof
eof
return (CommentLine comment),
do
string "Subroutine: "
name <- string_literal +++ manyTill (satisfy (\_ -> True)) eof
eof
return (SubroutineName name),
do
string "Shape: "
shape <- string_literal +++ manyTill (satisfy (\_ -> True)) eof
eof
return (SubroutineShape shape),
do
string "Controllable: "
val_string <- choice [string "yes",string "no", string "classically"]
let val = case val_string of
"yes" -> AllCtl
"no" -> NoCtl
"classically" -> OnlyClassicalCtl
_ -> error "The impossible happened"
eof
return (Controllable val),
do
string "QNot("
w <- int
char ')'
(cs,wts) <- option ([],[]) controls
ncf <- nocontrolflag
eof
return (G (QGate "not" False [w] [] cs ncf) wts),
do
string "QMultinot("
ws <- commalist int
char ')'
(cs,wts) <- option ([],[]) controls
ncf <- nocontrolflag
eof
return (G (QGate "multinot" False ws [] cs ncf) wts),
do
string "QHad("
w <- int
char ')'
(cs,wts) <- option ([],[]) controls
ncf <- nocontrolflag
eof
return (G (QGate "H" False [w] [] cs ncf) wts),
do
string "QSwap("
w1 <- int
char ','
w2 <- int
char ')'
(cs,wts) <- option ([],[]) controls
ncf <- nocontrolflag
eof
return (G (QGate "swap" False [w1, w2] [] cs ncf) wts),
do
string "QW("
w1 <- int
char ','
w2 <- int
char ')'
(cs,wts) <- option ([],[]) controls
ncf <- nocontrolflag
eof
return (G (QGate "W" False [w1, w2] [] cs ncf) wts),
do
string "GPhase() with t="
t <- double
(cs,wts) <- option ([],[]) controls
ncf <- nocontrolflag
ws <- option [] (do
skipSpaces
string "with anchors=["
ws <- commalist int
char ']'
return ws )
eof
return (G (GPhase t ws cs ncf) wts),
do
string "QGate["
name <- string_literal
char ']'
inv <- inversechar
char '('
ws1 <- commalist int
char ')'
ws2 <- option [] (do
string "; ["
ws <- commalist int
char ']'
return ws )
(cs,wts) <- option ([],[]) controls
ncf <- nocontrolflag
eof
return (G (QGate name inv ws1 ws2 cs ncf) wts),
do
string "QRot["
name <- string_literal
char ','
theta <- double
char ']'
inv <- inversechar
char '('
ws1 <- commalist int
char ')'
ws2 <- option [] ( do
string "; ["
ws <- commalist int
char ']'
return ws )
(cs,wts) <- option ([],[]) controls
ncf <- nocontrolflag
eof
return (G (QRot name inv theta ws1 ws2 cs ncf) wts),
do
string "CNot("
w <- int
char ')'
(cs,wts) <- option ([],[]) controls
ncf <- nocontrolflag
eof
return (G (CNot w cs ncf) wts),
do
string "CGate["
name <- string_literal
string "]("
ws <- commalist int
char ')'
ncf <- nocontrolflag
eof
return (G (CGate name (head ws) (tail ws) ncf) []),
do
string "CGate["
name <- string_literal
string "]*("
ws <- commalist int
char ')'
ncf <- nocontrolflag
eof
return (G (CGateInv name (head ws) (tail ws) ncf) []),
do
string "CSwap("
w1 <- int
char ','
w2 <- int
char ')'
(cs,wts) <- option ([],[]) controls
ncf <- nocontrolflag
eof
return (G (CSwap w1 w2 cs ncf) wts),
do
string "QPrep("
w <- int
char ')'
ncf <- nocontrolflag
eof
return (G (QPrep w ncf) []),
do
string "QUnprep("
w <- int
char ')'
ncf <- nocontrolflag
eof
return (G (QUnprep w ncf) []),
do
string "QInit"
val_char <- choice [char '0',char '1']
let val = val_char == '1'
char '('
w <- int
char ')'
ncf <- nocontrolflag
eof
return (G (QInit val w ncf) []),
do
string "CInit"
val_char <- choice [char '0',char '1']
let val = val_char == '1'
char '('
w <- int
char ')'
ncf <- nocontrolflag
eof
return (G (CInit val w ncf) []),
do
string "QTerm"
val_char <- choice [char '0',char '1']
let val = val_char == '1'
char '('
w <- int
char ')'
ncf <- nocontrolflag
eof
return (G (QTerm val w ncf) []),
do
string "CTerm"
val_char <- choice [char '0',char '1']
let val = val_char == '1'
char '('
w <- int
char ')'
ncf <- nocontrolflag
eof
return (G (CTerm val w ncf) []),
do
string "QMeas("
w <- int
char ')'
eof
return (G (QMeas w) []),
do
string "QDiscard("
w <- int
char ')'
eof
return (G (QDiscard w) []),
do
string "CDiscard("
w <- int
char ')'
eof
return (G (CDiscard w) []),
do
string "DTerm"
vc <- char '0' +++ char '1'
let b = case vc of
'0' -> False
'1' -> True
_ -> error "The impossible has happend"
char '('
w <- int
char ')'
eof
return (G (DTerm b w) []),
do
string "Subroutine"
reps <- option 1 $ do
string "(x"
r <- int
char ')'
return (toInteger r)
char '['
boxid <- box_id
char ']'
inv <- inversechar
string " ("
ws1 <- commalist int
string ") -> ("
ws2 <- commalist int
char ')'
(cs,wts) <- option ([],[]) controls
ncf <- nocontrolflag
eof
let dummy = error "attempted evaluation of a dummy value"
return (G (Subroutine boxid inv ws1 dummy ws2 dummy cs ncf dummy (RepeatFlag reps)) wts),
do
string "Comment"
skipSpaces
char '['
comment <- string_literal
char ']'
inv <- inversechar
ls <- labels
eof
return (G (Comment comment inv ls) [])
]
parse_ascii_line :: String -> Maybe GatePlus
parse_ascii_line s =
case readP_to_S ascii_line s of
(h, _):_ -> Just h
_ -> Nothing
where
readline = do
skipSpaces
l <- ascii_line
skipSpaces
eof
return l