{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE Safe #-}
module Parser.DefinedCategory (
parseAnySource,
) where
import Control.Monad (when)
import Prelude hiding (pi)
import Text.Parsec
import Text.Parsec.String
import Parser.Common
import Parser.Procedure ()
import Parser.TypeCategory
import Parser.TypeInstance ()
import Types.DefinedCategory
import Types.Procedure
import Types.TypeCategory
import Types.TypeInstance
import Types.Variance
instance ParseFromSource (DefinedCategory SourcePos) where
sourceParser :: Parser (DefinedCategory SourcePos)
sourceParser = String
-> Parser (DefinedCategory SourcePos)
-> Parser (DefinedCategory SourcePos)
forall a. String -> Parser a -> Parser a
labeled String
"defined concrete category" (Parser (DefinedCategory SourcePos)
-> Parser (DefinedCategory SourcePos))
-> Parser (DefinedCategory SourcePos)
-> Parser (DefinedCategory SourcePos)
forall a b. (a -> b) -> a -> b
$ do
SourcePos
c <- ParsecT String () Identity SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
Parser ()
kwDefine
CategoryName
n <- Parser CategoryName
forall a. ParseFromSource a => Parser a
sourceParser
Parser () -> Parser ()
forall a. Parser a -> Parser a
sepAfter (String -> Parser ()
string_ String
"{")
([ValueRefine SourcePos]
ds,[ValueDefine SourcePos]
rs) <- ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
parseRefinesDefines
([ValueParam SourcePos]
pi,[ParamFilter SourcePos]
fi) <- Parser ([ValueParam SourcePos], [ParamFilter SourcePos])
parseInternalParams Parser ([ValueParam SourcePos], [ParamFilter SourcePos])
-> Parser ([ValueParam SourcePos], [ParamFilter SourcePos])
-> Parser ([ValueParam SourcePos], [ParamFilter SourcePos])
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ([ValueParam SourcePos], [ParamFilter SourcePos])
-> Parser ([ValueParam SourcePos], [ParamFilter SourcePos])
forall (m :: * -> *) a. Monad m => a -> m a
return ([],[])
([DefinedMember SourcePos]
ms,[ExecutableProcedure SourcePos]
ps,[ScopedFunction SourcePos]
fs) <- CategoryName
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
parseMemberProcedureFunction CategoryName
n
Parser () -> Parser ()
forall a. Parser a -> Parser a
sepAfter (String -> Parser ()
string_ String
"}")
DefinedCategory SourcePos -> Parser (DefinedCategory SourcePos)
forall (m :: * -> *) a. Monad m => a -> m a
return (DefinedCategory SourcePos -> Parser (DefinedCategory SourcePos))
-> DefinedCategory SourcePos -> Parser (DefinedCategory SourcePos)
forall a b. (a -> b) -> a -> b
$ [SourcePos]
-> CategoryName
-> [ValueParam SourcePos]
-> [ValueRefine SourcePos]
-> [ValueDefine SourcePos]
-> [ParamFilter SourcePos]
-> [DefinedMember SourcePos]
-> [ExecutableProcedure SourcePos]
-> [ScopedFunction SourcePos]
-> DefinedCategory SourcePos
forall c.
[c]
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ValueDefine c]
-> [ParamFilter c]
-> [DefinedMember c]
-> [ExecutableProcedure c]
-> [ScopedFunction c]
-> DefinedCategory c
DefinedCategory [SourcePos
c] CategoryName
n [ValueParam SourcePos]
pi [ValueRefine SourcePos]
ds [ValueDefine SourcePos]
rs [ParamFilter SourcePos]
fi [DefinedMember SourcePos]
ms [ExecutableProcedure SourcePos]
ps [ScopedFunction SourcePos]
fs
where
parseRefinesDefines :: ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
parseRefinesDefines = ([([ValueRefine SourcePos], [ValueDefine SourcePos])]
-> ([ValueRefine SourcePos], [ValueDefine SourcePos]))
-> ParsecT
String
()
Identity
[([ValueRefine SourcePos], [ValueDefine SourcePos])]
-> ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [([ValueRefine SourcePos], [ValueDefine SourcePos])]
-> ([ValueRefine SourcePos], [ValueDefine SourcePos])
forall (f :: * -> *) a b.
(Foldable f, Monoid a, Monoid b) =>
f (a, b) -> (a, b)
merge2 (ParsecT
String
()
Identity
[([ValueRefine SourcePos], [ValueDefine SourcePos])]
-> ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos]))
-> ParsecT
String
()
Identity
[([ValueRefine SourcePos], [ValueDefine SourcePos])]
-> ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
forall a b. (a -> b) -> a -> b
$ ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
-> Parser ()
-> ParsecT
String
()
Identity
[([ValueRefine SourcePos], [ValueDefine SourcePos])]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
refineOrDefine Parser ()
optionalSpace
refineOrDefine :: ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
refineOrDefine = String
-> ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
-> ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
forall a. String -> Parser a -> Parser a
labeled String
"refine or define" (ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
-> ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos]))
-> ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
-> ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
forall a b. (a -> b) -> a -> b
$ ParsecT String () Identity (ValueRefine SourcePos)
-> ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
forall (m :: * -> *) a b.
(Functor m, Monad m) =>
m a -> m ([a], [b])
put12 ParsecT String () Identity (ValueRefine SourcePos)
singleRefine ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
-> ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
-> ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String () Identity (ValueDefine SourcePos)
-> ParsecT
String
()
Identity
([ValueRefine SourcePos], [ValueDefine SourcePos])
forall (m :: * -> *) b a.
(Functor m, Monad m) =>
m b -> m ([a], [b])
put22 ParsecT String () Identity (ValueDefine SourcePos)
singleDefine
parseInternalParams :: Parser ([ValueParam SourcePos], [ParamFilter SourcePos])
parseInternalParams = String
-> Parser ([ValueParam SourcePos], [ParamFilter SourcePos])
-> Parser ([ValueParam SourcePos], [ParamFilter SourcePos])
forall a. String -> Parser a -> Parser a
labeled String
"internal params" (Parser ([ValueParam SourcePos], [ParamFilter SourcePos])
-> Parser ([ValueParam SourcePos], [ParamFilter SourcePos]))
-> Parser ([ValueParam SourcePos], [ParamFilter SourcePos])
-> Parser ([ValueParam SourcePos], [ParamFilter SourcePos])
forall a b. (a -> b) -> a -> b
$ do
Parser () -> Parser ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parser ()
kwTypes
[ValueParam SourcePos]
pi <- Parser ()
-> Parser ()
-> ParsecT String () Identity [ValueParam SourcePos]
-> ParsecT String () Identity [ValueParam SourcePos]
forall s (m :: * -> *) t u open close a.
Stream s m t =>
ParsecT s u m open
-> ParsecT s u m close -> ParsecT s u m a -> ParsecT s u m a
between (Parser () -> Parser ()
forall a. Parser a -> Parser a
sepAfter (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ String -> Parser ()
string_ String
"<")
(Parser () -> Parser ()
forall a. Parser a -> Parser a
sepAfter (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ String -> Parser ()
string_ String
">")
(ParsecT String () Identity (ValueParam SourcePos)
-> Parser () -> ParsecT String () Identity [ValueParam SourcePos]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy ParsecT String () Identity (ValueParam SourcePos)
singleParam (Parser () -> Parser ()
forall a. Parser a -> Parser a
sepAfter (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ String -> Parser ()
string_ String
","))
[ParamFilter SourcePos]
fi <- ParsecT String () Identity [ParamFilter SourcePos]
parseInternalFilters
([ValueParam SourcePos], [ParamFilter SourcePos])
-> Parser ([ValueParam SourcePos], [ParamFilter SourcePos])
forall (m :: * -> *) a. Monad m => a -> m a
return ([ValueParam SourcePos]
pi,[ParamFilter SourcePos]
fi)
parseInternalFilters :: ParsecT String () Identity [ParamFilter SourcePos]
parseInternalFilters = do
Parser () -> Parser ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ Parser () -> Parser ()
forall a. Parser a -> Parser a
sepAfter (String -> Parser ()
string_ String
"{")
[ParamFilter SourcePos]
fi <- ParsecT String () Identity [ParamFilter SourcePos]
parseFilters
Parser () -> Parser ()
forall a. Parser a -> Parser a
sepAfter (String -> Parser ()
string_ String
"}")
[ParamFilter SourcePos]
-> ParsecT String () Identity [ParamFilter SourcePos]
forall (m :: * -> *) a. Monad m => a -> m a
return [ParamFilter SourcePos]
fi
singleParam :: ParsecT String () Identity (ValueParam SourcePos)
singleParam = String
-> ParsecT String () Identity (ValueParam SourcePos)
-> ParsecT String () Identity (ValueParam SourcePos)
forall a. String -> Parser a -> Parser a
labeled String
"param declaration" (ParsecT String () Identity (ValueParam SourcePos)
-> ParsecT String () Identity (ValueParam SourcePos))
-> ParsecT String () Identity (ValueParam SourcePos)
-> ParsecT String () Identity (ValueParam SourcePos)
forall a b. (a -> b) -> a -> b
$ do
SourcePos
c <- ParsecT String () Identity SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
ParamName
n <- Parser ParamName
forall a. ParseFromSource a => Parser a
sourceParser
ValueParam SourcePos
-> ParsecT String () Identity (ValueParam SourcePos)
forall (m :: * -> *) a. Monad m => a -> m a
return (ValueParam SourcePos
-> ParsecT String () Identity (ValueParam SourcePos))
-> ValueParam SourcePos
-> ParsecT String () Identity (ValueParam SourcePos)
forall a b. (a -> b) -> a -> b
$ [SourcePos] -> ParamName -> Variance -> ValueParam SourcePos
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [SourcePos
c] ParamName
n Variance
Invariant
instance ParseFromSource (DefinedMember SourcePos) where
sourceParser :: Parser (DefinedMember SourcePos)
sourceParser = String
-> Parser (DefinedMember SourcePos)
-> Parser (DefinedMember SourcePos)
forall a. String -> Parser a -> Parser a
labeled String
"defined member" (Parser (DefinedMember SourcePos)
-> Parser (DefinedMember SourcePos))
-> Parser (DefinedMember SourcePos)
-> Parser (DefinedMember SourcePos)
forall a b. (a -> b) -> a -> b
$ do
SourcePos
c <- ParsecT String () Identity SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
(SymbolScope
s,ValueType
t) <- ParsecT String () Identity (SymbolScope, ValueType)
-> ParsecT String () Identity (SymbolScope, ValueType)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT String () Identity (SymbolScope, ValueType)
parseType
VariableName
n <- Parser VariableName
forall a. ParseFromSource a => Parser a
sourceParser
Maybe (Expression SourcePos)
e <- if SymbolScope
s SymbolScope -> SymbolScope -> Bool
forall a. Eq a => a -> a -> Bool
== SymbolScope
ValueScope
then Maybe (Expression SourcePos)
-> ParsecT String () Identity (Maybe (Expression SourcePos))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Expression SourcePos)
forall a. Maybe a
Nothing
else ParsecT String () Identity (Maybe (Expression SourcePos))
parseInit
DefinedMember SourcePos -> Parser (DefinedMember SourcePos)
forall (m :: * -> *) a. Monad m => a -> m a
return (DefinedMember SourcePos -> Parser (DefinedMember SourcePos))
-> DefinedMember SourcePos -> Parser (DefinedMember SourcePos)
forall a b. (a -> b) -> a -> b
$ [SourcePos]
-> SymbolScope
-> ValueType
-> VariableName
-> Maybe (Expression SourcePos)
-> DefinedMember SourcePos
forall c.
[c]
-> SymbolScope
-> ValueType
-> VariableName
-> Maybe (Expression c)
-> DefinedMember c
DefinedMember [SourcePos
c] SymbolScope
s ValueType
t VariableName
n Maybe (Expression SourcePos)
e
where
parseInit :: ParsecT String () Identity (Maybe (Expression SourcePos))
parseInit = String
-> ParsecT String () Identity (Maybe (Expression SourcePos))
-> ParsecT String () Identity (Maybe (Expression SourcePos))
forall a. String -> Parser a -> Parser a
labeled String
"member initializer" (ParsecT String () Identity (Maybe (Expression SourcePos))
-> ParsecT String () Identity (Maybe (Expression SourcePos)))
-> ParsecT String () Identity (Maybe (Expression SourcePos))
-> ParsecT String () Identity (Maybe (Expression SourcePos))
forall a b. (a -> b) -> a -> b
$ do
Parser ()
assignOperator
Expression SourcePos
e <- Parser (Expression SourcePos)
forall a. ParseFromSource a => Parser a
sourceParser
Maybe (Expression SourcePos)
-> ParsecT String () Identity (Maybe (Expression SourcePos))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (Expression SourcePos)
-> ParsecT String () Identity (Maybe (Expression SourcePos)))
-> Maybe (Expression SourcePos)
-> ParsecT String () Identity (Maybe (Expression SourcePos))
forall a b. (a -> b) -> a -> b
$ Expression SourcePos -> Maybe (Expression SourcePos)
forall a. a -> Maybe a
Just Expression SourcePos
e
parseType :: ParsecT String () Identity (SymbolScope, ValueType)
parseType = do
SymbolScope
s <- Parser SymbolScope
parseScope
ValueType
t <- Parser ValueType
forall a. ParseFromSource a => Parser a
sourceParser
(SymbolScope, ValueType)
-> ParsecT String () Identity (SymbolScope, ValueType)
forall (m :: * -> *) a. Monad m => a -> m a
return (SymbolScope
s,ValueType
t)
parseMemberProcedureFunction ::
CategoryName ->
Parser ([DefinedMember SourcePos],[ExecutableProcedure SourcePos],[ScopedFunction SourcePos])
parseMemberProcedureFunction :: CategoryName
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
parseMemberProcedureFunction CategoryName
n = ParsecT
String
()
Identity
[([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])]
parsed ParsecT
String
()
Identity
[([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])]
-> ([([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])]
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos]))
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall (m :: * -> *) a. Monad m => a -> m a
return (([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos]))
-> ([([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])]
-> ([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos]))
-> [([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])]
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> ([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> ([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos]))
-> ([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> [([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])]
-> ([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> ([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> ([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall a a a. ([a], [a], [a]) -> ([a], [a], [a]) -> ([a], [a], [a])
merge ([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall a a a. ([a], [a], [a])
empty where
empty :: ([a], [a], [a])
empty = ([],[],[])
merge :: ([a], [a], [a]) -> ([a], [a], [a]) -> ([a], [a], [a])
merge ([a]
ms1,[a]
ps1,[a]
fs1) ([a]
ms2,[a]
ps2,[a]
fs2) = ([a]
ms1[a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++[a]
ms2,[a]
ps1[a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++[a]
ps2,[a]
fs1[a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++[a]
fs2)
parsed :: ParsecT
String
()
Identity
[([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])]
parsed = Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> Parser ()
-> ParsecT
String
()
Identity
[([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
anyType Parser ()
optionalSpace
anyType :: Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
anyType = String
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall a. String -> Parser a -> Parser a
labeled String
"" (Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos]))
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall a b. (a -> b) -> a -> b
$ Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall b. ParsecT String () Identity b
catchUnscopedType Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall a a. Parser ([DefinedMember SourcePos], [a], [a])
singleMember Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall a a. Parser ([a], [ExecutableProcedure SourcePos], [a])
singleProcedure Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
-> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Parser
([DefinedMember SourcePos], [ExecutableProcedure SourcePos],
[ScopedFunction SourcePos])
forall a.
Parser
([a], [ExecutableProcedure SourcePos], [ScopedFunction SourcePos])
singleFunction
singleMember :: Parser ([DefinedMember SourcePos], [a], [a])
singleMember = String
-> Parser ([DefinedMember SourcePos], [a], [a])
-> Parser ([DefinedMember SourcePos], [a], [a])
forall a. String -> Parser a -> Parser a
labeled String
"member" (Parser ([DefinedMember SourcePos], [a], [a])
-> Parser ([DefinedMember SourcePos], [a], [a]))
-> Parser ([DefinedMember SourcePos], [a], [a])
-> Parser ([DefinedMember SourcePos], [a], [a])
forall a b. (a -> b) -> a -> b
$ do
DefinedMember SourcePos
m <- Parser (DefinedMember SourcePos)
forall a. ParseFromSource a => Parser a
sourceParser
([DefinedMember SourcePos], [a], [a])
-> Parser ([DefinedMember SourcePos], [a], [a])
forall (m :: * -> *) a. Monad m => a -> m a
return ([DefinedMember SourcePos
m],[],[])
singleProcedure :: Parser ([a], [ExecutableProcedure SourcePos], [a])
singleProcedure = String
-> Parser ([a], [ExecutableProcedure SourcePos], [a])
-> Parser ([a], [ExecutableProcedure SourcePos], [a])
forall a. String -> Parser a -> Parser a
labeled String
"procedure" (Parser ([a], [ExecutableProcedure SourcePos], [a])
-> Parser ([a], [ExecutableProcedure SourcePos], [a]))
-> Parser ([a], [ExecutableProcedure SourcePos], [a])
-> Parser ([a], [ExecutableProcedure SourcePos], [a])
forall a b. (a -> b) -> a -> b
$ do
ExecutableProcedure SourcePos
p <- Parser (ExecutableProcedure SourcePos)
forall a. ParseFromSource a => Parser a
sourceParser
([a], [ExecutableProcedure SourcePos], [a])
-> Parser ([a], [ExecutableProcedure SourcePos], [a])
forall (m :: * -> *) a. Monad m => a -> m a
return ([],[ExecutableProcedure SourcePos
p],[])
singleFunction :: Parser
([a], [ExecutableProcedure SourcePos], [ScopedFunction SourcePos])
singleFunction = String
-> Parser
([a], [ExecutableProcedure SourcePos], [ScopedFunction SourcePos])
-> Parser
([a], [ExecutableProcedure SourcePos], [ScopedFunction SourcePos])
forall a. String -> Parser a -> Parser a
labeled String
"function" (Parser
([a], [ExecutableProcedure SourcePos], [ScopedFunction SourcePos])
-> Parser
([a], [ExecutableProcedure SourcePos], [ScopedFunction SourcePos]))
-> Parser
([a], [ExecutableProcedure SourcePos], [ScopedFunction SourcePos])
-> Parser
([a], [ExecutableProcedure SourcePos], [ScopedFunction SourcePos])
forall a b. (a -> b) -> a -> b
$ do
ScopedFunction SourcePos
f <- ParsecT String () Identity (ScopedFunction SourcePos)
-> ParsecT String () Identity (ScopedFunction SourcePos)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT String () Identity (ScopedFunction SourcePos)
-> ParsecT String () Identity (ScopedFunction SourcePos))
-> ParsecT String () Identity (ScopedFunction SourcePos)
-> ParsecT String () Identity (ScopedFunction SourcePos)
forall a b. (a -> b) -> a -> b
$ Parser SymbolScope
-> Parser CategoryName
-> ParsecT String () Identity (ScopedFunction SourcePos)
parseScopedFunction Parser SymbolScope
parseScope (CategoryName -> Parser CategoryName
forall (m :: * -> *) a. Monad m => a -> m a
return CategoryName
n)
ExecutableProcedure SourcePos
p <- String
-> Parser (ExecutableProcedure SourcePos)
-> Parser (ExecutableProcedure SourcePos)
forall a. String -> Parser a -> Parser a
labeled (String
"definition of function " String -> String -> String
forall a. [a] -> [a] -> [a]
++ FunctionName -> String
forall a. Show a => a -> String
show (ScopedFunction SourcePos -> FunctionName
forall c. ScopedFunction c -> FunctionName
sfName ScopedFunction SourcePos
f)) (Parser (ExecutableProcedure SourcePos)
-> Parser (ExecutableProcedure SourcePos))
-> Parser (ExecutableProcedure SourcePos)
-> Parser (ExecutableProcedure SourcePos)
forall a b. (a -> b) -> a -> b
$ Parser (ExecutableProcedure SourcePos)
forall a. ParseFromSource a => Parser a
sourceParser
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ScopedFunction SourcePos -> FunctionName
forall c. ScopedFunction c -> FunctionName
sfName ScopedFunction SourcePos
f FunctionName -> FunctionName -> Bool
forall a. Eq a => a -> a -> Bool
/= ExecutableProcedure SourcePos -> FunctionName
forall c. ExecutableProcedure c -> FunctionName
epName ExecutableProcedure SourcePos
p) (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ()) -> String -> Parser ()
forall a b. (a -> b) -> a -> b
$ String
"expecting definition of function " String -> String -> String
forall a. [a] -> [a] -> [a]
++ FunctionName -> String
forall a. Show a => a -> String
show (ScopedFunction SourcePos -> FunctionName
forall c. ScopedFunction c -> FunctionName
sfName ScopedFunction SourcePos
f) String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
" but got definition of " String -> String -> String
forall a. [a] -> [a] -> [a]
++ FunctionName -> String
forall a. Show a => a -> String
show (ExecutableProcedure SourcePos -> FunctionName
forall c. ExecutableProcedure c -> FunctionName
epName ExecutableProcedure SourcePos
p)
([a], [ExecutableProcedure SourcePos], [ScopedFunction SourcePos])
-> Parser
([a], [ExecutableProcedure SourcePos], [ScopedFunction SourcePos])
forall (m :: * -> *) a. Monad m => a -> m a
return ([],[ExecutableProcedure SourcePos
p],[ScopedFunction SourcePos
f])
catchUnscopedType :: ParsecT String () Identity b
catchUnscopedType = do
ValueType
_ <- Parser ValueType -> Parser ValueType
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try Parser ValueType
forall a. ParseFromSource a => Parser a
sourceParser :: Parser ValueType
String -> ParsecT String () Identity b
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> ParsecT String () Identity b)
-> String -> ParsecT String () Identity b
forall a b. (a -> b) -> a -> b
$ String
"members must have an explicit @value or @category scope"
parseAnySource :: Parser ([AnyCategory SourcePos],[DefinedCategory SourcePos])
parseAnySource :: Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos])
parseAnySource = ParsecT
String
()
Identity
[([AnyCategory SourcePos], [DefinedCategory SourcePos])]
parsed ParsecT
String
()
Identity
[([AnyCategory SourcePos], [DefinedCategory SourcePos])]
-> ([([AnyCategory SourcePos], [DefinedCategory SourcePos])]
-> Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos]))
-> Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ([AnyCategory SourcePos], [DefinedCategory SourcePos])
-> Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos])
forall (m :: * -> *) a. Monad m => a -> m a
return (([AnyCategory SourcePos], [DefinedCategory SourcePos])
-> Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos]))
-> ([([AnyCategory SourcePos], [DefinedCategory SourcePos])]
-> ([AnyCategory SourcePos], [DefinedCategory SourcePos]))
-> [([AnyCategory SourcePos], [DefinedCategory SourcePos])]
-> Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([AnyCategory SourcePos], [DefinedCategory SourcePos])
-> ([AnyCategory SourcePos], [DefinedCategory SourcePos])
-> ([AnyCategory SourcePos], [DefinedCategory SourcePos]))
-> ([AnyCategory SourcePos], [DefinedCategory SourcePos])
-> [([AnyCategory SourcePos], [DefinedCategory SourcePos])]
-> ([AnyCategory SourcePos], [DefinedCategory SourcePos])
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ([AnyCategory SourcePos], [DefinedCategory SourcePos])
-> ([AnyCategory SourcePos], [DefinedCategory SourcePos])
-> ([AnyCategory SourcePos], [DefinedCategory SourcePos])
forall a a. ([a], [a]) -> ([a], [a]) -> ([a], [a])
merge ([AnyCategory SourcePos], [DefinedCategory SourcePos])
forall a a. ([a], [a])
empty where
empty :: ([a], [a])
empty = ([],[])
merge :: ([a], [a]) -> ([a], [a]) -> ([a], [a])
merge ([a]
cs1,[a]
ds1) ([a]
cs2,[a]
ds2) = ([a]
cs1[a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++[a]
cs2,[a]
ds1[a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++[a]
ds2)
parsed :: ParsecT
String
()
Identity
[([AnyCategory SourcePos], [DefinedCategory SourcePos])]
parsed = Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos])
-> Parser ()
-> ParsecT
String
()
Identity
[([AnyCategory SourcePos], [DefinedCategory SourcePos])]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos])
anyType Parser ()
optionalSpace
anyType :: Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos])
anyType = Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos])
forall a. ParsecT String () Identity ([AnyCategory SourcePos], [a])
singleCategory Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos])
-> Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos])
-> Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos])
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Parser ([AnyCategory SourcePos], [DefinedCategory SourcePos])
forall a.
ParsecT String () Identity ([a], [DefinedCategory SourcePos])
singleDefine2
singleCategory :: ParsecT String () Identity ([AnyCategory SourcePos], [a])
singleCategory = do
AnyCategory SourcePos
c <- Parser (AnyCategory SourcePos)
forall a. ParseFromSource a => Parser a
sourceParser
([AnyCategory SourcePos], [a])
-> ParsecT String () Identity ([AnyCategory SourcePos], [a])
forall (m :: * -> *) a. Monad m => a -> m a
return ([AnyCategory SourcePos
c],[])
singleDefine2 :: ParsecT String () Identity ([a], [DefinedCategory SourcePos])
singleDefine2 = do
DefinedCategory SourcePos
d <- Parser (DefinedCategory SourcePos)
forall a. ParseFromSource a => Parser a
sourceParser
([a], [DefinedCategory SourcePos])
-> ParsecT String () Identity ([a], [DefinedCategory SourcePos])
forall (m :: * -> *) a. Monad m => a -> m a
return ([],[DefinedCategory SourcePos
d])