module Parser.Pragma (
autoPragma,
parsePragmas,
unknownPragma,
) where
import Control.Monad (when)
import Base.CompilerError
import Parser.Common
import Parser.TextParser
parsePragmas :: [TextParser a] -> TextParser [a]
parsePragmas :: forall a. [TextParser a] -> TextParser [a]
parsePragmas = ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity [a]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many (ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity [a])
-> ([ParsecT CompilerMessage String Identity a]
-> ParsecT CompilerMessage String Identity a)
-> [ParsecT CompilerMessage String Identity a]
-> ParsecT CompilerMessage String Identity [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity a)
-> ParsecT CompilerMessage String Identity a
-> [ParsecT CompilerMessage String Identity a]
-> ParsecT CompilerMessage String Identity a
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity a
forall a.
ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)) (ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity a
forall a.
ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT CompilerMessage String Identity a
forall a. TextParser a
unknownPragma)
unknownPragma :: TextParser a
unknownPragma :: forall a. TextParser a
unknownPragma = do
ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ()
forall a.
ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try ParsecT CompilerMessage String Identity ()
pragmaStart
String
p <- ParsecT CompilerMessage String Identity Char
-> ParsecT CompilerMessage String Identity String
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
some ParsecT CompilerMessage String Identity Char
ParsecT CompilerMessage String Identity (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
alphaNumChar
String -> TextParser a
forall a. String -> ParsecT CompilerMessage String Identity a
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> TextParser a) -> String -> TextParser a
forall a b. (a -> b) -> a -> b
$ String
"pragma " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
p String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not supported in this context"
autoPragma :: String -> Either (SourceContext -> a) (SourceContext -> TextParser a) -> TextParser a
autoPragma :: forall a.
String
-> Either (SourceContext -> a) (SourceContext -> TextParser a)
-> TextParser a
autoPragma String
p Either (SourceContext -> a) (SourceContext -> TextParser a)
f = do
SourceContext
c <- TextParser SourceContext
getSourceContext
ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ()
forall a.
ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try (ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ())
-> ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ()
forall a b. (a -> b) -> a -> b
$ ParsecT CompilerMessage String Identity ()
pragmaStart ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ()
forall a b.
ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity b
-> ParsecT CompilerMessage String Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> ParsecT CompilerMessage String Identity ()
string_ String
p ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ()
forall a b.
ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity b
-> ParsecT CompilerMessage String Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT CompilerMessage String Identity Char
-> ParsecT CompilerMessage String Identity ()
forall a.
ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity ()
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m ()
notFollowedBy ParsecT CompilerMessage String Identity Char
ParsecT CompilerMessage String Identity (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
alphaNumChar
Bool
hasArgs <- (ParsecT CompilerMessage String Identity ()
pragmaArgsStart ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ()
forall a b.
ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity b
-> ParsecT CompilerMessage String Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT CompilerMessage String Identity ()
optionalSpace ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity Bool
-> ParsecT CompilerMessage String Identity Bool
forall a b.
ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity b
-> ParsecT CompilerMessage String Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> ParsecT CompilerMessage String Identity Bool
forall a. a -> ParsecT CompilerMessage String Identity a
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 a.
ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> ParsecT CompilerMessage String Identity Bool
forall a. a -> ParsecT CompilerMessage String Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
a
x <- Bool
-> Either (SourceContext -> a) (SourceContext -> TextParser a)
-> SourceContext
-> TextParser a
forall {m :: * -> *} {t} {a}.
ErrorContextM m =>
Bool -> Either (t -> a) (t -> m a) -> t -> m a
delegate Bool
hasArgs Either (SourceContext -> a) (SourceContext -> TextParser a)
f SourceContext
c
if Bool
hasArgs
then do
String
extra <- ParsecT CompilerMessage String Identity Char
-> ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity String
forall (m :: * -> *) a end. MonadPlus m => m a -> m end -> m [a]
manyTill ParsecT CompilerMessage String Identity Char
ParsecT CompilerMessage String Identity (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
asciiChar (String -> ParsecT CompilerMessage String Identity ()
string_ String
"]$")
Bool
-> ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
extra) (ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ())
-> ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ()
forall a b. (a -> b) -> a -> b
$ String -> ParsecT CompilerMessage String Identity ()
forall a. String -> ParsecT CompilerMessage String Identity a
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> ParsecT CompilerMessage String Identity ())
-> String -> ParsecT CompilerMessage String Identity ()
forall a b. (a -> b) -> a -> b
$ String
"content unused by pragma " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
p String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
extra
ParsecT CompilerMessage String Identity ()
optionalSpace
else ParsecT CompilerMessage String Identity ()
-> ParsecT CompilerMessage String Identity ()
forall a.
ParsecT CompilerMessage String Identity a
-> ParsecT CompilerMessage String Identity a
sepAfter ParsecT CompilerMessage String Identity ()
pragmaEnd
a -> TextParser a
forall a. a -> ParsecT CompilerMessage String Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x where
delegate :: Bool -> Either (t -> a) (t -> m a) -> t -> m a
delegate Bool
False (Left t -> a
f2) t
c = a -> m a
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> m a) -> a -> m a
forall a b. (a -> b) -> a -> b
$ t -> a
f2 t
c
delegate Bool
True (Right t -> m a
f2) t
c = t -> m a
f2 t
c
delegate Bool
_ (Left t -> a
_) t
_ = String -> m a
forall a. String -> m a
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ String
"pragma " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
p String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" does not allow arguments using []"
delegate Bool
_ (Right t -> m a
_) t
_ = String -> m a
forall a. String -> m a
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ String
"pragma " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
p String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" requires arguments using []"