{-# LANGUAGE OverloadedStrings #-}
module Clash.Netlist.BlackBox.Parser
(runParse)
where
import Control.Applicative ((<|>))
import Data.Text.Lazy (Text, pack, unpack)
import qualified Data.Text.Lazy as Text
import Text.Trifecta hiding (Err)
import Text.Trifecta.Delta
import qualified Clash.Signal.Internal as Signal
import Clash.Netlist.BlackBox.Types
runParse :: Text -> Result BlackBoxTemplate
runParse :: Text -> Result [Element]
runParse = Parser [Element] -> Delta -> String -> Result [Element]
forall a. Parser a -> Delta -> String -> Result a
parseString (Parser [Element]
pBlackBoxD Parser [Element] -> Parser () -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Parser ()
forall (m :: Type -> Type). Parsing m => m ()
eof) (ByteString -> Int64 -> Int64 -> Int64 -> Int64 -> Delta
Directed ByteString
"" Int64
0 Int64
0 Int64
0 Int64
0) (String -> Result [Element])
-> (Text -> String) -> Text -> Result [Element]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack
pBlackBoxD :: Parser BlackBoxTemplate
pBlackBoxD :: Parser [Element]
pBlackBoxD = Parser Element -> Parser [Element]
forall a. Parser a -> Parser [a]
forall (f :: Type -> Type) a. Alternative f => f a -> f [a]
some Parser Element
pElement
pElement :: Parser Element
pElement :: Parser Element
pElement = Parser Element
pTagD
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Text -> Element
Text (Text -> Element) -> Parser Text -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text
pText
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Text -> Element
Text (Text -> Element) -> Parser Text -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Text
pack (String -> Text) -> Parser String -> Parser Text
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ ")
pText :: Parser Text
pText :: Parser Text
pText = String -> Text
pack (String -> Text) -> Parser String -> Parser Text
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Char -> Parser String
forall a. Parser a -> Parser [a]
forall (f :: Type -> Type) a. Alternative f => f a -> f [a]
some (Char -> Char -> Parser Char
forall (m :: Type -> Type). CharParsing m => Char -> Char -> m Char
satisfyRange Char
'\000' Char
'\125')
pEdge :: Parser Signal.ActiveEdge
pEdge :: Parser ActiveEdge
pEdge =
(ActiveEdge -> Parser ActiveEdge
forall a. a -> Parser a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ActiveEdge
Signal.Rising Parser ActiveEdge -> Parser String -> Parser ActiveEdge
forall a b. Parser a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* String -> Parser String
forall (m :: Type -> Type). TokenParsing m => String -> m String
symbol String
"Rising") Parser ActiveEdge -> Parser ActiveEdge -> Parser ActiveEdge
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|>
(ActiveEdge -> Parser ActiveEdge
forall a. a -> Parser a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ActiveEdge
Signal.Falling Parser ActiveEdge -> Parser String -> Parser ActiveEdge
forall a b. Parser a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* String -> Parser String
forall (m :: Type -> Type). TokenParsing m => String -> m String
symbol String
"Falling")
pTagD :: Parser Element
pTagD :: Parser Element
pTagD = Element -> [Element] -> [Element] -> Element
IF (Element -> [Element] -> [Element] -> Element)
-> Parser Element -> Parser ([Element] -> [Element] -> Element)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). TokenParsing m => String -> m String
symbol String
"~IF" Parser String -> Parser Element -> Parser Element
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Element
pTagE)
Parser ([Element] -> [Element] -> Element)
-> Parser [Element] -> Parser ([Element] -> Element)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> (Parser ()
forall (m :: Type -> Type). CharParsing m => m ()
spaces Parser () -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~THEN" Parser String -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser [Element]
pBlackBoxD))
Parser ([Element] -> Element) -> Parser [Element] -> Parser Element
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ELSE" Parser String -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> [Element] -> Parser [Element] -> Parser [Element]
forall (m :: Type -> Type) a. Alternative m => a -> m a -> m a
option ([Text -> Element
Text Text
""]) Parser [Element]
pBlackBoxD Parser [Element] -> Parser String -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~FI")
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Decl -> Element
Component (Decl -> Element) -> Parser Decl -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Decl
pDecl
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Parser Element
pTagE
pDecl :: Parser Decl
pDecl :: Parser Decl
pDecl = Int -> Int -> [([Element], [Element])] -> Decl
Decl (Int -> Int -> [([Element], [Element])] -> Decl)
-> Parser Int -> Parser (Int -> [([Element], [Element])] -> Decl)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). TokenParsing m => String -> m String
symbol String
"~INST" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural') Parser (Int -> [([Element], [Element])] -> Decl)
-> Parser Int -> Parser ([([Element], [Element])] -> Decl)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Int -> Parser Int
forall a. a -> Parser a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Int
0 Parser ([([Element], [Element])] -> Decl)
-> Parser [([Element], [Element])] -> Parser Decl
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*>
((:) (([Element], [Element])
-> [([Element], [Element])] -> [([Element], [Element])])
-> Parser ([Element], [Element])
-> Parser ([([Element], [Element])] -> [([Element], [Element])])
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ([Element], [Element])
pOutput Parser ([([Element], [Element])] -> [([Element], [Element])])
-> Parser [([Element], [Element])]
-> Parser [([Element], [Element])]
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser ([Element], [Element]) -> Parser [([Element], [Element])]
forall a. Parser a -> Parser [a]
forall (f :: Type -> Type) a. Alternative f => f a -> f [a]
many Parser ([Element], [Element])
pInput) Parser Decl -> Parser String -> Parser Decl
forall a b. Parser a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~INST"
pOutput :: Parser (BlackBoxTemplate,BlackBoxTemplate)
pOutput :: Parser ([Element], [Element])
pOutput = String -> Parser String
forall (m :: Type -> Type). TokenParsing m => String -> m String
symbol String
"~OUTPUT" Parser String -> Parser String -> Parser String
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> String -> Parser String
forall (m :: Type -> Type). TokenParsing m => String -> m String
symbol String
"<=" Parser String
-> Parser ([Element], [Element]) -> Parser ([Element], [Element])
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> ((,) ([Element] -> [Element] -> ([Element], [Element]))
-> Parser [Element] -> Parser ([Element] -> ([Element], [Element]))
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser [Element]
pBlackBoxE Parser [Element] -> Parser String -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* String -> Parser String
forall (m :: Type -> Type). TokenParsing m => String -> m String
symbol String
"~") Parser ([Element] -> ([Element], [Element]))
-> Parser [Element] -> Parser ([Element], [Element])
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser [Element]
pBlackBoxE) Parser ([Element], [Element])
-> Parser String -> Parser ([Element], [Element])
forall a b. Parser a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* String -> Parser String
forall (m :: Type -> Type). TokenParsing m => String -> m String
symbol String
"~"
pInput :: Parser (BlackBoxTemplate,BlackBoxTemplate)
pInput :: Parser ([Element], [Element])
pInput = String -> Parser String
forall (m :: Type -> Type). TokenParsing m => String -> m String
symbol String
"~INPUT" Parser String -> Parser String -> Parser String
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> String -> Parser String
forall (m :: Type -> Type). TokenParsing m => String -> m String
symbol String
"<=" Parser String
-> Parser ([Element], [Element]) -> Parser ([Element], [Element])
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> ((,) ([Element] -> [Element] -> ([Element], [Element]))
-> Parser [Element] -> Parser ([Element] -> ([Element], [Element]))
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser [Element]
pBlackBoxE Parser [Element] -> Parser String -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* String -> Parser String
forall (m :: Type -> Type). TokenParsing m => String -> m String
symbol String
"~") Parser ([Element] -> ([Element], [Element]))
-> Parser [Element] -> Parser ([Element], [Element])
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser [Element]
pBlackBoxE) Parser ([Element], [Element])
-> Parser String -> Parser ([Element], [Element])
forall a b. Parser a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* String -> Parser String
forall (m :: Type -> Type). TokenParsing m => String -> m String
symbol String
"~"
pTagE :: Parser Element
pTagE :: Parser Element
pTagE = Element
Result Element -> Parser String -> Parser Element
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~RESULT"
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Int -> Element
ArgGen (Int -> Int -> Element) -> Parser Int -> Parser (Int -> Element)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ARGN" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural') Parser (Int -> Element) -> Parser Int -> Parser Element
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural'
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
Arg (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ARG" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
Const (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~CONST" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
Lit (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~LIT" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
Name (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~NAME" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> [Element] -> Int -> Element
ToVar ([Element] -> Int -> Element)
-> Parser [Element] -> Parser (Int -> Element)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
forall (m :: Type -> Type) a. Parsing m => m a -> m a
try (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~VAR" Parser String -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
brackets' Parser [Element]
pSigDorEmpty) Parser (Int -> Element) -> Parser Int -> Parser Element
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural'
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> (Text -> Int -> Element
Sym Text
Text.empty) (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~SYM" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Maybe Int -> Element
Typ Maybe Int
forall a. Maybe a
Nothing Element -> Parser String -> Parser Element
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~TYPO"
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> (Maybe Int -> Element
Typ (Maybe Int -> Element) -> (Int -> Maybe Int) -> Int -> Element
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Maybe Int
forall a. a -> Maybe a
Just) (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Int -> Parser Int
forall a. Parser a -> Parser a
forall (m :: Type -> Type) a. Parsing m => m a -> m a
try (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~TYP" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Maybe Int -> Element
TypM Maybe Int
forall a. Maybe a
Nothing Element -> Parser String -> Parser Element
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~TYPMO"
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> (Maybe Int -> Element
TypM (Maybe Int -> Element) -> (Int -> Maybe Int) -> Int -> Element
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Maybe Int
forall a. a -> Maybe a
Just) (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~TYPM" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Maybe Int -> Element
Err Maybe Int
forall a. Maybe a
Nothing Element -> Parser String -> Parser Element
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ERRORO"
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> (Maybe Int -> Element
Err (Maybe Int -> Element) -> (Int -> Maybe Int) -> Int -> Element
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Maybe Int
forall a. a -> Maybe a
Just) (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ERROR" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Element -> Element
TypElem (Element -> Element) -> Parser Element -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~TYPEL" Parser String -> Parser Element -> Parser Element
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Element -> Parser Element
forall a. Parser a -> Parser a
brackets' Parser Element
pTagE)
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Element -> Element
IndexType (Element -> Element) -> Parser Element -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~INDEXTYPE" Parser String -> Parser Element -> Parser Element
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Element -> Parser Element
forall a. Parser a -> Parser a
brackets' Parser Element
pTagE)
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Element
CompName Element -> Parser String -> Parser Element
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~COMPNAME"
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
IncludeName (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~INCLUDENAME" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Element -> Element
Size (Element -> Element) -> Parser Element -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~SIZE" Parser String -> Parser Element -> Parser Element
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Element -> Parser Element
forall a. Parser a -> Parser a
brackets' Parser Element
pTagE)
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Element -> Element
Length (Element -> Element) -> Parser Element -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~LENGTH" Parser String -> Parser Element -> Parser Element
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Element -> Parser Element
forall a. Parser a -> Parser a
brackets' Parser Element
pTagE)
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Element -> Element
Depth (Element -> Element) -> Parser Element -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~DEPTH" Parser String -> Parser Element -> Parser Element
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Element -> Parser Element
forall a. Parser a -> Parser a
brackets' Parser Element
pTagE)
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Element -> Element
MaxIndex (Element -> Element) -> Parser Element -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~MAXINDEX" Parser String -> Parser Element -> Parser Element
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Element -> Parser Element
forall a. Parser a -> Parser a
brackets' Parser Element
pTagE)
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Element -> Element
FilePath (Element -> Element) -> Parser Element -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~FILE" Parser String -> Parser Element -> Parser Element
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Element -> Parser Element
forall a. Parser a -> Parser a
brackets' Parser Element
pTagE)
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Bool -> Element
Gen (Bool -> Element) -> Parser Bool -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Bool
True Bool -> Parser String -> Parser Bool
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~GENERATE")
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Bool -> Element
Gen (Bool -> Element) -> Parser Bool -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Bool
False Bool -> Parser String -> Parser Bool
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ENDGENERATE")
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> ([Element] -> Maybe Int -> Element
`SigD` Maybe Int
forall a. Maybe a
Nothing) ([Element] -> Element) -> Parser [Element] -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~SIGDO" Parser String -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
brackets' Parser [Element]
pSigD)
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> [Element] -> Maybe Int -> Element
SigD ([Element] -> Maybe Int -> Element)
-> Parser [Element] -> Parser (Maybe Int -> Element)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~SIGD" Parser String -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
brackets' Parser [Element]
pSigD) Parser (Maybe Int -> Element)
-> Parser (Maybe Int) -> Parser Element
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> (Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Parser Int -> Parser (Maybe Int)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural'))
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Element
IW64 Element -> Parser String -> Parser Element
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~IW64"
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Element -> Element -> Element
CmpLE (Element -> Element -> Element)
-> Parser Element -> Parser (Element -> Element)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Element -> Parser Element
forall a. Parser a -> Parser a
forall (m :: Type -> Type) a. Parsing m => m a -> m a
try (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~CMPLE" Parser String -> Parser Element -> Parser Element
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Element -> Parser Element
forall a. Parser a -> Parser a
brackets' Parser Element
pTagE) Parser (Element -> Element) -> Parser Element -> Parser Element
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser Element -> Parser Element
forall a. Parser a -> Parser a
brackets' Parser Element
pTagE
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> (HdlSyn -> Element
HdlSyn HdlSyn
Vivado) Element -> Parser String -> Parser Element
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~VIVADO"
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> (HdlSyn -> Element
HdlSyn HdlSyn
Other) Element -> Parser String -> Parser Element
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~OTHERSYN"
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> (Bool -> [Element] -> Element -> Element
BV Bool
True) ([Element] -> Element -> Element)
-> Parser [Element] -> Parser (Element -> Element)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~TOBV" Parser String -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
brackets' Parser [Element]
pSigD) Parser (Element -> Element) -> Parser Element -> Parser Element
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser Element -> Parser Element
forall a. Parser a -> Parser a
brackets' Parser Element
pTagE
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> (Bool -> [Element] -> Element -> Element
BV Bool
False) ([Element] -> Element -> Element)
-> Parser [Element] -> Parser (Element -> Element)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~FROMBV" Parser String -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
brackets' Parser [Element]
pSigD) Parser (Element -> Element) -> Parser Element -> Parser Element
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser Element -> Parser Element
forall a. Parser a -> Parser a
brackets' Parser Element
pTagE
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Element -> Int -> Element
Sel (Element -> Int -> Element)
-> Parser Element -> Parser (Int -> Element)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~SEL" Parser String -> Parser Element -> Parser Element
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Element -> Parser Element
forall a. Parser a -> Parser a
brackets' Parser Element
pTagE) Parser (Int -> Element) -> Parser Int -> Parser Element
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural'
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
IsLit (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ISLIT" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
IsVar (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ISVAR" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
IsScalar (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ISSCALAR" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
IsActiveHigh (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ISACTIVEHIGH" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
IsActiveEnable (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ISACTIVEENABLE" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
IsUndefined (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ISUNDEFINED" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> [Element] -> Int -> Element
StrCmp ([Element] -> Int -> Element)
-> Parser [Element] -> Parser (Int -> Element)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~STRCMP" Parser String -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
brackets' Parser [Element]
pSigD) Parser (Int -> Element) -> Parser Int -> Parser Element
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural'
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
OutputUsage (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~OUTPUTWIREREG" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
OutputUsage (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~OUTPUTUSAGE" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> [Element] -> Int -> Element
GenSym ([Element] -> Int -> Element)
-> Parser [Element] -> Parser (Int -> Element)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~GENSYM" Parser String -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
brackets' Parser [Element]
pSigD) Parser (Int -> Element) -> Parser Int -> Parser Element
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural'
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> [Element] -> [Element] -> Element
Template ([Element] -> [Element] -> Element)
-> Parser [Element] -> Parser ([Element] -> Element)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~TEMPLATE" Parser String -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
brackets' Parser [Element]
pSigD) Parser ([Element] -> Element) -> Parser [Element] -> Parser Element
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
brackets' Parser [Element]
pSigD
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> [Element] -> [Element] -> Element
Repeat ([Element] -> [Element] -> Element)
-> Parser [Element] -> Parser ([Element] -> Element)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~REPEAT" Parser String -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
brackets' Parser [Element]
pSigD) Parser ([Element] -> Element) -> Parser [Element] -> Parser Element
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
brackets' Parser [Element]
pSigD
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> [Element] -> Element
DevNull ([Element] -> Element) -> Parser [Element] -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~DEVNULL" Parser String -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
brackets' Parser [Element]
pSigD)
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> [Element] -> Element
And ([Element] -> Element) -> Parser [Element] -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~AND" Parser String -> Parser [Element] -> Parser [Element]
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a
brackets' (Parser Element -> Parser [Element]
forall (m :: Type -> Type) a. TokenParsing m => m a -> m [a]
commaSep Parser Element
pTagE))
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
Vars (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~VARS" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
Tag (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~TAG" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
Period (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~PERIOD" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> ActiveEdge -> Int -> Element
ActiveEdge (ActiveEdge -> Int -> Element)
-> Parser ActiveEdge -> Parser (Int -> Element)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ACTIVEEDGE" Parser String -> Parser ActiveEdge -> Parser ActiveEdge
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser ActiveEdge -> Parser ActiveEdge
forall (m :: Type -> Type) a. TokenParsing m => m a -> m a
brackets Parser ActiveEdge
pEdge) Parser (Int -> Element) -> Parser Int -> Parser Element
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural'
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
IsSync (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ISSYNC" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Int -> Element
IsInitDefined (Int -> Element) -> Parser Int -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~ISINITDEFINED" Parser String -> Parser Int -> Parser Int
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser Int -> Parser Int
forall a. Parser a -> Parser a
brackets' Parser Int
forall (m :: Type -> Type). TokenParsing m => m Int
natural')
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Element
CtxName Element -> Parser String -> Parser Element
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~CTXNAME"
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Element
LongestPeriod Element -> Parser String -> Parser Element
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"~LONGESTPERIOD"
natural' :: TokenParsing m => m Int
natural' :: forall (m :: Type -> Type). TokenParsing m => m Int
natural' = (Integer -> Int) -> m Integer -> m Int
forall a b. (a -> b) -> m a -> m b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> Int
forall a. Num a => Integer -> a
fromInteger m Integer
forall (m :: Type -> Type). TokenParsing m => m Integer
natural
brackets' :: Parser a -> Parser a
brackets' :: forall a. Parser a -> Parser a
brackets' Parser a
p = Char -> Parser Char
forall (m :: Type -> Type). CharParsing m => Char -> m Char
char Char
'[' Parser Char -> Parser a -> Parser a
forall a b. Parser a -> Parser b -> Parser b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Parser a
p Parser a -> Parser Char -> Parser a
forall a b. Parser a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Char -> Parser Char
forall (m :: Type -> Type). CharParsing m => Char -> m Char
char Char
']'
pBlackBoxE :: Parser BlackBoxTemplate
pBlackBoxE :: Parser [Element]
pBlackBoxE = Parser Element -> Parser [Element]
forall a. Parser a -> Parser [a]
forall (f :: Type -> Type) a. Alternative f => f a -> f [a]
some Parser Element
pElemE
pElemE :: Parser Element
pElemE :: Parser Element
pElemE = Parser Element
pTagE
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Text -> Element
Text (Text -> Element) -> Parser Text -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text
pText
pSigD :: Parser [Element]
pSigD :: Parser [Element]
pSigD = Parser Element -> Parser [Element]
forall a. Parser a -> Parser [a]
forall (f :: Type -> Type) a. Alternative f => f a -> f [a]
some (Parser Element
pTagE Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> (EscapedSymbol -> Element
EscapedSymbol EscapedSymbol
SquareBracketOpen Element -> Parser String -> Parser Element
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"[\\")
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> (EscapedSymbol -> Element
EscapedSymbol EscapedSymbol
SquareBracketClose Element -> Parser String -> Parser Element
forall a b. a -> Parser b -> Parser a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ String -> Parser String
forall (m :: Type -> Type). CharParsing m => String -> m String
string String
"\\]")
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> (Text -> Element
Text (Text -> Element) -> Parser Text -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Text
pack (String -> Text) -> Parser String -> Parser Text
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Char -> Parser String
forall a. Parser a -> Parser [a]
forall (f :: Type -> Type) a. Alternative f => f a -> f [a]
some (Char -> Char -> Parser Char
forall (m :: Type -> Type). CharParsing m => Char -> Char -> m Char
satisfyRange Char
'\000' Char
'\90')))
Parser Element -> Parser Element -> Parser Element
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> (Text -> Element
Text (Text -> Element) -> Parser Text -> Parser Element
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Text
pack (String -> Text) -> Parser String -> Parser Text
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Char -> Parser String
forall a. Parser a -> Parser [a]
forall (f :: Type -> Type) a. Alternative f => f a -> f [a]
some (Char -> Char -> Parser Char
forall (m :: Type -> Type). CharParsing m => Char -> Char -> m Char
satisfyRange Char
'\94' Char
'\125'))))
pSigDorEmpty :: Parser [Element]
pSigDorEmpty :: Parser [Element]
pSigDorEmpty = Parser [Element]
pSigD Parser [Element] -> Parser [Element] -> Parser [Element]
forall a. Parser a -> Parser a -> Parser a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
<|> Parser [Element]
forall a. Monoid a => a
mempty