{-# LANGUAGE FlexibleInstances #-}
module Parser.DefinedCategory (
) where
import Prelude hiding (pi)
import Base.CompilerError
import Parser.Common
import Parser.Procedure ()
import Parser.TextParser
import Parser.TypeCategory
import Parser.TypeInstance ()
import Types.DefinedCategory
import Types.Procedure
import Types.TypeCategory
import Types.TypeInstance
import Types.Variance
instance ParseFromSource (DefinedCategory SourceContext) where
sourceParser :: TextParser (DefinedCategory SourceContext)
sourceParser = String
-> TextParser (DefinedCategory SourceContext)
-> TextParser (DefinedCategory SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"defined concrete category" (TextParser (DefinedCategory SourceContext)
-> TextParser (DefinedCategory SourceContext))
-> TextParser (DefinedCategory SourceContext)
-> TextParser (DefinedCategory SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
TextParser ()
kwDefine
CategoryName
n <- TextParser CategoryName
forall a. ParseFromSource a => TextParser a
sourceParser
TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (String -> TextParser ()
string_ String
"{")
([ValueRefine SourceContext]
ds,[ValueDefine SourceContext]
rs) <- ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
parseRefinesDefines
([ValueParam SourceContext]
pi,[ParamFilter SourceContext]
fi) <- TextParser
([ValueParam SourceContext], [ParamFilter SourceContext])
parseInternalParams TextParser
([ValueParam SourceContext], [ParamFilter SourceContext])
-> TextParser
([ValueParam SourceContext], [ParamFilter SourceContext])
-> TextParser
([ValueParam SourceContext], [ParamFilter SourceContext])
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ([ValueParam SourceContext], [ParamFilter SourceContext])
-> TextParser
([ValueParam SourceContext], [ParamFilter SourceContext])
forall (m :: * -> *) a. Monad m => a -> m a
return ([],[])
([DefinedMember SourceContext]
ms,[ExecutableProcedure SourceContext]
ps,[ScopedFunction SourceContext]
fs) <- CategoryName
-> TextParser
([DefinedMember SourceContext],
[ExecutableProcedure SourceContext],
[ScopedFunction SourceContext])
parseMemberProcedureFunction CategoryName
n
TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (String -> TextParser ()
string_ String
"}")
DefinedCategory SourceContext
-> TextParser (DefinedCategory SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (DefinedCategory SourceContext
-> TextParser (DefinedCategory SourceContext))
-> DefinedCategory SourceContext
-> TextParser (DefinedCategory SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> CategoryName
-> [ValueParam SourceContext]
-> [ValueRefine SourceContext]
-> [ValueDefine SourceContext]
-> [ParamFilter SourceContext]
-> [DefinedMember SourceContext]
-> [ExecutableProcedure SourceContext]
-> [ScopedFunction SourceContext]
-> DefinedCategory SourceContext
forall c.
[c]
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ValueDefine c]
-> [ParamFilter c]
-> [DefinedMember c]
-> [ExecutableProcedure c]
-> [ScopedFunction c]
-> DefinedCategory c
DefinedCategory [SourceContext
c] CategoryName
n [ValueParam SourceContext]
pi [ValueRefine SourceContext]
ds [ValueDefine SourceContext]
rs [ParamFilter SourceContext]
fi [DefinedMember SourceContext]
ms [ExecutableProcedure SourceContext]
ps [ScopedFunction SourceContext]
fs
where
parseRefinesDefines :: ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
parseRefinesDefines = ([([ValueRefine SourceContext], [ValueDefine SourceContext])]
-> ([ValueRefine SourceContext], [ValueDefine SourceContext]))
-> ParsecT
CompilerMessage
String
Identity
[([ValueRefine SourceContext], [ValueDefine SourceContext])]
-> ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [([ValueRefine SourceContext], [ValueDefine SourceContext])]
-> ([ValueRefine SourceContext], [ValueDefine SourceContext])
forall (f :: * -> *) a b.
(Foldable f, Monoid a, Monoid b) =>
f (a, b) -> (a, b)
merge2 (ParsecT
CompilerMessage
String
Identity
[([ValueRefine SourceContext], [ValueDefine SourceContext])]
-> ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext]))
-> ParsecT
CompilerMessage
String
Identity
[([ValueRefine SourceContext], [ValueDefine SourceContext])]
-> ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
forall a b. (a -> b) -> a -> b
$ ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
-> TextParser ()
-> ParsecT
CompilerMessage
String
Identity
[([ValueRefine SourceContext], [ValueDefine SourceContext])]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
refineOrDefine TextParser ()
optionalSpace
refineOrDefine :: ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
refineOrDefine = String
-> ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
-> ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
forall a. String -> TextParser a -> TextParser a
labeled String
"refine or define" (ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
-> ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext]))
-> ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
-> ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
forall a b. (a -> b) -> a -> b
$ ParsecT CompilerMessage String Identity (ValueRefine SourceContext)
-> ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
forall (m :: * -> *) a b.
(Functor m, Monad m) =>
m a -> m ([a], [b])
put12 ParsecT CompilerMessage String Identity (ValueRefine SourceContext)
singleRefine ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
-> ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
-> ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT CompilerMessage String Identity (ValueDefine SourceContext)
-> ParsecT
CompilerMessage
String
Identity
([ValueRefine SourceContext], [ValueDefine SourceContext])
forall (m :: * -> *) b a.
(Functor m, Monad m) =>
m b -> m ([a], [b])
put22 ParsecT CompilerMessage String Identity (ValueDefine SourceContext)
singleDefine
parseInternalParams :: TextParser
([ValueParam SourceContext], [ParamFilter SourceContext])
parseInternalParams = String
-> TextParser
([ValueParam SourceContext], [ParamFilter SourceContext])
-> TextParser
([ValueParam SourceContext], [ParamFilter SourceContext])
forall a. String -> TextParser a -> TextParser a
labeled String
"internal params" (TextParser
([ValueParam SourceContext], [ParamFilter SourceContext])
-> TextParser
([ValueParam SourceContext], [ParamFilter SourceContext]))
-> TextParser
([ValueParam SourceContext], [ParamFilter SourceContext])
-> TextParser
([ValueParam SourceContext], [ParamFilter SourceContext])
forall a b. (a -> b) -> a -> b
$ do
TextParser ()
kwTypes
[ValueParam SourceContext]
pi <- TextParser ()
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [ValueParam SourceContext]
-> ParsecT
CompilerMessage String Identity [ValueParam 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 (ValueParam SourceContext)
-> TextParser ()
-> ParsecT
CompilerMessage String Identity [ValueParam SourceContext]
forall (m :: * -> *) a sep. MonadPlus m => m a -> m sep -> m [a]
sepBy ParsecT CompilerMessage String Identity (ValueParam SourceContext)
singleParam (TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String -> TextParser ()
string_ String
","))
[ParamFilter SourceContext]
fi <- ParsecT CompilerMessage String Identity [ParamFilter SourceContext]
parseInternalFilters
([ValueParam SourceContext], [ParamFilter SourceContext])
-> TextParser
([ValueParam SourceContext], [ParamFilter SourceContext])
forall (m :: * -> *) a. Monad m => a -> m a
return ([ValueParam SourceContext]
pi,[ParamFilter SourceContext]
fi)
parseInternalFilters :: ParsecT CompilerMessage String Identity [ParamFilter SourceContext]
parseInternalFilters = do
TextParser () -> TextParser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (TextParser () -> TextParser ()) -> TextParser () -> TextParser ()
forall a b. (a -> b) -> a -> b
$ TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (String -> TextParser ()
string_ String
"{")
[ParamFilter SourceContext]
fi <- ParsecT CompilerMessage String Identity [ParamFilter SourceContext]
parseFilters
TextParser () -> TextParser ()
forall a. TextParser a -> TextParser a
sepAfter (String -> TextParser ()
string_ String
"}")
[ParamFilter SourceContext]
-> ParsecT
CompilerMessage String Identity [ParamFilter SourceContext]
forall (m :: * -> *) a. Monad m => a -> m a
return [ParamFilter SourceContext]
fi
singleParam :: ParsecT CompilerMessage String Identity (ValueParam SourceContext)
singleParam = String
-> ParsecT
CompilerMessage String Identity (ValueParam SourceContext)
-> ParsecT
CompilerMessage String Identity (ValueParam SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"param declaration" (ParsecT CompilerMessage String Identity (ValueParam SourceContext)
-> ParsecT
CompilerMessage String Identity (ValueParam SourceContext))
-> ParsecT
CompilerMessage String Identity (ValueParam SourceContext)
-> ParsecT
CompilerMessage String Identity (ValueParam SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
ParamName
n <- TextParser ParamName
forall a. ParseFromSource a => TextParser a
sourceParser
ValueParam SourceContext
-> ParsecT
CompilerMessage String Identity (ValueParam SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ValueParam SourceContext
-> ParsecT
CompilerMessage String Identity (ValueParam SourceContext))
-> ValueParam SourceContext
-> ParsecT
CompilerMessage String Identity (ValueParam SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> ParamName -> Variance -> ValueParam SourceContext
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [SourceContext
c] ParamName
n Variance
Invariant
instance ParseFromSource (DefinedMember SourceContext) where
sourceParser :: TextParser (DefinedMember SourceContext)
sourceParser = String
-> TextParser (DefinedMember SourceContext)
-> TextParser (DefinedMember SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"defined member" (TextParser (DefinedMember SourceContext)
-> TextParser (DefinedMember SourceContext))
-> TextParser (DefinedMember SourceContext)
-> TextParser (DefinedMember SourceContext)
forall a b. (a -> b) -> a -> b
$ do
SourceContext
c <- TextParser SourceContext
getSourceContext
(SymbolScope
s,ValueType
t) <- ParsecT CompilerMessage String Identity (SymbolScope, ValueType)
-> ParsecT CompilerMessage String Identity (SymbolScope, ValueType)
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT CompilerMessage String Identity (SymbolScope, ValueType)
parseType
VariableName
n <- TextParser VariableName
forall a. ParseFromSource a => TextParser a
sourceParser
Maybe (Expression SourceContext)
e <- if SymbolScope
s SymbolScope -> SymbolScope -> Bool
forall a. Eq a => a -> a -> Bool
== SymbolScope
ValueScope
then Maybe (Expression SourceContext)
-> ParsecT
CompilerMessage String Identity (Maybe (Expression SourceContext))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Expression SourceContext)
forall a. Maybe a
Nothing
else ParsecT
CompilerMessage String Identity (Maybe (Expression SourceContext))
parseInit
DefinedMember SourceContext
-> TextParser (DefinedMember SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (DefinedMember SourceContext
-> TextParser (DefinedMember SourceContext))
-> DefinedMember SourceContext
-> TextParser (DefinedMember SourceContext)
forall a b. (a -> b) -> a -> b
$ [SourceContext]
-> SymbolScope
-> ValueType
-> VariableName
-> Maybe (Expression SourceContext)
-> DefinedMember SourceContext
forall c.
[c]
-> SymbolScope
-> ValueType
-> VariableName
-> Maybe (Expression c)
-> DefinedMember c
DefinedMember [SourceContext
c] SymbolScope
s ValueType
t VariableName
n Maybe (Expression SourceContext)
e
where
parseInit :: ParsecT
CompilerMessage String Identity (Maybe (Expression SourceContext))
parseInit = String
-> ParsecT
CompilerMessage String Identity (Maybe (Expression SourceContext))
-> ParsecT
CompilerMessage String Identity (Maybe (Expression SourceContext))
forall a. String -> TextParser a -> TextParser a
labeled String
"member initializer" (ParsecT
CompilerMessage String Identity (Maybe (Expression SourceContext))
-> ParsecT
CompilerMessage String Identity (Maybe (Expression SourceContext)))
-> ParsecT
CompilerMessage String Identity (Maybe (Expression SourceContext))
-> ParsecT
CompilerMessage String Identity (Maybe (Expression SourceContext))
forall a b. (a -> b) -> a -> b
$ do
TextParser ()
assignOperator
Expression SourceContext
e <- TextParser (Expression SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
Maybe (Expression SourceContext)
-> ParsecT
CompilerMessage String Identity (Maybe (Expression SourceContext))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (Expression SourceContext)
-> ParsecT
CompilerMessage String Identity (Maybe (Expression SourceContext)))
-> Maybe (Expression SourceContext)
-> ParsecT
CompilerMessage String Identity (Maybe (Expression SourceContext))
forall a b. (a -> b) -> a -> b
$ Expression SourceContext -> Maybe (Expression SourceContext)
forall a. a -> Maybe a
Just Expression SourceContext
e
parseType :: ParsecT CompilerMessage String Identity (SymbolScope, ValueType)
parseType = do
SymbolScope
s <- TextParser SymbolScope
parseScope
ValueType
t <- TextParser ValueType
forall a. ParseFromSource a => TextParser a
sourceParser
(SymbolScope, ValueType)
-> ParsecT CompilerMessage String Identity (SymbolScope, ValueType)
forall (m :: * -> *) a. Monad m => a -> m a
return (SymbolScope
s,ValueType
t)
parseMemberProcedureFunction ::
CategoryName -> TextParser ([DefinedMember SourceContext],
[ExecutableProcedure SourceContext],
[ScopedFunction SourceContext])
parseMemberProcedureFunction :: CategoryName
-> TextParser
([DefinedMember SourceContext],
[ExecutableProcedure SourceContext],
[ScopedFunction SourceContext])
parseMemberProcedureFunction CategoryName
n = do
([DefinedMember SourceContext]
ms,[ExecutableProcedure SourceContext]
ps,[(ScopedFunction SourceContext, ExecutableProcedure SourceContext)]
fs) <- TextParser (DefinedMember SourceContext)
-> TextParser (ExecutableProcedure SourceContext)
-> TextParser
(ScopedFunction SourceContext, ExecutableProcedure SourceContext)
-> TextParser
([DefinedMember SourceContext],
[ExecutableProcedure SourceContext],
[(ScopedFunction SourceContext,
ExecutableProcedure SourceContext)])
forall a b c.
TextParser a
-> TextParser b -> TextParser c -> TextParser ([a], [b], [c])
parseAny3 (TextParser (DefinedMember SourceContext)
forall a. TextParser a
catchUnscopedType TextParser (DefinedMember SourceContext)
-> TextParser (DefinedMember SourceContext)
-> TextParser (DefinedMember SourceContext)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextParser (DefinedMember SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser) TextParser (ExecutableProcedure SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser TextParser
(ScopedFunction SourceContext, ExecutableProcedure SourceContext)
singleFunction
let ps2 :: [ExecutableProcedure SourceContext]
ps2 = [ExecutableProcedure SourceContext]
ps [ExecutableProcedure SourceContext]
-> [ExecutableProcedure SourceContext]
-> [ExecutableProcedure SourceContext]
forall a. [a] -> [a] -> [a]
++ ((ScopedFunction SourceContext, ExecutableProcedure SourceContext)
-> ExecutableProcedure SourceContext)
-> [(ScopedFunction SourceContext,
ExecutableProcedure SourceContext)]
-> [ExecutableProcedure SourceContext]
forall a b. (a -> b) -> [a] -> [b]
map (ScopedFunction SourceContext, ExecutableProcedure SourceContext)
-> ExecutableProcedure SourceContext
forall a b. (a, b) -> b
snd [(ScopedFunction SourceContext, ExecutableProcedure SourceContext)]
fs
let fs2 :: [ScopedFunction SourceContext]
fs2 = ((ScopedFunction SourceContext, ExecutableProcedure SourceContext)
-> ScopedFunction SourceContext)
-> [(ScopedFunction SourceContext,
ExecutableProcedure SourceContext)]
-> [ScopedFunction SourceContext]
forall a b. (a -> b) -> [a] -> [b]
map (ScopedFunction SourceContext, ExecutableProcedure SourceContext)
-> ScopedFunction SourceContext
forall a b. (a, b) -> a
fst [(ScopedFunction SourceContext, ExecutableProcedure SourceContext)]
fs
([DefinedMember SourceContext],
[ExecutableProcedure SourceContext],
[ScopedFunction SourceContext])
-> TextParser
([DefinedMember SourceContext],
[ExecutableProcedure SourceContext],
[ScopedFunction SourceContext])
forall (m :: * -> *) a. Monad m => a -> m a
return ([DefinedMember SourceContext]
ms,[ExecutableProcedure SourceContext]
ps2,[ScopedFunction SourceContext]
fs2) where
singleFunction :: TextParser
(ScopedFunction SourceContext, ExecutableProcedure SourceContext)
singleFunction = String
-> TextParser
(ScopedFunction SourceContext, ExecutableProcedure SourceContext)
-> TextParser
(ScopedFunction SourceContext, ExecutableProcedure SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled String
"function" (TextParser
(ScopedFunction SourceContext, ExecutableProcedure SourceContext)
-> TextParser
(ScopedFunction SourceContext, ExecutableProcedure SourceContext))
-> TextParser
(ScopedFunction SourceContext, ExecutableProcedure SourceContext)
-> TextParser
(ScopedFunction SourceContext, ExecutableProcedure SourceContext)
forall a b. (a -> b) -> a -> b
$ do
ScopedFunction SourceContext
f <- TextParser SymbolScope
-> TextParser CategoryName
-> TextParser (ScopedFunction SourceContext)
parseScopedFunction TextParser SymbolScope
parseScope (CategoryName -> TextParser CategoryName
forall (m :: * -> *) a. Monad m => a -> m a
return CategoryName
n)
TextParser () -> TextParser ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
lookAhead (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 ()) -> String -> TextParser ()
forall a b. (a -> b) -> a -> b
$ FunctionName -> String
forall a. Show a => a -> String
show (ScopedFunction SourceContext -> FunctionName
forall c. ScopedFunction c -> FunctionName
sfName ScopedFunction SourceContext
f)) TextParser () -> TextParser () -> TextParser ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(String -> TextParser ()
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> TextParser ()) -> String -> TextParser ()
forall a b. (a -> b) -> a -> b
$ String
"expected definition of function " String -> String -> String
forall a. [a] -> [a] -> [a]
++ FunctionName -> String
forall a. Show a => a -> String
show (ScopedFunction SourceContext -> FunctionName
forall c. ScopedFunction c -> FunctionName
sfName ScopedFunction SourceContext
f))
ExecutableProcedure SourceContext
p <- String
-> TextParser (ExecutableProcedure SourceContext)
-> TextParser (ExecutableProcedure SourceContext)
forall a. String -> TextParser a -> TextParser a
labeled (String
"definition of function " String -> String -> String
forall a. [a] -> [a] -> [a]
++ FunctionName -> String
forall a. Show a => a -> String
show (ScopedFunction SourceContext -> FunctionName
forall c. ScopedFunction c -> FunctionName
sfName ScopedFunction SourceContext
f)) (TextParser (ExecutableProcedure SourceContext)
-> TextParser (ExecutableProcedure SourceContext))
-> TextParser (ExecutableProcedure SourceContext)
-> TextParser (ExecutableProcedure SourceContext)
forall a b. (a -> b) -> a -> b
$ TextParser (ExecutableProcedure SourceContext)
forall a. ParseFromSource a => TextParser a
sourceParser
(ScopedFunction SourceContext, ExecutableProcedure SourceContext)
-> TextParser
(ScopedFunction SourceContext, ExecutableProcedure SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (ScopedFunction SourceContext
f,ExecutableProcedure SourceContext
p)
catchUnscopedType :: TextParser a
catchUnscopedType = String -> TextParser a -> TextParser a
forall a. String -> TextParser a -> TextParser a
labeled String
"" (TextParser a -> TextParser a) -> TextParser a -> TextParser a
forall a b. (a -> b) -> a -> b
$ do
ValueType
_ <- TextParser ValueType -> TextParser ValueType
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try TextParser ValueType
forall a. ParseFromSource a => TextParser a
sourceParser :: TextParser ValueType
String -> TextParser a
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM String
"members must have an explicit @value or @category scope"