{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
module Parser.Procedure (
MarkType(..),
PragmaExpr(..),
PragmaStatement(..),
pragmaExprLookup,
pragmaHidden,
pragmaNoTrace,
pragmaReadOnly,
pragmaSourceContext,
pragmaTraceCreation,
) where
import Control.Monad (when)
import qualified Data.Set as Set
import Base.CompilerError
import Base.Positional
import Parser.Common
import Parser.Pragma
import Parser.TextParser
import Parser.TypeCategory ()
import Parser.TypeInstance ()
import Types.Procedure
import Types.TypeCategory
instance ParseFromSource (ExecutableProcedure SourceContext) where
sourceParser :: TextParser (ExecutableProcedure SourceContext)
sourceParser = String
-> TextParser (ExecutableProcedure SourceContext)
-> TextParser (ExecutableProcedure SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"executable procedure" (TextParser (ExecutableProcedure SourceContext)
-> TextParser (ExecutableProcedure SourceContext))
-> TextParser (ExecutableProcedure SourceContext)
-> TextParser (ExecutableProcedure SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
FunctionName
n <- ParsecT CompilerMessage String Identity FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT CompilerMessage String Identity FunctionName
forall a. ParseFromSource a => TextParser a
sourceParser
ArgValues SourceContext
as <- TextParser (ArgValues SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
ReturnValues SourceContext
rs <- TextParser (ReturnValues SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (String -> TextParser ()
string_ String
"{")
[PragmaProcedure SourceContext]
pragmas <- [TextParser (PragmaProcedure SourceContext)]
-> TextParser [PragmaProcedure SourceContext]
forall a. [TextParser a] -> TextParser [a]
parsePragmas [TextParser (PragmaProcedure SourceContext)
pragmaNoTrace,TextParser (PragmaProcedure SourceContext)
pragmaTraceCreation]
Procedure SourceContext
pp <- TextParser (Procedure SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
SourceContext
c2 <- TextParser SourceContext
getSourceContext
TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (String -> TextParser ()
string_ String
"}")
ExecutableProcedure SourceContext
-> TextParser (ExecutableProcedure SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExecutableProcedure SourceContext
-> TextParser (ExecutableProcedure SourceContext))
-> ExecutableProcedure SourceContext
-> TextParser (ExecutableProcedure SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> [PragmaProcedure SourceContext]
-> [SourceContext]
-> FunctionName
-> ArgValues SourceContext
-> ReturnValues SourceContext
-> Procedure SourceContext
-> ExecutableProcedure SourceContext
forall c.
[c]
-> [PragmaProcedure c]
-> [c]
-> FunctionName
-> ArgValues c
-> ReturnValues c
-> Procedure c
-> ExecutableProcedure c
ExecutableProcedure [SourceContext
c] [PragmaProcedure SourceContext]
pragmas [SourceContext
c2] FunctionName
n ArgValues SourceContext
as ReturnValues SourceContext
rs Procedure SourceContext
pp
instance ParseFromSource (TestProcedure SourceContext) where
sourceParser :: TextParser (TestProcedure SourceContext)
sourceParser = String
-> TextParser (TestProcedure SourceContext)
-> TextParser (TestProcedure SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"test procedure" (TextParser (TestProcedure SourceContext)
-> TextParser (TestProcedure SourceContext))
-> TextParser (TestProcedure SourceContext)
-> TextParser (TestProcedure SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
kwUnittest
FunctionName
n <- ParsecT CompilerMessage String Identity FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT CompilerMessage String Identity FunctionName
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (String -> TextParser ()
string_ String
"{")
Procedure SourceContext
pp <- TextParser (Procedure SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (String -> TextParser ()
string_ String
"}")
TestProcedure SourceContext
-> TextParser (TestProcedure SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (TestProcedure SourceContext
-> TextParser (TestProcedure SourceContext))
-> TestProcedure SourceContext
-> TextParser (TestProcedure SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> FunctionName
-> Procedure SourceContext
-> TestProcedure SourceContext
forall c. [c] -> FunctionName -> Procedure c -> TestProcedure c
TestProcedure [SourceContext
c] FunctionName
n Procedure SourceContext
pp
instance ParseFromSource (ArgValues SourceContext) where
sourceParser :: TextParser (ArgValues SourceContext)
sourceParser = String
-> TextParser (ArgValues SourceContext)
-> TextParser (ArgValues SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"procedure arguments" (TextParser (ArgValues SourceContext)
-> TextParser (ArgValues SourceContext))
-> TextParser (ArgValues SourceContext)
-> TextParser (ArgValues SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
[InputValue SourceContext]
as <- TextParser ()
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [InputValue SourceContext]
-> ParsecT
CompilerMessage String Identity [InputValue SourceContext]
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"(")
(TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
")")
(ParsecT CompilerMessage String Identity (InputValue SourceContext)
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [InputValue SourceContext]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy ParsecT CompilerMessage String Identity (InputValue SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
","))
ArgValues SourceContext -> TextParser (ArgValues SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ArgValues SourceContext -> TextParser (ArgValues SourceContext))
-> ArgValues SourceContext -> TextParser (ArgValues SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Positional (InputValue SourceContext) -> ArgValues SourceContext
forall c. [c] -> Positional (InputValue c) -> ArgValues c
ArgValues [SourceContext
c] ([InputValue SourceContext] -> Positional (InputValue SourceContext)
forall a. [a] -> Positional a
Positional [InputValue SourceContext]
as)
instance ParseFromSource (ReturnValues SourceContext) where
sourceParser :: TextParser (ReturnValues SourceContext)
sourceParser = String
-> TextParser (ReturnValues SourceContext)
-> TextParser (ReturnValues SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"procedure returns" (TextParser (ReturnValues SourceContext)
-> TextParser (ReturnValues SourceContext))
-> TextParser (ReturnValues SourceContext)
-> TextParser (ReturnValues SourceContext)
forall a b. (a -> b) -> a -> b
$ TextParser (ReturnValues SourceContext)
namedReturns TextParser (ReturnValues SourceContext)
-> TextParser (ReturnValues SourceContext)
-> TextParser (ReturnValues SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (ReturnValues SourceContext)
unnamedReturns where
namedReturns :: TextParser (ReturnValues SourceContext)
namedReturns = do
SourceContext
c <- TextParser SourceContext
getSourceContext
[OutputValue SourceContext]
rs <- TextParser ()
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [OutputValue SourceContext]
-> ParsecT
CompilerMessage String Identity [OutputValue SourceContext]
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"(")
(TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
")")
(ParsecT CompilerMessage String Identity (OutputValue SourceContext)
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [OutputValue SourceContext]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy ParsecT CompilerMessage String Identity (OutputValue SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
","))
ReturnValues SourceContext
-> TextParser (ReturnValues SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ReturnValues SourceContext
-> TextParser (ReturnValues SourceContext))
-> ReturnValues SourceContext
-> TextParser (ReturnValues SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Positional (OutputValue SourceContext)
-> ReturnValues SourceContext
forall c. [c] -> Positional (OutputValue c) -> ReturnValues c
NamedReturns [SourceContext
c] ([OutputValue SourceContext]
-> Positional (OutputValue SourceContext)
forall a. [a] -> Positional a
Positional [OutputValue SourceContext]
rs)
unnamedReturns :: TextParser (ReturnValues SourceContext)
unnamedReturns = do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser () -> TextParser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy (String -> TextParser ()
string_ String
"(")
ReturnValues SourceContext
-> TextParser (ReturnValues SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ReturnValues SourceContext
-> TextParser (ReturnValues SourceContext))
-> ReturnValues SourceContext
-> TextParser (ReturnValues SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> ReturnValues SourceContext
forall c. [c] -> ReturnValues c
UnnamedReturns [SourceContext
c]
instance ParseFromSource VariableName where
sourceParser :: TextParser VariableName
sourceParser = String -> TextParser VariableName -> TextParser VariableName
forall a. String -> TextParser a -> TextParser a
labeled String
"variable name" (TextParser VariableName -> TextParser VariableName)
-> TextParser VariableName -> TextParser VariableName
forall a b. (a -> b) -> a -> b
$ do
TextParser ()
noKeywords
Char
b <- ParsecT CompilerMessage String Identity Char
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
lowerChar
String
e <- TextParser String -> TextParser String
forall a. TextParser a -> TextParser a
sepAfter (TextParser String -> TextParser String)
-> TextParser String -> TextParser String
forall a b. (a -> b) -> a -> b
$ ParsecT CompilerMessage String Identity Char -> TextParser String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many ParsecT CompilerMessage String Identity Char
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
alphaNumChar
VariableName -> TextParser VariableName
forall (m :: * -> *) a. Monad m => a -> m a
return (VariableName -> TextParser VariableName)
-> VariableName -> TextParser VariableName
forall a b. (a -> b) -> a -> b
$ String -> VariableName
VariableName (Char
bChar -> String -> String
forall a. a -> [a] -> [a]
:String
e)
instance ParseFromSource (InputValue SourceContext) where
sourceParser :: ParsecT CompilerMessage String Identity (InputValue SourceContext)
sourceParser = String
-> ParsecT
CompilerMessage String Identity (InputValue SourceContext)
-> ParsecT
CompilerMessage String Identity (InputValue SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"input variable" (ParsecT CompilerMessage String Identity (InputValue SourceContext)
-> ParsecT
CompilerMessage String Identity (InputValue SourceContext))
-> ParsecT
CompilerMessage String Identity (InputValue SourceContext)
-> ParsecT
CompilerMessage String Identity (InputValue SourceContext)
forall a b. (a -> b) -> a -> b
$ ParsecT CompilerMessage String Identity (InputValue SourceContext)
variable ParsecT CompilerMessage String Identity (InputValue SourceContext)
-> ParsecT
CompilerMessage String Identity (InputValue SourceContext)
-> ParsecT
CompilerMessage String Identity (InputValue SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT CompilerMessage String Identity (InputValue SourceContext)
discard where
variable :: ParsecT CompilerMessage String Identity (InputValue SourceContext)
variable = do
SourceContext
c <- TextParser SourceContext
getSourceContext
VariableName
v <- TextParser VariableName
forall a. ParseFromSource a => TextParser a
sourceParser
InputValue SourceContext
-> ParsecT
CompilerMessage String Identity (InputValue SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (InputValue SourceContext
-> ParsecT
CompilerMessage String Identity (InputValue SourceContext))
-> InputValue SourceContext
-> ParsecT
CompilerMessage String Identity (InputValue SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> VariableName -> InputValue SourceContext
forall c. [c] -> VariableName -> InputValue c
InputValue [SourceContext
c] VariableName
v
discard :: ParsecT CompilerMessage String Identity (InputValue SourceContext)
discard = do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (String -> TextParser ()
string_ String
"_")
InputValue SourceContext
-> ParsecT
CompilerMessage String Identity (InputValue SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (InputValue SourceContext
-> ParsecT
CompilerMessage String Identity (InputValue SourceContext))
-> InputValue SourceContext
-> ParsecT
CompilerMessage String Identity (InputValue SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> InputValue SourceContext
forall c. [c] -> InputValue c
DiscardInput [SourceContext
c]
instance ParseFromSource (OutputValue SourceContext) where
sourceParser :: ParsecT CompilerMessage String Identity (OutputValue SourceContext)
sourceParser = String
-> ParsecT
CompilerMessage String Identity (OutputValue SourceContext)
-> ParsecT
CompilerMessage String Identity (OutputValue SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"output variable" (ParsecT
CompilerMessage String Identity (OutputValue SourceContext)
-> ParsecT
CompilerMessage String Identity (OutputValue SourceContext))
-> ParsecT
CompilerMessage String Identity (OutputValue SourceContext)
-> ParsecT
CompilerMessage String Identity (OutputValue SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
VariableName
v <- TextParser VariableName
forall a. ParseFromSource a => TextParser a
sourceParser
OutputValue SourceContext
-> ParsecT
CompilerMessage String Identity (OutputValue SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (OutputValue SourceContext
-> ParsecT
CompilerMessage String Identity (OutputValue SourceContext))
-> OutputValue SourceContext
-> ParsecT
CompilerMessage String Identity (OutputValue SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> VariableName -> OutputValue SourceContext
forall c. [c] -> VariableName -> OutputValue c
OutputValue [SourceContext
c] VariableName
v
instance ParseFromSource (Procedure SourceContext) where
sourceParser :: TextParser (Procedure SourceContext)
sourceParser = String
-> TextParser (Procedure SourceContext)
-> TextParser (Procedure SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"procedure" (TextParser (Procedure SourceContext)
-> TextParser (Procedure SourceContext))
-> TextParser (Procedure SourceContext)
-> TextParser (Procedure SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
[Statement SourceContext]
rs <- ParsecT CompilerMessage String Identity (Statement SourceContext)
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [Statement SourceContext]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy ParsecT CompilerMessage String Identity (Statement SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser TextParser ()
optionalSpace
Procedure SourceContext -> TextParser (Procedure SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Procedure SourceContext -> TextParser (Procedure SourceContext))
-> Procedure SourceContext -> TextParser (Procedure SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> [Statement SourceContext] -> Procedure SourceContext
forall c. [c] -> [Statement c] -> Procedure c
Procedure [SourceContext
c] [Statement SourceContext]
rs
instance ParseFromSource (Statement SourceContext) where
sourceParser :: ParsecT CompilerMessage String Identity (Statement SourceContext)
sourceParser = ParsecT CompilerMessage String Identity (Statement SourceContext)
parseReturn ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
ParsecT CompilerMessage String Identity (Statement SourceContext)
parseBreak ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
ParsecT CompilerMessage String Identity (Statement SourceContext)
parseContinue ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
ParsecT CompilerMessage String Identity (Statement SourceContext)
parseFailCall ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
ParsecT CompilerMessage String Identity (Statement SourceContext)
parseVoid ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
ParsecT CompilerMessage String Identity (Statement SourceContext)
parseAssign ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
ParsecT CompilerMessage String Identity (Statement SourceContext)
parsePragma ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
ParsecT CompilerMessage String Identity (Statement SourceContext)
parseIgnore where
parseAssign :: ParsecT CompilerMessage String Identity (Statement SourceContext)
parseAssign = String
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"statement" (ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
[Assignable SourceContext]
as <- ParsecT CompilerMessage String Identity (Assignable SourceContext)
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [Assignable SourceContext]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy ParsecT CompilerMessage String Identity (Assignable SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
",")
TextParser ()
assignOperator
Expression SourceContext
e <- TextParser (Expression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser ()
statementEnd
Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Positional (Assignable SourceContext)
-> Expression SourceContext
-> Statement SourceContext
forall c.
[c] -> Positional (Assignable c) -> Expression c -> Statement c
Assignment [SourceContext
c] ([Assignable SourceContext] -> Positional (Assignable SourceContext)
forall a. [a] -> Positional a
Positional [Assignable SourceContext]
as) Expression SourceContext
e
parseBreak :: ParsecT CompilerMessage String Identity (Statement SourceContext)
parseBreak = String
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"break" (ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
kwBreak
Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> Statement SourceContext
forall c. [c] -> Statement c
LoopBreak [SourceContext
c]
parseContinue :: ParsecT CompilerMessage String Identity (Statement SourceContext)
parseContinue = String
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"continue" (ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
kwContinue
Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> Statement SourceContext
forall c. [c] -> Statement c
LoopContinue [SourceContext
c]
parseFailCall :: ParsecT CompilerMessage String Identity (Statement SourceContext)
parseFailCall = do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
kwFail
Expression SourceContext
e <- TextParser ()
-> TextParser ()
-> TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"(") (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
")") TextParser (Expression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Expression SourceContext -> Statement SourceContext
forall c. [c] -> Expression c -> Statement c
FailCall [SourceContext
c] Expression SourceContext
e
parseIgnore :: ParsecT CompilerMessage String Identity (Statement SourceContext)
parseIgnore = do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
statementStart
Expression SourceContext
e <- TextParser (Expression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser ()
statementEnd
Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Expression SourceContext -> Statement SourceContext
forall c. [c] -> Expression c -> Statement c
IgnoreValues [SourceContext
c] Expression SourceContext
e
parseReturn :: ParsecT CompilerMessage String Identity (Statement SourceContext)
parseReturn = String
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"return" (ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
kwReturn
SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
emptyReturn SourceContext
c ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
multiReturn SourceContext
c
multiReturn :: SourceContext -> TextParser (Statement SourceContext)
multiReturn :: SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
multiReturn SourceContext
c = do
[Expression SourceContext]
rs <- TextParser (Expression SourceContext)
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [Expression SourceContext]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy TextParser (Expression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
",")
TextParser ()
statementEnd
Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Positional (Expression SourceContext) -> Statement SourceContext
forall c. [c] -> Positional (Expression c) -> Statement c
ExplicitReturn [SourceContext
c] ([Expression SourceContext] -> Positional (Expression SourceContext)
forall a. [a] -> Positional a
Positional [Expression SourceContext]
rs)
emptyReturn :: SourceContext -> TextParser (Statement SourceContext)
emptyReturn :: SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
emptyReturn SourceContext
c = do
TextParser ()
kwIgnore
TextParser ()
statementEnd
Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> Statement SourceContext
forall c. [c] -> Statement c
EmptyReturn [SourceContext
c]
parseVoid :: ParsecT CompilerMessage String Identity (Statement SourceContext)
parseVoid = do
SourceContext
c <- TextParser SourceContext
getSourceContext
VoidExpression SourceContext
e <- TextParser (VoidExpression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> VoidExpression SourceContext -> Statement SourceContext
forall c. [c] -> VoidExpression c -> Statement c
NoValueExpression [SourceContext
c] VoidExpression SourceContext
e
parsePragma :: ParsecT CompilerMessage String Identity (Statement SourceContext)
parsePragma = do
PragmaStatement SourceContext
p <- TextParser (PragmaStatement SourceContext)
pragmaReadOnly TextParser (PragmaStatement SourceContext)
-> TextParser (PragmaStatement SourceContext)
-> TextParser (PragmaStatement SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (PragmaStatement SourceContext)
pragmaHidden TextParser (PragmaStatement SourceContext)
-> TextParser (PragmaStatement SourceContext)
-> TextParser (PragmaStatement SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (PragmaStatement SourceContext)
forall a. TextParser a
unknownPragma
case PragmaStatement SourceContext
p of
PragmaMarkVars [SourceContext]
c MarkType
ReadOnly [VariableName]
vs -> Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> [VariableName] -> Statement SourceContext
forall c. [c] -> [VariableName] -> Statement c
MarkReadOnly [SourceContext]
c [VariableName]
vs
PragmaMarkVars [SourceContext]
c MarkType
Hidden [VariableName]
vs -> Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> [VariableName] -> Statement SourceContext
forall c. [c] -> [VariableName] -> Statement c
MarkHidden [SourceContext]
c [VariableName]
vs
instance ParseFromSource (Assignable SourceContext) where
sourceParser :: ParsecT CompilerMessage String Identity (Assignable SourceContext)
sourceParser = ParsecT CompilerMessage String Identity (Assignable SourceContext)
existing ParsecT CompilerMessage String Identity (Assignable SourceContext)
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT CompilerMessage String Identity (Assignable SourceContext)
create where
create :: ParsecT CompilerMessage String Identity (Assignable SourceContext)
create = String
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"variable creation" (ParsecT CompilerMessage String Identity (Assignable SourceContext)
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext))
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
forall a b. (a -> b) -> a -> b
$ do
ValueType
t <- TextParser ValueType
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser ()
forall a. TextParser a
strayFuncCall TextParser () -> TextParser () -> TextParser ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> () -> TextParser ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
SourceContext
c <- TextParser SourceContext
getSourceContext
VariableName
n <- TextParser VariableName
forall a. ParseFromSource a => TextParser a
sourceParser
Assignable SourceContext
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Assignable SourceContext
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext))
-> Assignable SourceContext
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> ValueType -> VariableName -> Assignable SourceContext
forall c. [c] -> ValueType -> VariableName -> Assignable c
CreateVariable [SourceContext
c] ValueType
t VariableName
n
existing :: ParsecT CompilerMessage String Identity (Assignable SourceContext)
existing = String
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"variable name" (ParsecT CompilerMessage String Identity (Assignable SourceContext)
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext))
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
forall a b. (a -> b) -> a -> b
$ do
InputValue SourceContext
n <- ParsecT CompilerMessage String Identity (InputValue SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser ()
forall a. TextParser a
strayFuncCall TextParser () -> TextParser () -> TextParser ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> () -> TextParser ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Assignable SourceContext
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Assignable SourceContext
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext))
-> Assignable SourceContext
-> ParsecT
CompilerMessage String Identity (Assignable SourceContext)
forall a b. (a -> b) -> a -> b
$ InputValue SourceContext -> Assignable SourceContext
forall c. InputValue c -> Assignable c
ExistingVariable InputValue SourceContext
n
strayFuncCall :: ParsecT CompilerMessage String Identity b
strayFuncCall = do
TextParser ()
valueSymbolGet TextParser () -> TextParser () -> TextParser ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser ()
typeSymbolGet TextParser () -> TextParser () -> TextParser ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser ()
categorySymbolGet
String -> ParsecT CompilerMessage String Identity b
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM String
"function returns must be explicitly handled"
instance ParseFromSource (VoidExpression SourceContext) where
sourceParser :: TextParser (VoidExpression SourceContext)
sourceParser = TextParser (VoidExpression SourceContext)
conditional TextParser (VoidExpression SourceContext)
-> TextParser (VoidExpression SourceContext)
-> TextParser (VoidExpression SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (VoidExpression SourceContext)
loop TextParser (VoidExpression SourceContext)
-> TextParser (VoidExpression SourceContext)
-> TextParser (VoidExpression SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (VoidExpression SourceContext)
scoped where
conditional :: TextParser (VoidExpression SourceContext)
conditional = do
IfElifElse SourceContext
e <- TextParser (IfElifElse SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
VoidExpression SourceContext
-> TextParser (VoidExpression SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (VoidExpression SourceContext
-> TextParser (VoidExpression SourceContext))
-> VoidExpression SourceContext
-> TextParser (VoidExpression SourceContext)
forall a b. (a -> b) -> a -> b
$ IfElifElse SourceContext -> VoidExpression SourceContext
forall c. IfElifElse c -> VoidExpression c
Conditional IfElifElse SourceContext
e
loop :: TextParser (VoidExpression SourceContext)
loop = do
IteratedLoop SourceContext
e <- TextParser (IteratedLoop SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
VoidExpression SourceContext
-> TextParser (VoidExpression SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (VoidExpression SourceContext
-> TextParser (VoidExpression SourceContext))
-> VoidExpression SourceContext
-> TextParser (VoidExpression SourceContext)
forall a b. (a -> b) -> a -> b
$ IteratedLoop SourceContext -> VoidExpression SourceContext
forall c. IteratedLoop c -> VoidExpression c
Loop IteratedLoop SourceContext
e
scoped :: TextParser (VoidExpression SourceContext)
scoped = do
ScopedBlock SourceContext
e <- TextParser (ScopedBlock SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
VoidExpression SourceContext
-> TextParser (VoidExpression SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (VoidExpression SourceContext
-> TextParser (VoidExpression SourceContext))
-> VoidExpression SourceContext
-> TextParser (VoidExpression SourceContext)
forall a b. (a -> b) -> a -> b
$ ScopedBlock SourceContext -> VoidExpression SourceContext
forall c. ScopedBlock c -> VoidExpression c
WithScope ScopedBlock SourceContext
e
instance ParseFromSource (IfElifElse SourceContext) where
sourceParser :: TextParser (IfElifElse SourceContext)
sourceParser = String
-> TextParser (IfElifElse SourceContext)
-> TextParser (IfElifElse SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"if-elif-else" (TextParser (IfElifElse SourceContext)
-> TextParser (IfElifElse SourceContext))
-> TextParser (IfElifElse SourceContext)
-> TextParser (IfElifElse SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
kwIf TextParser ()
-> TextParser (IfElifElse SourceContext)
-> TextParser (IfElifElse SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> SourceContext -> TextParser (IfElifElse SourceContext)
parseIf SourceContext
c
where
parseIf :: SourceContext -> TextParser (IfElifElse SourceContext)
parseIf SourceContext
c = do
Expression SourceContext
i <- TextParser ()
-> TextParser ()
-> TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"(") (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
")") TextParser (Expression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
Procedure SourceContext
p <- TextParser ()
-> TextParser ()
-> TextParser (Procedure SourceContext)
-> TextParser (Procedure SourceContext)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"{") (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"}") TextParser (Procedure SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
IfElifElse SourceContext
next <- TextParser (IfElifElse SourceContext)
parseElif TextParser (IfElifElse SourceContext)
-> TextParser (IfElifElse SourceContext)
-> TextParser (IfElifElse SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (IfElifElse SourceContext)
parseElse TextParser (IfElifElse SourceContext)
-> TextParser (IfElifElse SourceContext)
-> TextParser (IfElifElse SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> IfElifElse SourceContext -> TextParser (IfElifElse SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return IfElifElse SourceContext
forall c. IfElifElse c
TerminateConditional
IfElifElse SourceContext -> TextParser (IfElifElse SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (IfElifElse SourceContext -> TextParser (IfElifElse SourceContext))
-> IfElifElse SourceContext
-> TextParser (IfElifElse SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Expression SourceContext
-> Procedure SourceContext
-> IfElifElse SourceContext
-> IfElifElse SourceContext
forall c.
[c] -> Expression c -> Procedure c -> IfElifElse c -> IfElifElse c
IfStatement [SourceContext
c] Expression SourceContext
i Procedure SourceContext
p IfElifElse SourceContext
next
parseElif :: TextParser (IfElifElse SourceContext)
parseElif = do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
kwElif TextParser ()
-> TextParser (IfElifElse SourceContext)
-> TextParser (IfElifElse SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> SourceContext -> TextParser (IfElifElse SourceContext)
parseIf SourceContext
c
parseElse :: TextParser (IfElifElse SourceContext)
parseElse = do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
kwElse
Procedure SourceContext
p <- TextParser ()
-> TextParser ()
-> TextParser (Procedure SourceContext)
-> TextParser (Procedure SourceContext)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"{") (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"}") TextParser (Procedure SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
IfElifElse SourceContext -> TextParser (IfElifElse SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (IfElifElse SourceContext -> TextParser (IfElifElse SourceContext))
-> IfElifElse SourceContext
-> TextParser (IfElifElse SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Procedure SourceContext -> IfElifElse SourceContext
forall c. [c] -> Procedure c -> IfElifElse c
ElseStatement [SourceContext
c] Procedure SourceContext
p
instance ParseFromSource (IteratedLoop SourceContext) where
sourceParser :: TextParser (IteratedLoop SourceContext)
sourceParser = TextParser (IteratedLoop SourceContext)
while TextParser (IteratedLoop SourceContext)
-> TextParser (IteratedLoop SourceContext)
-> TextParser (IteratedLoop SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (IteratedLoop SourceContext)
trav where
while :: TextParser (IteratedLoop SourceContext)
while = String
-> TextParser (IteratedLoop SourceContext)
-> TextParser (IteratedLoop SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"while" (TextParser (IteratedLoop SourceContext)
-> TextParser (IteratedLoop SourceContext))
-> TextParser (IteratedLoop SourceContext)
-> TextParser (IteratedLoop SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
kwWhile
Expression SourceContext
i <- TextParser ()
-> TextParser ()
-> TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"(") (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
")") TextParser (Expression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
Procedure SourceContext
p <- TextParser ()
-> TextParser ()
-> TextParser (Procedure SourceContext)
-> TextParser (Procedure SourceContext)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"{") (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"}") TextParser (Procedure SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
Maybe (Procedure SourceContext)
u <- (Procedure SourceContext -> Maybe (Procedure SourceContext))
-> TextParser (Procedure SourceContext)
-> ParsecT
CompilerMessage String Identity (Maybe (Procedure SourceContext))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Procedure SourceContext -> Maybe (Procedure SourceContext)
forall a. a -> Maybe a
Just TextParser (Procedure SourceContext)
parseUpdate ParsecT
CompilerMessage String Identity (Maybe (Procedure SourceContext))
-> ParsecT
CompilerMessage String Identity (Maybe (Procedure SourceContext))
-> ParsecT
CompilerMessage String Identity (Maybe (Procedure SourceContext))
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe (Procedure SourceContext)
-> ParsecT
CompilerMessage String Identity (Maybe (Procedure SourceContext))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Procedure SourceContext)
forall a. Maybe a
Nothing
IteratedLoop SourceContext
-> TextParser (IteratedLoop SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (IteratedLoop SourceContext
-> TextParser (IteratedLoop SourceContext))
-> IteratedLoop SourceContext
-> TextParser (IteratedLoop SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Expression SourceContext
-> Procedure SourceContext
-> Maybe (Procedure SourceContext)
-> IteratedLoop SourceContext
forall c.
[c]
-> Expression c
-> Procedure c
-> Maybe (Procedure c)
-> IteratedLoop c
WhileLoop [SourceContext
c] Expression SourceContext
i Procedure SourceContext
p Maybe (Procedure SourceContext)
u
where
parseUpdate :: TextParser (Procedure SourceContext)
parseUpdate = do
TextParser ()
kwUpdate
TextParser ()
-> TextParser ()
-> TextParser (Procedure SourceContext)
-> TextParser (Procedure SourceContext)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"{") (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"}") TextParser (Procedure SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
trav :: TextParser (IteratedLoop SourceContext)
trav = String
-> TextParser (IteratedLoop SourceContext)
-> TextParser (IteratedLoop SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"traverse" (TextParser (IteratedLoop SourceContext)
-> TextParser (IteratedLoop SourceContext))
-> TextParser (IteratedLoop SourceContext)
-> TextParser (IteratedLoop SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c1 <- TextParser SourceContext
getSourceContext
TextParser ()
kwTraverse
TextParser String -> TextParser ()
forall a. TextParser a -> TextParser ()
sepAfter_ (TextParser String -> TextParser ())
-> TextParser String -> TextParser ()
forall a b. (a -> b) -> a -> b
$ Tokens String
-> ParsecT CompilerMessage String Identity (Tokens String)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string String
Tokens String
"("
Expression SourceContext
e <- TextParser (Expression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser String -> TextParser ()
forall a. TextParser a -> TextParser ()
sepAfter_ (TextParser String -> TextParser ())
-> TextParser String -> TextParser ()
forall a b. (a -> b) -> a -> b
$ Tokens String
-> ParsecT CompilerMessage String Identity (Tokens String)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string String
Tokens String
"->"
SourceContext
c2 <- TextParser SourceContext
getSourceContext
Assignable SourceContext
a <- ParsecT CompilerMessage String Identity (Assignable SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser String -> TextParser ()
forall a. TextParser a -> TextParser ()
sepAfter_ (TextParser String -> TextParser ())
-> TextParser String -> TextParser ()
forall a b. (a -> b) -> a -> b
$ Tokens String
-> ParsecT CompilerMessage String Identity (Tokens String)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string String
Tokens String
")"
Procedure SourceContext
p <- TextParser ()
-> TextParser ()
-> TextParser (Procedure SourceContext)
-> TextParser (Procedure SourceContext)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"{") (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"}") TextParser (Procedure SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
IteratedLoop SourceContext
-> TextParser (IteratedLoop SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (IteratedLoop SourceContext
-> TextParser (IteratedLoop SourceContext))
-> IteratedLoop SourceContext
-> TextParser (IteratedLoop SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Expression SourceContext
-> [SourceContext]
-> Assignable SourceContext
-> Procedure SourceContext
-> IteratedLoop SourceContext
forall c.
[c]
-> Expression c
-> [c]
-> Assignable c
-> Procedure c
-> IteratedLoop c
TraverseLoop [SourceContext
c1] Expression SourceContext
e [SourceContext
c2] Assignable SourceContext
a Procedure SourceContext
p
instance ParseFromSource (ScopedBlock SourceContext) where
sourceParser :: TextParser (ScopedBlock SourceContext)
sourceParser = TextParser (ScopedBlock SourceContext)
scoped TextParser (ScopedBlock SourceContext)
-> TextParser (ScopedBlock SourceContext)
-> TextParser (ScopedBlock SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (ScopedBlock SourceContext)
justCleanup where
scoped :: TextParser (ScopedBlock SourceContext)
scoped = String
-> TextParser (ScopedBlock SourceContext)
-> TextParser (ScopedBlock SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"scoped" (TextParser (ScopedBlock SourceContext)
-> TextParser (ScopedBlock SourceContext))
-> TextParser (ScopedBlock SourceContext)
-> TextParser (ScopedBlock SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
kwScoped
Procedure SourceContext
p <- TextParser ()
-> TextParser ()
-> TextParser (Procedure SourceContext)
-> TextParser (Procedure SourceContext)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"{") (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"}") TextParser (Procedure SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
Maybe (Procedure SourceContext)
cl <- (Procedure SourceContext -> Maybe (Procedure SourceContext))
-> TextParser (Procedure SourceContext)
-> ParsecT
CompilerMessage String Identity (Maybe (Procedure SourceContext))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Procedure SourceContext -> Maybe (Procedure SourceContext)
forall a. a -> Maybe a
Just TextParser (Procedure SourceContext)
parseCleanup ParsecT
CompilerMessage String Identity (Maybe (Procedure SourceContext))
-> ParsecT
CompilerMessage String Identity (Maybe (Procedure SourceContext))
-> ParsecT
CompilerMessage String Identity (Maybe (Procedure SourceContext))
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe (Procedure SourceContext)
-> ParsecT
CompilerMessage String Identity (Maybe (Procedure SourceContext))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Procedure SourceContext)
forall a. Maybe a
Nothing
TextParser ()
kwIn
SourceContext
c2 <- TextParser SourceContext
getSourceContext
Statement SourceContext
s <- ParsecT CompilerMessage String Identity (Statement SourceContext)
unconditional ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT CompilerMessage String Identity (Statement SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
ScopedBlock SourceContext -> TextParser (ScopedBlock SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ScopedBlock SourceContext
-> TextParser (ScopedBlock SourceContext))
-> ScopedBlock SourceContext
-> TextParser (ScopedBlock SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Procedure SourceContext
-> Maybe (Procedure SourceContext)
-> [SourceContext]
-> Statement SourceContext
-> ScopedBlock SourceContext
forall c.
[c]
-> Procedure c
-> Maybe (Procedure c)
-> [c]
-> Statement c
-> ScopedBlock c
ScopedBlock [SourceContext
c] Procedure SourceContext
p Maybe (Procedure SourceContext)
cl [SourceContext
c2] Statement SourceContext
s
justCleanup :: TextParser (ScopedBlock SourceContext)
justCleanup = do
SourceContext
c <- TextParser SourceContext
getSourceContext
Procedure SourceContext
cl <- TextParser (Procedure SourceContext)
parseCleanup
TextParser ()
kwIn
SourceContext
c2 <- TextParser SourceContext
getSourceContext
Statement SourceContext
s <- ParsecT CompilerMessage String Identity (Statement SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser ParsecT CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT CompilerMessage String Identity (Statement SourceContext)
unconditional
ScopedBlock SourceContext -> TextParser (ScopedBlock SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ScopedBlock SourceContext
-> TextParser (ScopedBlock SourceContext))
-> ScopedBlock SourceContext
-> TextParser (ScopedBlock SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Procedure SourceContext
-> Maybe (Procedure SourceContext)
-> [SourceContext]
-> Statement SourceContext
-> ScopedBlock SourceContext
forall c.
[c]
-> Procedure c
-> Maybe (Procedure c)
-> [c]
-> Statement c
-> ScopedBlock c
ScopedBlock [SourceContext
c] ([SourceContext]
-> [Statement SourceContext] -> Procedure SourceContext
forall c. [c] -> [Statement c] -> Procedure c
Procedure [] []) (Procedure SourceContext -> Maybe (Procedure SourceContext)
forall a. a -> Maybe a
Just Procedure SourceContext
cl) [SourceContext
c2] Statement SourceContext
s
parseCleanup :: TextParser (Procedure SourceContext)
parseCleanup = do
TextParser ()
kwCleanup
TextParser ()
-> TextParser ()
-> TextParser (Procedure SourceContext)
-> TextParser (Procedure SourceContext)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"{") (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"}") TextParser (Procedure SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
unconditional :: ParsecT CompilerMessage String Identity (Statement SourceContext)
unconditional = do
SourceContext
c <- TextParser SourceContext
getSourceContext
Procedure SourceContext
p <- TextParser ()
-> TextParser ()
-> TextParser (Procedure SourceContext)
-> TextParser (Procedure SourceContext)
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"{") (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"}") TextParser (Procedure SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext))
-> Statement SourceContext
-> ParsecT
CompilerMessage String Identity (Statement SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> VoidExpression SourceContext -> Statement SourceContext
forall c. [c] -> VoidExpression c -> Statement c
NoValueExpression [SourceContext
c] (Procedure SourceContext -> VoidExpression SourceContext
forall c. Procedure c -> VoidExpression c
Unconditional Procedure SourceContext
p)
unaryOperator :: TextParser (Operator SourceContext)
unaryOperator :: TextParser (Operator SourceContext)
unaryOperator = do
SourceContext
c <- TextParser SourceContext
getSourceContext
String
o <- TextParser String
op
Operator SourceContext -> TextParser (Operator SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Operator SourceContext -> TextParser (Operator SourceContext))
-> Operator SourceContext -> TextParser (Operator SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> String -> Operator SourceContext
forall c. [c] -> String -> Operator c
NamedOperator [SourceContext
c] String
o where
op :: TextParser String
op = String -> TextParser String -> TextParser String
forall a. String -> TextParser a -> TextParser a
labeled String
"unary operator" (TextParser String -> TextParser String)
-> TextParser String -> TextParser String
forall a b. (a -> b) -> a -> b
$ (TextParser String -> TextParser String -> TextParser String)
-> TextParser String -> [TextParser String] -> TextParser String
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr TextParser String -> TextParser String -> TextParser String
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>) TextParser String
forall (f :: * -> *) a. Alternative f => f a
empty ([TextParser String] -> TextParser String)
-> [TextParser String] -> TextParser String
forall a b. (a -> b) -> a -> b
$ (String -> TextParser String) -> [String] -> [TextParser String]
forall a b. (a -> b) -> [a] -> [b]
map (TextParser String -> TextParser String
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (TextParser String -> TextParser String)
-> (String -> TextParser String) -> String -> TextParser String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> TextParser String
operator) [String]
ops
ops :: [String]
ops = [String]
logicalUnary [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
arithUnary [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
bitwiseUnary
logicalUnary :: [String]
logicalUnary :: [String]
logicalUnary = [String
"!"]
arithUnary :: [String]
arithUnary :: [String]
arithUnary = [String
"-"]
bitwiseUnary :: [String]
bitwiseUnary :: [String]
bitwiseUnary = [String
"~"]
infixOperator :: TextParser (Operator SourceContext)
infixOperator :: TextParser (Operator SourceContext)
infixOperator = do
SourceContext
c <- TextParser SourceContext
getSourceContext
String
o <- TextParser String
op
Operator SourceContext -> TextParser (Operator SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Operator SourceContext -> TextParser (Operator SourceContext))
-> Operator SourceContext -> TextParser (Operator SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> String -> Operator SourceContext
forall c. [c] -> String -> Operator c
NamedOperator [SourceContext
c] String
o where
op :: TextParser String
op = String -> TextParser String -> TextParser String
forall a. String -> TextParser a -> TextParser a
labeled String
"binary operator" (TextParser String -> TextParser String)
-> TextParser String -> TextParser String
forall a b. (a -> b) -> a -> b
$ (TextParser String -> TextParser String -> TextParser String)
-> TextParser String -> [TextParser String] -> TextParser String
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr TextParser String -> TextParser String -> TextParser String
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>) TextParser String
forall (f :: * -> *) a. Alternative f => f a
empty ([TextParser String] -> TextParser String)
-> [TextParser String] -> TextParser String
forall a b. (a -> b) -> a -> b
$ (String -> TextParser String) -> [String] -> [TextParser String]
forall a b. (a -> b) -> [a] -> [b]
map (TextParser String -> TextParser String
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (TextParser String -> TextParser String)
-> (String -> TextParser String) -> String -> TextParser String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> TextParser String
operator) [String]
ops
ops :: [String]
ops = [String]
compareInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
logicalInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
addInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
subInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
multInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
divInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
bitwiseInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
bitshiftInfix
compareInfix :: [String]
compareInfix :: [String]
compareInfix = [String
"==",String
"!=",String
"<",String
"<=",String
">",String
">="]
logicalInfix :: [String]
logicalInfix :: [String]
logicalInfix = [String
"&&",String
"||"]
addInfix :: [String]
addInfix :: [String]
addInfix = [String
"+"]
subInfix :: [String]
subInfix :: [String]
subInfix = [String
"-"]
multInfix :: [String]
multInfix :: [String]
multInfix = [String
"*"]
divInfix :: [String]
divInfix :: [String]
divInfix = [String
"/",String
"%"]
bitwiseInfix :: [String]
bitwiseInfix :: [String]
bitwiseInfix = [String
"&",String
"|",String
"^"]
bitshiftInfix :: [String]
bitshiftInfix :: [String]
bitshiftInfix = [String
">>",String
"<<"]
leftAssocInfix :: [String]
leftAssocInfix :: [String]
leftAssocInfix = [String]
addInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
subInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
multInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
divInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
bitwiseInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
bitshiftInfix
rightAssocInfix :: [String]
rightAssocInfix :: [String]
rightAssocInfix = [String]
logicalInfix
nonAssocInfix :: [String]
nonAssocInfix :: [String]
nonAssocInfix = [String]
compareInfix
functionOperator :: TextParser (Operator SourceContext)
functionOperator :: TextParser (Operator SourceContext)
functionOperator = do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
infixFuncStart
FunctionSpec SourceContext
q <- TextParser (FunctionSpec SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser ()
infixFuncEnd
Operator SourceContext -> TextParser (Operator SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Operator SourceContext -> TextParser (Operator SourceContext))
-> Operator SourceContext -> TextParser (Operator SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> FunctionSpec SourceContext -> Operator SourceContext
forall c. [c] -> FunctionSpec c -> Operator c
FunctionOperator [SourceContext
c] FunctionSpec SourceContext
q
inOperatorSet :: Operator c -> [String] -> Bool
inOperatorSet :: Operator c -> [String] -> Bool
inOperatorSet (NamedOperator [c]
_ String
o) [String]
ss = String
o String -> Set String -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` [String] -> Set String
forall a. Ord a => [a] -> Set a
Set.fromList [String]
ss
inOperatorSet Operator c
_ [String]
_ = Bool
False
bothInOperatorSet :: Operator c -> Operator c -> [String] -> Bool
bothInOperatorSet :: Operator c -> Operator c -> [String] -> Bool
bothInOperatorSet Operator c
o1 Operator c
o2 [String]
ss = Operator c
o1 Operator c -> [String] -> Bool
forall c. Operator c -> [String] -> Bool
`inOperatorSet` [String]
ss Bool -> Bool -> Bool
&& Operator c
o2 Operator c -> [String] -> Bool
forall c. Operator c -> [String] -> Bool
`inOperatorSet` [String]
ss
infixPrecedence :: Operator c -> Int
infixPrecedence :: Operator c -> Int
infixPrecedence Operator c
o
| Operator c
o Operator c -> [String] -> Bool
forall c. Operator c -> [String] -> Bool
`inOperatorSet` ([String]
multInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
divInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
bitshiftInfix) = Int
1
| Operator c
o Operator c -> [String] -> Bool
forall c. Operator c -> [String] -> Bool
`inOperatorSet` ([String]
addInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
subInfix [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
bitwiseInfix) = Int
2
| Operator c
o Operator c -> [String] -> Bool
forall c. Operator c -> [String] -> Bool
`inOperatorSet` [String]
compareInfix = Int
4
| Operator c
o Operator c -> [String] -> Bool
forall c. Operator c -> [String] -> Bool
`inOperatorSet` [String]
logicalInfix = Int
5
infixPrecedence Operator c
_ = Int
3
infixBefore :: (Show c, ErrorContextM m) => Operator c -> Operator c -> m Bool
infixBefore :: Operator c -> Operator c -> m Bool
infixBefore Operator c
o1 Operator c
o2 = do
let prec1 :: Int
prec1 = Operator c -> Int
forall c. Operator c -> Int
infixPrecedence Operator c
o1
let prec2 :: Int
prec2 = Operator c -> Int
forall c. Operator c -> Int
infixPrecedence Operator c
o2
if Int
prec1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
prec2
then Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> m Bool) -> Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Int
prec1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
prec2
else if Operator c -> Operator c -> [String] -> Bool
forall c. Operator c -> Operator c -> [String] -> Bool
bothInOperatorSet Operator c
o1 Operator c
o2 [String]
rightAssocInfix
then Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
else Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
checkAmbiguous :: (Show c, ErrorContextM m) => Operator c -> Operator c -> m ()
checkAmbiguous :: Operator c -> Operator c -> m ()
checkAmbiguous Operator c
o1 Operator c
o2 = m ()
checked where
formatOperator :: Operator a -> String
formatOperator Operator a
o = FunctionName -> String
forall a. Show a => a -> String
show (Operator a -> FunctionName
forall c. Operator c -> FunctionName
getOperatorName Operator a
o) String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
" (" String -> String -> String
forall a. [a] -> [a] -> [a]
++ [a] -> String
forall a. Show a => [a] -> String
formatFullContext (Operator a -> [a]
forall c. Operator c -> [c]
getOperatorContext Operator a
o) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
checked :: m ()
checked
| Operator c -> Int
forall c. Operator c -> Int
infixPrecedence Operator c
o1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Operator c -> Int
forall c. Operator c -> Int
infixPrecedence Operator c
o2 = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Operator c -> Operator c -> [String] -> Bool
forall c. Operator c -> Operator c -> [String] -> Bool
bothInOperatorSet Operator c
o1 Operator c
o2 [String]
leftAssocInfix = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Operator c -> Operator c -> [String] -> Bool
forall c. Operator c -> Operator c -> [String] -> Bool
bothInOperatorSet Operator c
o1 Operator c
o2 [String]
rightAssocInfix = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Operator c -> Bool
forall c. Operator c -> Bool
isFunctionOperator Operator c
o1 Bool -> Bool -> Bool
&& Operator c -> Bool
forall c. Operator c -> Bool
isFunctionOperator Operator c
o2 = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise =
String -> m ()
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"the order of operators " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Operator c -> String
forall a. Show a => Operator a -> String
formatOperator Operator c
o1 String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
" and " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Operator c -> String
forall a. Show a => Operator a -> String
formatOperator Operator c
o2 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is ambiguous"
instance ParseFromSource (Expression SourceContext) where
sourceParser :: TextParser (Expression SourceContext)
sourceParser = do
Expression SourceContext
e <- TextParser (Expression SourceContext)
notInfix
[Expression SourceContext]
-> [([SourceContext], Operator SourceContext)]
-> TextParser (Expression SourceContext)
asInfix [Expression SourceContext
e] [] TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Expression SourceContext -> TextParser (Expression SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return Expression SourceContext
e
where
notInfix :: TextParser (Expression SourceContext)
notInfix = TextParser (Expression SourceContext)
literal TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (Expression SourceContext)
unary TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (Expression SourceContext)
initalize TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (Expression SourceContext)
expression
asInfix :: [Expression SourceContext]
-> [([SourceContext], Operator SourceContext)]
-> TextParser (Expression SourceContext)
asInfix [Expression SourceContext]
es [([SourceContext], Operator SourceContext)]
os = do
SourceContext
c <- TextParser SourceContext
getSourceContext
Operator SourceContext
o <- TextParser (Operator SourceContext)
infixOperator TextParser (Operator SourceContext)
-> TextParser (Operator SourceContext)
-> TextParser (Operator SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (Operator SourceContext)
functionOperator
Bool -> TextParser () -> TextParser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [([SourceContext], Operator SourceContext)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [([SourceContext], Operator SourceContext)]
os) (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ Operator SourceContext -> Operator SourceContext -> TextParser ()
forall c (m :: * -> *).
(Show c, ErrorContextM m) =>
Operator c -> Operator c -> m ()
checkAmbiguous (([SourceContext], Operator SourceContext) -> Operator SourceContext
forall a b. (a, b) -> b
snd (([SourceContext], Operator SourceContext)
-> Operator SourceContext)
-> ([SourceContext], Operator SourceContext)
-> Operator SourceContext
forall a b. (a -> b) -> a -> b
$ [([SourceContext], Operator SourceContext)]
-> ([SourceContext], Operator SourceContext)
forall a. [a] -> a
last [([SourceContext], Operator SourceContext)]
os) Operator SourceContext
o
Expression SourceContext
e2 <- TextParser (Expression SourceContext)
notInfix
let es' :: [Expression SourceContext]
es' = [Expression SourceContext]
es [Expression SourceContext]
-> [Expression SourceContext] -> [Expression SourceContext]
forall a. [a] -> [a] -> [a]
++ [Expression SourceContext
e2]
let os' :: [([SourceContext], Operator SourceContext)]
os' = [([SourceContext], Operator SourceContext)]
os [([SourceContext], Operator SourceContext)]
-> [([SourceContext], Operator SourceContext)]
-> [([SourceContext], Operator SourceContext)]
forall a. [a] -> [a] -> [a]
++ [([SourceContext
c],Operator SourceContext
o)]
[Expression SourceContext]
-> [([SourceContext], Operator SourceContext)]
-> TextParser (Expression SourceContext)
asInfix [Expression SourceContext]
es' [([SourceContext], Operator SourceContext)]
os' TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ([(Expression SourceContext, [SourceContext],
Operator SourceContext)]
-> [Expression SourceContext]
-> [([SourceContext], Operator SourceContext)]
-> TextParser (Expression SourceContext)
forall (m :: * -> *) c.
(Show c, ErrorContextM m) =>
[(Expression c, [c], Operator c)]
-> [Expression c] -> [([c], Operator c)] -> m (Expression c)
infixToTree [] [Expression SourceContext]
es' [([SourceContext], Operator SourceContext)]
os')
infixToTree :: [(Expression c, [c], Operator c)]
-> [Expression c] -> [([c], Operator c)] -> m (Expression c)
infixToTree [(Expression c
e1,[c]
c1,Operator c
o1)] [Expression c
e2] [] = Expression c -> m (Expression c)
forall (m :: * -> *) a. Monad m => a -> m a
return (Expression c -> m (Expression c))
-> Expression c -> m (Expression c)
forall a b. (a -> b) -> a -> b
$ [c] -> Expression c -> Operator c -> Expression c -> Expression c
forall c.
[c] -> Expression c -> Operator c -> Expression c -> Expression c
InfixExpression [c]
c1 Expression c
e1 Operator c
o1 Expression c
e2
infixToTree [] (Expression c
e1:[Expression c]
es) (([c]
c1,Operator c
o1):[([c], Operator c)]
os) = [(Expression c, [c], Operator c)]
-> [Expression c] -> [([c], Operator c)] -> m (Expression c)
infixToTree [(Expression c
e1,[c]
c1,Operator c
o1)] [Expression c]
es [([c], Operator c)]
os
infixToTree ((Expression c
e1,[c]
c1,Operator c
o1):[(Expression c, [c], Operator c)]
ss) [Expression c
e2] [] = let e2' :: Expression c
e2' = [c] -> Expression c -> Operator c -> Expression c -> Expression c
forall c.
[c] -> Expression c -> Operator c -> Expression c -> Expression c
InfixExpression [c]
c1 Expression c
e1 Operator c
o1 Expression c
e2 in
[(Expression c, [c], Operator c)]
-> [Expression c] -> [([c], Operator c)] -> m (Expression c)
infixToTree [(Expression c, [c], Operator c)]
ss [Expression c
e2'] []
infixToTree ((Expression c
e1,[c]
c1,Operator c
o1):[(Expression c, [c], Operator c)]
ss) (Expression c
e2:[Expression c]
es) (([c]
c2,Operator c
o2):[([c], Operator c)]
os) = do
Bool
before <- Operator c
o1 Operator c -> Operator c -> m Bool
forall c (m :: * -> *).
(Show c, ErrorContextM m) =>
Operator c -> Operator c -> m Bool
`infixBefore` Operator c
o2
if Bool
before
then let e1' :: Expression c
e1' = [c] -> Expression c -> Operator c -> Expression c -> Expression c
forall c.
[c] -> Expression c -> Operator c -> Expression c -> Expression c
InfixExpression [c]
c1 Expression c
e1 Operator c
o1 Expression c
e2 in
[(Expression c, [c], Operator c)]
-> [Expression c] -> [([c], Operator c)] -> m (Expression c)
infixToTree [(Expression c, [c], Operator c)]
ss (Expression c
e1'Expression c -> [Expression c] -> [Expression c]
forall a. a -> [a] -> [a]
:[Expression c]
es) (([c]
c2,Operator c
o2)([c], Operator c) -> [([c], Operator c)] -> [([c], Operator c)]
forall a. a -> [a] -> [a]
:[([c], Operator c)]
os)
else [(Expression c, [c], Operator c)]
-> [Expression c] -> [([c], Operator c)] -> m (Expression c)
infixToTree ((Expression c
e2,[c]
c2,Operator c
o2)(Expression c, [c], Operator c)
-> [(Expression c, [c], Operator c)]
-> [(Expression c, [c], Operator c)]
forall a. a -> [a] -> [a]
:(Expression c
e1,[c]
c1,Operator c
o1)(Expression c, [c], Operator c)
-> [(Expression c, [c], Operator c)]
-> [(Expression c, [c], Operator c)]
forall a. a -> [a] -> [a]
:[(Expression c, [c], Operator c)]
ss) [Expression c]
es [([c], Operator c)]
os
infixToTree [(Expression c, [c], Operator c)]
_ [Expression c]
_ [([c], Operator c)]
_ = m (Expression c)
forall a. HasCallStack => a
undefined
literal :: TextParser (Expression SourceContext)
literal = do
ValueLiteral SourceContext
l <- TextParser (ValueLiteral SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
Expression SourceContext -> TextParser (Expression SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Expression SourceContext -> TextParser (Expression SourceContext))
-> Expression SourceContext
-> TextParser (Expression SourceContext)
forall a b. (a -> b) -> a -> b
$ ValueLiteral SourceContext -> Expression SourceContext
forall c. ValueLiteral c -> Expression c
Literal ValueLiteral SourceContext
l
unary :: TextParser (Expression SourceContext)
unary = do
SourceContext
c <- TextParser SourceContext
getSourceContext
Operator SourceContext
o <- TextParser (Operator SourceContext)
unaryOperator TextParser (Operator SourceContext)
-> TextParser (Operator SourceContext)
-> TextParser (Operator SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (Operator SourceContext)
functionOperator
Expression SourceContext
e <- TextParser (Expression SourceContext)
notInfix
Expression SourceContext -> TextParser (Expression SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Expression SourceContext -> TextParser (Expression SourceContext))
-> Expression SourceContext
-> TextParser (Expression SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Operator SourceContext
-> Expression SourceContext
-> Expression SourceContext
forall c. [c] -> Operator c -> Expression c -> Expression c
UnaryExpression [SourceContext
c] Operator SourceContext
o Expression SourceContext
e
expression :: TextParser (Expression SourceContext)
expression = String
-> TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"expression" (TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext))
-> TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
ExpressionStart SourceContext
s <- TextParser (ExpressionStart SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
[ValueOperation SourceContext]
vs <- ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
-> ParsecT
CompilerMessage String Identity [ValueOperation SourceContext]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
Expression SourceContext -> TextParser (Expression SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Expression SourceContext -> TextParser (Expression SourceContext))
-> Expression SourceContext
-> TextParser (Expression SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> ExpressionStart SourceContext
-> [ValueOperation SourceContext]
-> Expression SourceContext
forall c.
[c] -> ExpressionStart c -> [ValueOperation c] -> Expression c
Expression [SourceContext
c] ExpressionStart SourceContext
s [ValueOperation SourceContext]
vs
initalize :: TextParser (Expression SourceContext)
initalize = do
SourceContext
c <- TextParser SourceContext
getSourceContext
Maybe TypeInstance
t <- ParsecT CompilerMessage String Identity (Maybe TypeInstance)
-> ParsecT CompilerMessage String Identity (Maybe TypeInstance)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT CompilerMessage String Identity (Maybe TypeInstance)
-> ParsecT CompilerMessage String Identity (Maybe TypeInstance))
-> ParsecT CompilerMessage String Identity (Maybe TypeInstance)
-> ParsecT CompilerMessage String Identity (Maybe TypeInstance)
forall a b. (a -> b) -> a -> b
$ do
Maybe TypeInstance
t2 <- (TextParser ()
paramSelf TextParser ()
-> ParsecT CompilerMessage String Identity (Maybe TypeInstance)
-> ParsecT CompilerMessage String Identity (Maybe TypeInstance)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe TypeInstance
-> ParsecT CompilerMessage String Identity (Maybe TypeInstance)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TypeInstance
forall a. Maybe a
Nothing) ParsecT CompilerMessage String Identity (Maybe TypeInstance)
-> ParsecT CompilerMessage String Identity (Maybe TypeInstance)
-> ParsecT CompilerMessage String Identity (Maybe TypeInstance)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (TypeInstance -> Maybe TypeInstance)
-> ParsecT CompilerMessage String Identity TypeInstance
-> ParsecT CompilerMessage String Identity (Maybe TypeInstance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TypeInstance -> Maybe TypeInstance
forall a. a -> Maybe a
Just ParsecT CompilerMessage String Identity TypeInstance
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (String -> TextParser () -> TextParser ()
forall a. String -> TextParser a -> TextParser a
labeled String
"@value initializer" (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"{")
Maybe TypeInstance
-> ParsecT CompilerMessage String Identity (Maybe TypeInstance)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TypeInstance
t2
[Expression SourceContext]
as <- TextParser (Expression SourceContext)
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [Expression SourceContext]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy TextParser (Expression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
",")
TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (String -> TextParser ()
string_ String
"}")
Expression SourceContext -> TextParser (Expression SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (Expression SourceContext -> TextParser (Expression SourceContext))
-> Expression SourceContext
-> TextParser (Expression SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Maybe TypeInstance
-> Positional (Expression SourceContext)
-> Expression SourceContext
forall c.
[c]
-> Maybe TypeInstance -> Positional (Expression c) -> Expression c
InitializeValue [SourceContext
c] Maybe TypeInstance
t ([Expression SourceContext] -> Positional (Expression SourceContext)
forall a. [a] -> Positional a
Positional [Expression SourceContext]
as)
instance ParseFromSource (FunctionQualifier SourceContext) where
sourceParser :: TextParser (FunctionQualifier SourceContext)
sourceParser = TextParser (FunctionQualifier SourceContext)
valueFunc TextParser (FunctionQualifier SourceContext)
-> TextParser (FunctionQualifier SourceContext)
-> TextParser (FunctionQualifier SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (FunctionQualifier SourceContext)
categoryFunc TextParser (FunctionQualifier SourceContext)
-> TextParser (FunctionQualifier SourceContext)
-> TextParser (FunctionQualifier SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (FunctionQualifier SourceContext)
typeFunc where
valueFunc :: TextParser (FunctionQualifier SourceContext)
valueFunc = do
SourceContext
c <- TextParser SourceContext
getSourceContext
Expression SourceContext
q <- TextParser (Expression SourceContext)
-> TextParser (Expression SourceContext)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try TextParser (Expression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser ()
valueSymbolGet
FunctionQualifier SourceContext
-> TextParser (FunctionQualifier SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (FunctionQualifier SourceContext
-> TextParser (FunctionQualifier SourceContext))
-> FunctionQualifier SourceContext
-> TextParser (FunctionQualifier SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Expression SourceContext -> FunctionQualifier SourceContext
forall c. [c] -> Expression c -> FunctionQualifier c
ValueFunction [SourceContext
c] Expression SourceContext
q
categoryFunc :: TextParser (FunctionQualifier SourceContext)
categoryFunc = do
SourceContext
c <- TextParser SourceContext
getSourceContext
CategoryName
q <- ParsecT CompilerMessage String Identity CategoryName
-> ParsecT CompilerMessage String Identity CategoryName
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT CompilerMessage String Identity CategoryName
-> ParsecT CompilerMessage String Identity CategoryName)
-> ParsecT CompilerMessage String Identity CategoryName
-> ParsecT CompilerMessage String Identity CategoryName
forall a b. (a -> b) -> a -> b
$ do
CategoryName
q2 <- ParsecT CompilerMessage String Identity CategoryName
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser ()
categorySymbolGet
CategoryName
-> ParsecT CompilerMessage String Identity CategoryName
forall (m :: * -> *) a. Monad m => a -> m a
return CategoryName
q2
FunctionQualifier SourceContext
-> TextParser (FunctionQualifier SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (FunctionQualifier SourceContext
-> TextParser (FunctionQualifier SourceContext))
-> FunctionQualifier SourceContext
-> TextParser (FunctionQualifier SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> CategoryName -> FunctionQualifier SourceContext
forall c. [c] -> CategoryName -> FunctionQualifier c
CategoryFunction [SourceContext
c] CategoryName
q
typeFunc :: TextParser (FunctionQualifier SourceContext)
typeFunc = do
SourceContext
c <- TextParser SourceContext
getSourceContext
TypeInstanceOrParam
q <- ParsecT CompilerMessage String Identity TypeInstanceOrParam
-> ParsecT CompilerMessage String Identity TypeInstanceOrParam
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT CompilerMessage String Identity TypeInstanceOrParam
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser ()
typeSymbolGet
FunctionQualifier SourceContext
-> TextParser (FunctionQualifier SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (FunctionQualifier SourceContext
-> TextParser (FunctionQualifier SourceContext))
-> FunctionQualifier SourceContext
-> TextParser (FunctionQualifier SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> TypeInstanceOrParam -> FunctionQualifier SourceContext
forall c. [c] -> TypeInstanceOrParam -> FunctionQualifier c
TypeFunction [SourceContext
c] TypeInstanceOrParam
q
instance ParseFromSource (FunctionSpec SourceContext) where
sourceParser :: TextParser (FunctionSpec SourceContext)
sourceParser = TextParser (FunctionSpec SourceContext)
-> TextParser (FunctionSpec SourceContext)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try TextParser (FunctionSpec SourceContext)
qualified TextParser (FunctionSpec SourceContext)
-> TextParser (FunctionSpec SourceContext)
-> TextParser (FunctionSpec SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (FunctionSpec SourceContext)
unqualified where
qualified :: TextParser (FunctionSpec SourceContext)
qualified = do
SourceContext
c <- TextParser SourceContext
getSourceContext
FunctionQualifier SourceContext
q <- TextParser (FunctionQualifier SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
FunctionName
n <- ParsecT CompilerMessage String Identity FunctionName
forall a. ParseFromSource a => TextParser a
sourceParser
[InstanceOrInferred SourceContext]
ps <- ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext])
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall a b. (a -> b) -> a -> b
$ TextParser ()
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"<")
(TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
">")
(ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
",")) ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall (m :: * -> *) a. Monad m => a -> m a
return []
FunctionSpec SourceContext
-> TextParser (FunctionSpec SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (FunctionSpec SourceContext
-> TextParser (FunctionSpec SourceContext))
-> FunctionSpec SourceContext
-> TextParser (FunctionSpec SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> FunctionQualifier SourceContext
-> FunctionName
-> Positional (InstanceOrInferred SourceContext)
-> FunctionSpec SourceContext
forall c.
[c]
-> FunctionQualifier c
-> FunctionName
-> Positional (InstanceOrInferred c)
-> FunctionSpec c
FunctionSpec [SourceContext
c] FunctionQualifier SourceContext
q FunctionName
n ([InstanceOrInferred SourceContext]
-> Positional (InstanceOrInferred SourceContext)
forall a. [a] -> Positional a
Positional [InstanceOrInferred SourceContext]
ps)
unqualified :: TextParser (FunctionSpec SourceContext)
unqualified = do
SourceContext
c <- TextParser SourceContext
getSourceContext
FunctionName
n <- ParsecT CompilerMessage String Identity FunctionName
forall a. ParseFromSource a => TextParser a
sourceParser
[InstanceOrInferred SourceContext]
ps <- ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext])
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall a b. (a -> b) -> a -> b
$ TextParser ()
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"<")
(TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
">")
(ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
",")) ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall (m :: * -> *) a. Monad m => a -> m a
return []
FunctionSpec SourceContext
-> TextParser (FunctionSpec SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (FunctionSpec SourceContext
-> TextParser (FunctionSpec SourceContext))
-> FunctionSpec SourceContext
-> TextParser (FunctionSpec SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> FunctionQualifier SourceContext
-> FunctionName
-> Positional (InstanceOrInferred SourceContext)
-> FunctionSpec SourceContext
forall c.
[c]
-> FunctionQualifier c
-> FunctionName
-> Positional (InstanceOrInferred c)
-> FunctionSpec c
FunctionSpec [SourceContext
c] FunctionQualifier SourceContext
forall c. FunctionQualifier c
UnqualifiedFunction FunctionName
n ([InstanceOrInferred SourceContext]
-> Positional (InstanceOrInferred SourceContext)
forall a. [a] -> Positional a
Positional [InstanceOrInferred SourceContext]
ps)
instance ParseFromSource (InstanceOrInferred SourceContext) where
sourceParser :: ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
sourceParser = ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
assigned ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
-> ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
-> ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
inferred where
assigned :: ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
assigned = do
SourceContext
c <- TextParser SourceContext
getSourceContext
GeneralInstance
t <- TextParser GeneralInstance
forall a. ParseFromSource a => TextParser a
sourceParser
InstanceOrInferred SourceContext
-> ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (InstanceOrInferred SourceContext
-> ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext))
-> InstanceOrInferred SourceContext
-> ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> GeneralInstance -> InstanceOrInferred SourceContext
forall c. [c] -> GeneralInstance -> InstanceOrInferred c
AssignedInstance [SourceContext
c] GeneralInstance
t
inferred :: ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
inferred = do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser () -> TextParser ()
forall a. TextParser a -> TextParser ()
sepAfter_ TextParser ()
inferredParam
InstanceOrInferred SourceContext
-> ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (InstanceOrInferred SourceContext
-> ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext))
-> InstanceOrInferred SourceContext
-> ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> InstanceOrInferred SourceContext
forall c. [c] -> InstanceOrInferred c
InferredInstance [SourceContext
c]
parseFunctionCall :: SourceContext -> FunctionName -> TextParser (FunctionCall SourceContext)
parseFunctionCall :: SourceContext
-> FunctionName -> TextParser (FunctionCall SourceContext)
parseFunctionCall SourceContext
c FunctionName
n = do
[InstanceOrInferred SourceContext]
ps <- ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext])
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall a b. (a -> b) -> a -> b
$ TextParser ()
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"<")
(TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
">")
(ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy ParsecT
CompilerMessage String Identity (InstanceOrInferred SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
",")) ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [InstanceOrInferred SourceContext]
-> ParsecT
CompilerMessage String Identity [InstanceOrInferred SourceContext]
forall (m :: * -> *) a. Monad m => a -> m a
return []
[Expression SourceContext]
es <- TextParser ()
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [Expression SourceContext]
-> ParsecT
CompilerMessage String Identity [Expression SourceContext]
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
"(")
(TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
")")
(TextParser (Expression SourceContext)
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [Expression SourceContext]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy TextParser (Expression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
","))
FunctionCall SourceContext
-> TextParser (FunctionCall SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (FunctionCall SourceContext
-> TextParser (FunctionCall SourceContext))
-> FunctionCall SourceContext
-> TextParser (FunctionCall SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> FunctionName
-> Positional (InstanceOrInferred SourceContext)
-> Positional (Expression SourceContext)
-> FunctionCall SourceContext
forall c.
[c]
-> FunctionName
-> Positional (InstanceOrInferred c)
-> Positional (Expression c)
-> FunctionCall c
FunctionCall [SourceContext
c] FunctionName
n ([InstanceOrInferred SourceContext]
-> Positional (InstanceOrInferred SourceContext)
forall a. [a] -> Positional a
Positional [InstanceOrInferred SourceContext]
ps) ([Expression SourceContext] -> Positional (Expression SourceContext)
forall a. [a] -> Positional a
Positional [Expression SourceContext]
es)
builtinFunction :: TextParser FunctionName
builtinFunction :: ParsecT CompilerMessage String Identity FunctionName
builtinFunction = (ParsecT CompilerMessage String Identity FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
-> ParsecT CompilerMessage String Identity FunctionName)
-> ParsecT CompilerMessage String Identity FunctionName
-> [ParsecT CompilerMessage String Identity FunctionName]
-> ParsecT CompilerMessage String Identity FunctionName
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ParsecT CompilerMessage String Identity FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>) ParsecT CompilerMessage String Identity FunctionName
forall (f :: * -> *) a. Alternative f => f a
empty ([ParsecT CompilerMessage String Identity FunctionName]
-> ParsecT CompilerMessage String Identity FunctionName)
-> [ParsecT CompilerMessage String Identity FunctionName]
-> ParsecT CompilerMessage String Identity FunctionName
forall a b. (a -> b) -> a -> b
$ (ParsecT CompilerMessage String Identity FunctionName
-> ParsecT CompilerMessage String Identity FunctionName)
-> [ParsecT CompilerMessage String Identity FunctionName]
-> [ParsecT CompilerMessage String Identity FunctionName]
forall a b. (a -> b) -> [a] -> [b]
map ParsecT CompilerMessage String Identity FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try [
TextParser ()
kwPresent TextParser ()
-> ParsecT CompilerMessage String Identity FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall (m :: * -> *) a. Monad m => a -> m a
return FunctionName
BuiltinPresent,
TextParser ()
kwReduce TextParser ()
-> ParsecT CompilerMessage String Identity FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall (m :: * -> *) a. Monad m => a -> m a
return FunctionName
BuiltinReduce,
TextParser ()
kwRequire TextParser ()
-> ParsecT CompilerMessage String Identity FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall (m :: * -> *) a. Monad m => a -> m a
return FunctionName
BuiltinRequire,
TextParser ()
kwStrong TextParser ()
-> ParsecT CompilerMessage String Identity FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall (m :: * -> *) a. Monad m => a -> m a
return FunctionName
BuiltinStrong,
TextParser ()
kwTypename TextParser ()
-> ParsecT CompilerMessage String Identity FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FunctionName
-> ParsecT CompilerMessage String Identity FunctionName
forall (m :: * -> *) a. Monad m => a -> m a
return FunctionName
BuiltinTypename
]
instance ParseFromSource (ExpressionStart SourceContext) where
sourceParser :: TextParser (ExpressionStart SourceContext)
sourceParser = String
-> TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"expression start" (TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext))
-> TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
forall a b. (a -> b) -> a -> b
$
TextParser (ExpressionStart SourceContext)
parens TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
TextParser (ExpressionStart SourceContext)
variableOrUnqualified TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
TextParser (ExpressionStart SourceContext)
builtinCall TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
TextParser (ExpressionStart SourceContext)
builtinValue TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
TextParser (ExpressionStart SourceContext)
sourceContext TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
TextParser (ExpressionStart SourceContext)
exprLookup TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
TextParser (ExpressionStart SourceContext)
categoryCall TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
TextParser (ExpressionStart SourceContext)
typeCall where
parens :: TextParser (ExpressionStart SourceContext)
parens = do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (String -> TextParser ()
string_ String
"(")
ExpressionStart SourceContext
e <- TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (SourceContext -> TextParser (ExpressionStart SourceContext)
assign SourceContext
c) TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> SourceContext -> TextParser (ExpressionStart SourceContext)
expr SourceContext
c
TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (String -> TextParser ()
string_ String
")")
ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return ExpressionStart SourceContext
e
assign :: SourceContext -> TextParser (ExpressionStart SourceContext)
assign :: SourceContext -> TextParser (ExpressionStart SourceContext)
assign SourceContext
c = do
VariableName
n <- TextParser VariableName
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser ()
assignOperator
Expression SourceContext
e <- TextParser (Expression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext))
-> ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> VariableName
-> Expression SourceContext
-> ExpressionStart SourceContext
forall c. [c] -> VariableName -> Expression c -> ExpressionStart c
InlineAssignment [SourceContext
c] VariableName
n Expression SourceContext
e
expr :: SourceContext -> TextParser (ExpressionStart SourceContext)
expr :: SourceContext -> TextParser (ExpressionStart SourceContext)
expr SourceContext
c = do
Expression SourceContext
e <- TextParser (Expression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext))
-> ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Expression SourceContext -> ExpressionStart SourceContext
forall c. [c] -> Expression c -> ExpressionStart c
ParensExpression [SourceContext
c] Expression SourceContext
e
builtinCall :: TextParser (ExpressionStart SourceContext)
builtinCall = do
SourceContext
c <- TextParser SourceContext
getSourceContext
FunctionName
n <- ParsecT CompilerMessage String Identity FunctionName
builtinFunction
FunctionCall SourceContext
f <- SourceContext
-> FunctionName -> TextParser (FunctionCall SourceContext)
parseFunctionCall SourceContext
c FunctionName
n
ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext))
-> ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> FunctionCall SourceContext -> ExpressionStart SourceContext
forall c. [c] -> FunctionCall c -> ExpressionStart c
BuiltinCall [SourceContext
c] FunctionCall SourceContext
f
builtinValue :: TextParser (ExpressionStart SourceContext)
builtinValue = do
SourceContext
c <- TextParser SourceContext
getSourceContext
String
n <- TextParser String
builtinValues
ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext))
-> ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall a b. (a -> b) -> a -> b
$ OutputValue SourceContext -> ExpressionStart SourceContext
forall c. OutputValue c -> ExpressionStart c
NamedVariable ([SourceContext] -> VariableName -> OutputValue SourceContext
forall c. [c] -> VariableName -> OutputValue c
OutputValue [SourceContext
c] (String -> VariableName
VariableName String
n))
sourceContext :: TextParser (ExpressionStart SourceContext)
sourceContext = do
PragmaExpr SourceContext
pragma <- TextParser (PragmaExpr SourceContext)
pragmaSourceContext
case PragmaExpr SourceContext
pragma of
(PragmaSourceContext SourceContext
c) -> ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext))
-> ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> Expression SourceContext -> ExpressionStart SourceContext
forall c. [c] -> Expression c -> ExpressionStart c
ParensExpression [SourceContext
c] (Expression SourceContext -> ExpressionStart SourceContext)
-> Expression SourceContext -> ExpressionStart SourceContext
forall a b. (a -> b) -> a -> b
$ ValueLiteral SourceContext -> Expression SourceContext
forall c. ValueLiteral c -> Expression c
Literal ([SourceContext] -> String -> ValueLiteral SourceContext
forall c. [c] -> String -> ValueLiteral c
StringLiteral [SourceContext
c] (SourceContext -> String
forall a. Show a => a -> String
show SourceContext
c))
PragmaExpr SourceContext
_ -> TextParser (ExpressionStart SourceContext)
forall a. HasCallStack => a
undefined
exprLookup :: TextParser (ExpressionStart SourceContext)
exprLookup = do
PragmaExpr SourceContext
pragma <- TextParser (PragmaExpr SourceContext)
pragmaExprLookup
case PragmaExpr SourceContext
pragma of
(PragmaExprLookup [SourceContext]
c MacroName
name) -> ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext))
-> ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> MacroName -> ExpressionStart SourceContext
forall c. [c] -> MacroName -> ExpressionStart c
NamedMacro [SourceContext]
c MacroName
name
PragmaExpr SourceContext
_ -> TextParser (ExpressionStart SourceContext)
forall a. HasCallStack => a
undefined
variableOrUnqualified :: TextParser (ExpressionStart SourceContext)
variableOrUnqualified = do
SourceContext
c <- TextParser SourceContext
getSourceContext
VariableName
n <- TextParser VariableName
forall a. ParseFromSource a => TextParser a
sourceParser :: TextParser VariableName
SourceContext
-> VariableName -> TextParser (ExpressionStart SourceContext)
asUnqualifiedCall SourceContext
c VariableName
n TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
-> TextParser (ExpressionStart SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> SourceContext
-> VariableName -> TextParser (ExpressionStart SourceContext)
forall (m :: * -> *) c.
Monad m =>
c -> VariableName -> m (ExpressionStart c)
asVariable SourceContext
c VariableName
n
asVariable :: c -> VariableName -> m (ExpressionStart c)
asVariable c
c VariableName
n = do
ExpressionStart c -> m (ExpressionStart c)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExpressionStart c -> m (ExpressionStart c))
-> ExpressionStart c -> m (ExpressionStart c)
forall a b. (a -> b) -> a -> b
$ OutputValue c -> ExpressionStart c
forall c. OutputValue c -> ExpressionStart c
NamedVariable ([c] -> VariableName -> OutputValue c
forall c. [c] -> VariableName -> OutputValue c
OutputValue [c
c] VariableName
n)
asUnqualifiedCall :: SourceContext
-> VariableName -> TextParser (ExpressionStart SourceContext)
asUnqualifiedCall SourceContext
c VariableName
n = do
FunctionCall SourceContext
f <- SourceContext
-> FunctionName -> TextParser (FunctionCall SourceContext)
parseFunctionCall SourceContext
c (String -> FunctionName
FunctionName (VariableName -> String
vnName VariableName
n))
ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext))
-> ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> FunctionCall SourceContext -> ExpressionStart SourceContext
forall c. [c] -> FunctionCall c -> ExpressionStart c
UnqualifiedCall [SourceContext
c] FunctionCall SourceContext
f
categoryCall :: TextParser (ExpressionStart SourceContext)
categoryCall = do
SourceContext
c <- TextParser SourceContext
getSourceContext
CategoryName
t <- ParsecT CompilerMessage String Identity CategoryName
-> ParsecT CompilerMessage String Identity CategoryName
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT CompilerMessage String Identity CategoryName
-> ParsecT CompilerMessage String Identity CategoryName)
-> ParsecT CompilerMessage String Identity CategoryName
-> ParsecT CompilerMessage String Identity CategoryName
forall a b. (a -> b) -> a -> b
$ do
CategoryName
t2 <- ParsecT CompilerMessage String Identity CategoryName
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser ()
categorySymbolGet
CategoryName
-> ParsecT CompilerMessage String Identity CategoryName
forall (m :: * -> *) a. Monad m => a -> m a
return CategoryName
t2
FunctionName
n <- ParsecT CompilerMessage String Identity FunctionName
forall a. ParseFromSource a => TextParser a
sourceParser
FunctionCall SourceContext
f <- SourceContext
-> FunctionName -> TextParser (FunctionCall SourceContext)
parseFunctionCall SourceContext
c FunctionName
n
ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext))
-> ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> CategoryName
-> FunctionCall SourceContext
-> ExpressionStart SourceContext
forall c.
[c] -> CategoryName -> FunctionCall c -> ExpressionStart c
CategoryCall [SourceContext
c] CategoryName
t FunctionCall SourceContext
f
typeCall :: TextParser (ExpressionStart SourceContext)
typeCall = do
SourceContext
c <- TextParser SourceContext
getSourceContext
TypeInstanceOrParam
t <- ParsecT CompilerMessage String Identity TypeInstanceOrParam
-> ParsecT CompilerMessage String Identity TypeInstanceOrParam
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT CompilerMessage String Identity TypeInstanceOrParam
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser ()
typeSymbolGet
FunctionName
n <- ParsecT CompilerMessage String Identity FunctionName
forall a. ParseFromSource a => TextParser a
sourceParser
FunctionCall SourceContext
f <- SourceContext
-> FunctionName -> TextParser (FunctionCall SourceContext)
parseFunctionCall SourceContext
c FunctionName
n
ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext))
-> ExpressionStart SourceContext
-> TextParser (ExpressionStart SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> TypeInstanceOrParam
-> FunctionCall SourceContext
-> ExpressionStart SourceContext
forall c.
[c] -> TypeInstanceOrParam -> FunctionCall c -> ExpressionStart c
TypeCall [SourceContext
c] TypeInstanceOrParam
t FunctionCall SourceContext
f
instance ParseFromSource (ValueLiteral SourceContext) where
sourceParser :: TextParser (ValueLiteral SourceContext)
sourceParser = String
-> TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"literal" (TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext))
-> TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
forall a b. (a -> b) -> a -> b
$
TextParser (ValueLiteral SourceContext)
stringLiteral TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
TextParser (ValueLiteral SourceContext)
charLiteral TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
TextParser (ValueLiteral SourceContext)
escapedInteger TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
TextParser (ValueLiteral SourceContext)
integerOrDecimal TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
TextParser (ValueLiteral SourceContext)
boolLiteral TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
TextParser (ValueLiteral SourceContext)
emptyLiteral where
stringLiteral :: TextParser (ValueLiteral SourceContext)
stringLiteral = do
SourceContext
c <- TextParser SourceContext
getSourceContext
String
ss <- TextParser String
quotedString
TextParser ()
optionalSpace
ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext))
-> ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> String -> ValueLiteral SourceContext
forall c. [c] -> String -> ValueLiteral c
StringLiteral [SourceContext
c] String
ss
charLiteral :: TextParser (ValueLiteral SourceContext)
charLiteral = do
SourceContext
c <- TextParser SourceContext
getSourceContext
String -> TextParser ()
string_ String
"'"
Char
ch <- ParsecT CompilerMessage String Identity Char
stringChar ParsecT CompilerMessage String Identity Char
-> ParsecT CompilerMessage String Identity Char
-> ParsecT CompilerMessage String Identity Char
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Token String
-> ParsecT CompilerMessage String Identity (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'"'
String -> TextParser ()
string_ String
"'"
TextParser ()
optionalSpace
ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext))
-> ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> Char -> ValueLiteral SourceContext
forall c. [c] -> Char -> ValueLiteral c
CharLiteral [SourceContext
c] Char
ch
escapedInteger :: TextParser (ValueLiteral SourceContext)
escapedInteger = do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
escapeStart
Char
b <- [Token String]
-> ParsecT CompilerMessage String Identity (Token String)
forall (f :: * -> *) e s (m :: * -> *).
(Foldable f, MonadParsec e s m) =>
f (Token s) -> m (Token s)
oneOf String
[Token String]
"bBoOdDxX"
Integer
d <- case Char
b of
Char
'b' -> ParsecT CompilerMessage String Identity Integer
parseBin
Char
'B' -> ParsecT CompilerMessage String Identity Integer
parseBin
Char
'o' -> ParsecT CompilerMessage String Identity Integer
parseOct
Char
'O' -> ParsecT CompilerMessage String Identity Integer
parseOct
Char
'd' -> ParsecT CompilerMessage String Identity Integer
parseDec
Char
'D' -> ParsecT CompilerMessage String Identity Integer
parseDec
Char
'x' -> ParsecT CompilerMessage String Identity Integer
parseHex
Char
'X' -> ParsecT CompilerMessage String Identity Integer
parseHex
Char
_ -> ParsecT CompilerMessage String Identity Integer
forall a. HasCallStack => a
undefined
TextParser ()
optionalSpace
ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext))
-> ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> Bool -> Integer -> ValueLiteral SourceContext
forall c. [c] -> Bool -> Integer -> ValueLiteral c
IntegerLiteral [SourceContext
c] Bool
True Integer
d
integerOrDecimal :: TextParser (ValueLiteral SourceContext)
integerOrDecimal = do
SourceContext
c <- TextParser SourceContext
getSourceContext
Integer
d <- ParsecT CompilerMessage String Identity Integer
parseDec
SourceContext -> Integer -> TextParser (ValueLiteral SourceContext)
forall c.
c
-> Integer
-> ParsecT CompilerMessage String Identity (ValueLiteral c)
decimal SourceContext
c Integer
d TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
-> TextParser (ValueLiteral SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> SourceContext -> Integer -> TextParser (ValueLiteral SourceContext)
forall c.
c
-> Integer
-> ParsecT CompilerMessage String Identity (ValueLiteral c)
integer SourceContext
c Integer
d
decimal :: c
-> Integer
-> ParsecT CompilerMessage String Identity (ValueLiteral c)
decimal c
c Integer
d = do
Char -> TextParser ()
char_ Char
'.'
(Integer
n,Integer
d2) <- TextParser (Integer, Integer)
parseSubOne
Integer
e <- ParsecT CompilerMessage String Identity Integer
decExponent ParsecT CompilerMessage String Identity Integer
-> ParsecT CompilerMessage String Identity Integer
-> ParsecT CompilerMessage String Identity Integer
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Integer -> ParsecT CompilerMessage String Identity Integer
forall (m :: * -> *) a. Monad m => a -> m a
return Integer
0
TextParser ()
optionalSpace
ValueLiteral c
-> ParsecT CompilerMessage String Identity (ValueLiteral c)
forall (m :: * -> *) a. Monad m => a -> m a
return (ValueLiteral c
-> ParsecT CompilerMessage String Identity (ValueLiteral c))
-> ValueLiteral c
-> ParsecT CompilerMessage String Identity (ValueLiteral c)
forall a b. (a -> b) -> a -> b
$ [c] -> Integer -> Integer -> ValueLiteral c
forall c. [c] -> Integer -> Integer -> ValueLiteral c
DecimalLiteral [c
c] (Integer
dInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
10Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
d2) (Integer
e Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
n)
decExponent :: ParsecT CompilerMessage String Identity Integer
decExponent = do
String -> TextParser ()
string_ String
"e" TextParser () -> TextParser () -> TextParser ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> String -> TextParser ()
string_ String
"E"
Integer
s <- (String -> TextParser ()
string_ String
"+" TextParser ()
-> ParsecT CompilerMessage String Identity Integer
-> ParsecT CompilerMessage String Identity Integer
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Integer -> ParsecT CompilerMessage String Identity Integer
forall (m :: * -> *) a. Monad m => a -> m a
return Integer
1) ParsecT CompilerMessage String Identity Integer
-> ParsecT CompilerMessage String Identity Integer
-> ParsecT CompilerMessage String Identity Integer
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (String -> TextParser ()
string_ String
"-" TextParser ()
-> ParsecT CompilerMessage String Identity Integer
-> ParsecT CompilerMessage String Identity Integer
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Integer -> ParsecT CompilerMessage String Identity Integer
forall (m :: * -> *) a. Monad m => a -> m a
return (-Integer
1)) ParsecT CompilerMessage String Identity Integer
-> ParsecT CompilerMessage String Identity Integer
-> ParsecT CompilerMessage String Identity Integer
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Integer -> ParsecT CompilerMessage String Identity Integer
forall (m :: * -> *) a. Monad m => a -> m a
return Integer
1
Integer
e <- ParsecT CompilerMessage String Identity Integer
parseDec
Integer -> ParsecT CompilerMessage String Identity Integer
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer
sInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
e)
integer :: c
-> Integer
-> ParsecT CompilerMessage String Identity (ValueLiteral c)
integer c
c Integer
d = do
TextParser ()
optionalSpace
ValueLiteral c
-> ParsecT CompilerMessage String Identity (ValueLiteral c)
forall (m :: * -> *) a. Monad m => a -> m a
return (ValueLiteral c
-> ParsecT CompilerMessage String Identity (ValueLiteral c))
-> ValueLiteral c
-> ParsecT CompilerMessage String Identity (ValueLiteral c)
forall a b. (a -> b) -> a -> b
$ [c] -> Bool -> Integer -> ValueLiteral c
forall c. [c] -> Bool -> Integer -> ValueLiteral c
IntegerLiteral [c
c] Bool
False Integer
d
boolLiteral :: TextParser (ValueLiteral SourceContext)
boolLiteral = do
SourceContext
c <- TextParser SourceContext
getSourceContext
Bool
b <- ParsecT CompilerMessage String Identity Bool
-> ParsecT CompilerMessage String Identity Bool
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT CompilerMessage String Identity Bool
-> ParsecT CompilerMessage String Identity Bool)
-> ParsecT CompilerMessage String Identity Bool
-> ParsecT CompilerMessage String Identity Bool
forall a b. (a -> b) -> a -> b
$ (TextParser ()
kwTrue TextParser ()
-> ParsecT CompilerMessage String Identity Bool
-> ParsecT CompilerMessage String Identity Bool
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> ParsecT CompilerMessage String Identity Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True) ParsecT CompilerMessage String Identity Bool
-> ParsecT CompilerMessage String Identity Bool
-> ParsecT CompilerMessage String Identity Bool
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (TextParser ()
kwFalse TextParser ()
-> ParsecT CompilerMessage String Identity Bool
-> ParsecT CompilerMessage String Identity Bool
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> ParsecT CompilerMessage String Identity Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False)
ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext))
-> ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> Bool -> ValueLiteral SourceContext
forall c. [c] -> Bool -> ValueLiteral c
BoolLiteral [SourceContext
c] Bool
b
emptyLiteral :: TextParser (ValueLiteral SourceContext)
emptyLiteral = do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
kwEmpty
ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext))
-> ValueLiteral SourceContext
-> TextParser (ValueLiteral SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext] -> ValueLiteral SourceContext
forall c. [c] -> ValueLiteral c
EmptyLiteral [SourceContext
c]
instance ParseFromSource (ValueOperation SourceContext) where
sourceParser :: ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
sourceParser = ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
valueCall ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
conversion where
valueCall :: ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
valueCall = String
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"function call" (ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext))
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
valueSymbolGet
FunctionName
n <- ParsecT CompilerMessage String Identity FunctionName
forall a. ParseFromSource a => TextParser a
sourceParser
FunctionCall SourceContext
f <- SourceContext
-> FunctionName -> TextParser (FunctionCall SourceContext)
parseFunctionCall SourceContext
c FunctionName
n
ValueOperation SourceContext
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ValueOperation SourceContext
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext))
-> ValueOperation SourceContext
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> FunctionCall SourceContext -> ValueOperation SourceContext
forall c. [c] -> FunctionCall c -> ValueOperation c
ValueCall [SourceContext
c] FunctionCall SourceContext
f
conversion :: ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
conversion = String
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"type conversion" (ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext))
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
valueSymbolGet
TypeInstance
t <- ParsecT CompilerMessage String Identity TypeInstance
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser ()
typeSymbolGet
FunctionName
n <- ParsecT CompilerMessage String Identity FunctionName
forall a. ParseFromSource a => TextParser a
sourceParser
FunctionCall SourceContext
f <- SourceContext
-> FunctionName -> TextParser (FunctionCall SourceContext)
parseFunctionCall SourceContext
c FunctionName
n
ValueOperation SourceContext
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ValueOperation SourceContext
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext))
-> ValueOperation SourceContext
-> ParsecT
CompilerMessage String Identity (ValueOperation SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> TypeInstance
-> FunctionCall SourceContext
-> ValueOperation SourceContext
forall c. [c] -> TypeInstance -> FunctionCall c -> ValueOperation c
ConvertedCall [SourceContext
c] TypeInstance
t FunctionCall SourceContext
f
instance ParseFromSource MacroName where
sourceParser :: TextParser MacroName
sourceParser = String -> TextParser MacroName -> TextParser MacroName
forall a. String -> TextParser a -> TextParser a
labeled String
"macro name" (TextParser MacroName -> TextParser MacroName)
-> TextParser MacroName -> TextParser MacroName
forall a b. (a -> b) -> a -> b
$ do
Char
h <- ParsecT CompilerMessage String Identity Char
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
upperChar ParsecT CompilerMessage String Identity Char
-> ParsecT CompilerMessage String Identity Char
-> ParsecT CompilerMessage String Identity Char
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Token String
-> ParsecT CompilerMessage String Identity (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'_'
String
t <- ParsecT CompilerMessage String Identity Char -> TextParser String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (ParsecT CompilerMessage String Identity Char
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
upperChar ParsecT CompilerMessage String Identity Char
-> ParsecT CompilerMessage String Identity Char
-> ParsecT CompilerMessage String Identity Char
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT CompilerMessage String Identity Char
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
digitChar ParsecT CompilerMessage String Identity Char
-> ParsecT CompilerMessage String Identity Char
-> ParsecT CompilerMessage String Identity Char
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Token String
-> ParsecT CompilerMessage String Identity (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'_')
TextParser ()
optionalSpace
MacroName -> TextParser MacroName
forall (m :: * -> *) a. Monad m => a -> m a
return (MacroName -> TextParser MacroName)
-> MacroName -> TextParser MacroName
forall a b. (a -> b) -> a -> b
$ String -> MacroName
MacroName (Char
hChar -> String -> String
forall a. a -> [a] -> [a]
:String
t)
pragmaNoTrace :: TextParser (PragmaProcedure SourceContext)
pragmaNoTrace :: TextParser (PragmaProcedure SourceContext)
pragmaNoTrace = String
-> Either
(SourceContext -> PragmaProcedure SourceContext)
(SourceContext -> TextParser (PragmaProcedure SourceContext))
-> TextParser (PragmaProcedure SourceContext)
forall a.
String
-> Either (SourceContext -> a) (SourceContext -> TextParser a)
-> TextParser a
autoPragma String
"NoTrace" (Either
(SourceContext -> PragmaProcedure SourceContext)
(SourceContext -> TextParser (PragmaProcedure SourceContext))
-> TextParser (PragmaProcedure SourceContext))
-> Either
(SourceContext -> PragmaProcedure SourceContext)
(SourceContext -> TextParser (PragmaProcedure SourceContext))
-> TextParser (PragmaProcedure SourceContext)
forall a b. (a -> b) -> a -> b
$ (SourceContext -> PragmaProcedure SourceContext)
-> Either
(SourceContext -> PragmaProcedure SourceContext)
(SourceContext -> TextParser (PragmaProcedure SourceContext))
forall a b. a -> Either a b
Left SourceContext -> PragmaProcedure SourceContext
forall c. c -> PragmaProcedure c
parseAt where
parseAt :: c -> PragmaProcedure c
parseAt c
c = [c] -> TraceType -> PragmaProcedure c
forall c. [c] -> TraceType -> PragmaProcedure c
PragmaTracing [c
c] TraceType
NoTrace
pragmaTraceCreation :: TextParser (PragmaProcedure SourceContext)
pragmaTraceCreation :: TextParser (PragmaProcedure SourceContext)
pragmaTraceCreation = String
-> Either
(SourceContext -> PragmaProcedure SourceContext)
(SourceContext -> TextParser (PragmaProcedure SourceContext))
-> TextParser (PragmaProcedure SourceContext)
forall a.
String
-> Either (SourceContext -> a) (SourceContext -> TextParser a)
-> TextParser a
autoPragma String
"TraceCreation" (Either
(SourceContext -> PragmaProcedure SourceContext)
(SourceContext -> TextParser (PragmaProcedure SourceContext))
-> TextParser (PragmaProcedure SourceContext))
-> Either
(SourceContext -> PragmaProcedure SourceContext)
(SourceContext -> TextParser (PragmaProcedure SourceContext))
-> TextParser (PragmaProcedure SourceContext)
forall a b. (a -> b) -> a -> b
$ (SourceContext -> PragmaProcedure SourceContext)
-> Either
(SourceContext -> PragmaProcedure SourceContext)
(SourceContext -> TextParser (PragmaProcedure SourceContext))
forall a b. a -> Either a b
Left SourceContext -> PragmaProcedure SourceContext
forall c. c -> PragmaProcedure c
parseAt where
parseAt :: c -> PragmaProcedure c
parseAt c
c = [c] -> TraceType -> PragmaProcedure c
forall c. [c] -> TraceType -> PragmaProcedure c
PragmaTracing [c
c] TraceType
TraceCreation
data PragmaExpr c =
PragmaExprLookup {
PragmaExpr c -> [c]
pelContext :: [c],
PragmaExpr c -> MacroName
pelName :: MacroName
} |
PragmaSourceContext {
PragmaExpr c -> c
pscContext :: c
}
deriving (Int -> PragmaExpr c -> String -> String
[PragmaExpr c] -> String -> String
PragmaExpr c -> String
(Int -> PragmaExpr c -> String -> String)
-> (PragmaExpr c -> String)
-> ([PragmaExpr c] -> String -> String)
-> Show (PragmaExpr c)
forall c. Show c => Int -> PragmaExpr c -> String -> String
forall c. Show c => [PragmaExpr c] -> String -> String
forall c. Show c => PragmaExpr c -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PragmaExpr c] -> String -> String
$cshowList :: forall c. Show c => [PragmaExpr c] -> String -> String
show :: PragmaExpr c -> String
$cshow :: forall c. Show c => PragmaExpr c -> String
showsPrec :: Int -> PragmaExpr c -> String -> String
$cshowsPrec :: forall c. Show c => Int -> PragmaExpr c -> String -> String
Show)
pragmaExprLookup :: TextParser (PragmaExpr SourceContext)
pragmaExprLookup :: TextParser (PragmaExpr SourceContext)
pragmaExprLookup = String
-> Either
(SourceContext -> PragmaExpr SourceContext)
(SourceContext -> TextParser (PragmaExpr SourceContext))
-> TextParser (PragmaExpr SourceContext)
forall a.
String
-> Either (SourceContext -> a) (SourceContext -> TextParser a)
-> TextParser a
autoPragma String
"ExprLookup" (Either
(SourceContext -> PragmaExpr SourceContext)
(SourceContext -> TextParser (PragmaExpr SourceContext))
-> TextParser (PragmaExpr SourceContext))
-> Either
(SourceContext -> PragmaExpr SourceContext)
(SourceContext -> TextParser (PragmaExpr SourceContext))
-> TextParser (PragmaExpr SourceContext)
forall a b. (a -> b) -> a -> b
$ (SourceContext -> TextParser (PragmaExpr SourceContext))
-> Either
(SourceContext -> PragmaExpr SourceContext)
(SourceContext -> TextParser (PragmaExpr SourceContext))
forall a b. b -> Either a b
Right SourceContext -> TextParser (PragmaExpr SourceContext)
forall c.
c -> ParsecT CompilerMessage String Identity (PragmaExpr c)
parseAt where
parseAt :: c -> ParsecT CompilerMessage String Identity (PragmaExpr c)
parseAt c
c = do
MacroName
name <- TextParser MacroName
forall a. ParseFromSource a => TextParser a
sourceParser
PragmaExpr c
-> ParsecT CompilerMessage String Identity (PragmaExpr c)
forall (m :: * -> *) a. Monad m => a -> m a
return (PragmaExpr c
-> ParsecT CompilerMessage String Identity (PragmaExpr c))
-> PragmaExpr c
-> ParsecT CompilerMessage String Identity (PragmaExpr c)
forall a b. (a -> b) -> a -> b
$ [c] -> MacroName -> PragmaExpr c
forall c. [c] -> MacroName -> PragmaExpr c
PragmaExprLookup [c
c] MacroName
name
pragmaSourceContext :: TextParser (PragmaExpr SourceContext)
pragmaSourceContext :: TextParser (PragmaExpr SourceContext)
pragmaSourceContext = String
-> Either
(SourceContext -> PragmaExpr SourceContext)
(SourceContext -> TextParser (PragmaExpr SourceContext))
-> TextParser (PragmaExpr SourceContext)
forall a.
String
-> Either (SourceContext -> a) (SourceContext -> TextParser a)
-> TextParser a
autoPragma String
"SourceContext" (Either
(SourceContext -> PragmaExpr SourceContext)
(SourceContext -> TextParser (PragmaExpr SourceContext))
-> TextParser (PragmaExpr SourceContext))
-> Either
(SourceContext -> PragmaExpr SourceContext)
(SourceContext -> TextParser (PragmaExpr SourceContext))
-> TextParser (PragmaExpr SourceContext)
forall a b. (a -> b) -> a -> b
$ (SourceContext -> PragmaExpr SourceContext)
-> Either
(SourceContext -> PragmaExpr SourceContext)
(SourceContext -> TextParser (PragmaExpr SourceContext))
forall a b. a -> Either a b
Left SourceContext -> PragmaExpr SourceContext
forall c. c -> PragmaExpr c
parseAt where
parseAt :: c -> PragmaExpr c
parseAt c
c = c -> PragmaExpr c
forall c. c -> PragmaExpr c
PragmaSourceContext c
c
data MarkType = ReadOnly | Hidden deriving (Int -> MarkType -> String -> String
[MarkType] -> String -> String
MarkType -> String
(Int -> MarkType -> String -> String)
-> (MarkType -> String)
-> ([MarkType] -> String -> String)
-> Show MarkType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MarkType] -> String -> String
$cshowList :: [MarkType] -> String -> String
show :: MarkType -> String
$cshow :: MarkType -> String
showsPrec :: Int -> MarkType -> String -> String
$cshowsPrec :: Int -> MarkType -> String -> String
Show)
data PragmaStatement c =
PragmaMarkVars {
PragmaStatement c -> [c]
pmvContext :: [c],
PragmaStatement c -> MarkType
pmvType :: MarkType,
PragmaStatement c -> [VariableName]
pmvVars :: [VariableName]
}
deriving (Int -> PragmaStatement c -> String -> String
[PragmaStatement c] -> String -> String
PragmaStatement c -> String
(Int -> PragmaStatement c -> String -> String)
-> (PragmaStatement c -> String)
-> ([PragmaStatement c] -> String -> String)
-> Show (PragmaStatement c)
forall c. Show c => Int -> PragmaStatement c -> String -> String
forall c. Show c => [PragmaStatement c] -> String -> String
forall c. Show c => PragmaStatement c -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PragmaStatement c] -> String -> String
$cshowList :: forall c. Show c => [PragmaStatement c] -> String -> String
show :: PragmaStatement c -> String
$cshow :: forall c. Show c => PragmaStatement c -> String
showsPrec :: Int -> PragmaStatement c -> String -> String
$cshowsPrec :: forall c. Show c => Int -> PragmaStatement c -> String -> String
Show)
pragmaReadOnly :: TextParser (PragmaStatement SourceContext)
pragmaReadOnly :: TextParser (PragmaStatement SourceContext)
pragmaReadOnly = String
-> Either
(SourceContext -> PragmaStatement SourceContext)
(SourceContext -> TextParser (PragmaStatement SourceContext))
-> TextParser (PragmaStatement SourceContext)
forall a.
String
-> Either (SourceContext -> a) (SourceContext -> TextParser a)
-> TextParser a
autoPragma String
"ReadOnly" (Either
(SourceContext -> PragmaStatement SourceContext)
(SourceContext -> TextParser (PragmaStatement SourceContext))
-> TextParser (PragmaStatement SourceContext))
-> Either
(SourceContext -> PragmaStatement SourceContext)
(SourceContext -> TextParser (PragmaStatement SourceContext))
-> TextParser (PragmaStatement SourceContext)
forall a b. (a -> b) -> a -> b
$ (SourceContext -> TextParser (PragmaStatement SourceContext))
-> Either
(SourceContext -> PragmaStatement SourceContext)
(SourceContext -> TextParser (PragmaStatement SourceContext))
forall a b. b -> Either a b
Right SourceContext -> TextParser (PragmaStatement SourceContext)
forall c.
c -> ParsecT CompilerMessage String Identity (PragmaStatement c)
parseAt where
parseAt :: c -> ParsecT CompilerMessage String Identity (PragmaStatement c)
parseAt c
c = do
[VariableName]
vs <- String -> TextParser [VariableName] -> TextParser [VariableName]
forall a. String -> TextParser a -> TextParser a
labeled String
"variable names" (TextParser [VariableName] -> TextParser [VariableName])
-> TextParser [VariableName] -> TextParser [VariableName]
forall a b. (a -> b) -> a -> b
$ TextParser VariableName
-> TextParser String -> TextParser [VariableName]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy TextParser VariableName
forall a. ParseFromSource a => TextParser a
sourceParser (TextParser String -> TextParser String
forall a. TextParser a -> TextParser a
sepAfter (TextParser String -> TextParser String)
-> TextParser String -> TextParser String
forall a b. (a -> b) -> a -> b
$ Tokens String
-> ParsecT CompilerMessage String Identity (Tokens String)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string String
Tokens String
",")
PragmaStatement c
-> ParsecT CompilerMessage String Identity (PragmaStatement c)
forall (m :: * -> *) a. Monad m => a -> m a
return (PragmaStatement c
-> ParsecT CompilerMessage String Identity (PragmaStatement c))
-> PragmaStatement c
-> ParsecT CompilerMessage String Identity (PragmaStatement c)
forall a b. (a -> b) -> a -> b
$ [c] -> MarkType -> [VariableName] -> PragmaStatement c
forall c. [c] -> MarkType -> [VariableName] -> PragmaStatement c
PragmaMarkVars [c
c] MarkType
ReadOnly [VariableName]
vs
pragmaHidden :: TextParser (PragmaStatement SourceContext)
pragmaHidden :: TextParser (PragmaStatement SourceContext)
pragmaHidden = String
-> Either
(SourceContext -> PragmaStatement SourceContext)
(SourceContext -> TextParser (PragmaStatement SourceContext))
-> TextParser (PragmaStatement SourceContext)
forall a.
String
-> Either (SourceContext -> a) (SourceContext -> TextParser a)
-> TextParser a
autoPragma String
"Hidden" (Either
(SourceContext -> PragmaStatement SourceContext)
(SourceContext -> TextParser (PragmaStatement SourceContext))
-> TextParser (PragmaStatement SourceContext))
-> Either
(SourceContext -> PragmaStatement SourceContext)
(SourceContext -> TextParser (PragmaStatement SourceContext))
-> TextParser (PragmaStatement SourceContext)
forall a b. (a -> b) -> a -> b
$ (SourceContext -> TextParser (PragmaStatement SourceContext))
-> Either
(SourceContext -> PragmaStatement SourceContext)
(SourceContext -> TextParser (PragmaStatement SourceContext))
forall a b. b -> Either a b
Right SourceContext -> TextParser (PragmaStatement SourceContext)
forall c.
c -> ParsecT CompilerMessage String Identity (PragmaStatement c)
parseAt where
parseAt :: c -> ParsecT CompilerMessage String Identity (PragmaStatement c)
parseAt c
c = do
[VariableName]
vs <- String -> TextParser [VariableName] -> TextParser [VariableName]
forall a. String -> TextParser a -> TextParser a
labeled String
"variable names" (TextParser [VariableName] -> TextParser [VariableName])
-> TextParser [VariableName] -> TextParser [VariableName]
forall a b. (a -> b) -> a -> b
$ TextParser VariableName
-> TextParser String -> TextParser [VariableName]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy TextParser VariableName
forall a. ParseFromSource a => TextParser a
sourceParser (TextParser String -> TextParser String
forall a. TextParser a -> TextParser a
sepAfter (TextParser String -> TextParser String)
-> TextParser String -> TextParser String
forall a b. (a -> b) -> a -> b
$ Tokens String
-> ParsecT CompilerMessage String Identity (Tokens String)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string String
Tokens String
",")
PragmaStatement c
-> ParsecT CompilerMessage String Identity (PragmaStatement c)
forall (m :: * -> *) a. Monad m => a -> m a
return (PragmaStatement c
-> ParsecT CompilerMessage String Identity (PragmaStatement c))
-> PragmaStatement c
-> ParsecT CompilerMessage String Identity (PragmaStatement c)
forall a b. (a -> b) -> a -> b
$ [c] -> MarkType -> [VariableName] -> PragmaStatement c
forall c. [c] -> MarkType -> [VariableName] -> PragmaStatement c
PragmaMarkVars [c
c] MarkType
Hidden [VariableName]
vs