module Test.Pragma (tests) where
import Base.TrackedErrors
import Parser.Common
import Parser.Pragma
import Parser.TextParser
import Test.Common
tests :: [IO (TrackedErrors ())]
tests :: [IO (TrackedErrors ())]
tests = [
forall a.
Show a =>
String -> TextParser a -> (a -> Bool) -> IO (TrackedErrors ())
checkParseMatch String
"$Comment[ \"this is a pragma with args\" ]$" (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. a -> [a] -> [a]
:[]) TextParser (PragmaComment SourceContext)
pragmaComment)
(\[PragmaComment SourceContext]
e -> case [PragmaComment SourceContext]
e of
[PragmaComment [SourceContext]
_ String
"this is a pragma with args"] -> Bool
True
[PragmaComment SourceContext]
_ -> Bool
False),
forall a.
Show a =>
String -> String -> TextParser a -> IO (TrackedErrors ())
checkParseError String
"$Comment$" String
"requires arguments" TextParser (PragmaComment SourceContext)
pragmaComment
]
data c =
{
forall c. PragmaComment c -> [c]
pcContext :: [c],
:: String
}
deriving (Int -> PragmaComment c -> ShowS
forall c. Show c => Int -> PragmaComment c -> ShowS
forall c. Show c => [PragmaComment c] -> ShowS
forall c. Show c => PragmaComment c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PragmaComment c] -> ShowS
$cshowList :: forall c. Show c => [PragmaComment c] -> ShowS
show :: PragmaComment c -> String
$cshow :: forall c. Show c => PragmaComment c -> String
showsPrec :: Int -> PragmaComment c -> ShowS
$cshowsPrec :: forall c. Show c => Int -> PragmaComment c -> ShowS
Show)
pragmaComment :: TextParser (PragmaComment SourceContext)
= forall a.
String
-> Either (SourceContext -> a) (SourceContext -> TextParser a)
-> TextParser a
autoPragma String
"Comment" forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right forall {c}.
c -> ParsecT CompilerMessage String Identity (PragmaComment c)
parseAt where
parseAt :: c -> ParsecT CompilerMessage String Identity (PragmaComment c)
parseAt c
c = do
String -> TextParser ()
string_ String
"\""
String
ss <- forall (m :: * -> *) a end. MonadPlus m => m a -> m end -> m [a]
manyTill TextParser Char
stringChar (String -> TextParser ()
string_ String
"\"")
TextParser ()
optionalSpace
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall c. [c] -> String -> PragmaComment c
PragmaComment [c
c] String
ss