module Text.Docvim.Parse ( parse
, rstrip
, strip
, unit
) where
import Control.Applicative hiding ((<|>), many, optional)
import Data.Char
import Data.List (groupBy, intercalate)
import System.Exit
import System.IO
import Text.Docvim.AST
import Text.Parsec hiding (newline, parse)
import Text.Parsec.String
command :: String -> Parser ()
command description = try (string prefix >> remainder rest)
<?> prefix ++ rest
where prefix = takeWhile (/= '[') description
rest = init (snd (splitAt (1 + length prefix) description))
remainder [r] = optional (char r)
remainder (r:rs) = optional (char r >> remainder rs)
remainder [] = error "Unexpected empty remainder"
function :: Parser Node
function = FunctionDeclaration
<$> (fu *> bang <* wsc)
<*> (name <* optional wsc)
<*> arguments
<*> (attributes <* optional wsc)
<*> (skippable *> many node <* (optional ws >> endfunction))
where
fu = command "fu[nction]"
name = choice [script, normal, autoloaded] <* optional wsc
script = liftA2 (++) (try $ string "s:") (many $ oneOf identifier)
normal = liftA2 (++) (many1 upper) (many $ oneOf identifier)
autoloaded = do
a <- many1 $ oneOf identifier
b <- string "#"
c <- sepBy1 (many1 $ oneOf identifier) (string "#")
return $ a ++ b ++ intercalate "#" c
identifier = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ "_"
arguments = (char '(' >> optional wsc)
*> (ArgumentList <$> argument `sepBy` (char ',' >> optional wsc))
<* (optional wsc >> char ')' >> optional wsc)
argument = Argument <$> (string "..." <|> many1 alphaNum) <* optional wsc
attributes = choice [string "abort", string "range", string "dict"] `sepEndBy` wsc
endfunction :: Parser ()
endfunction = lookAhead (string "endf" >> notFollowedBy (string "o"))
>> command "endf[unction]"
<* eos
lStatement :: Parser Node
lStatement = lookAhead (char 'l')
>> choice [ try (lookAhead (string "lw")) >> lwindow
, try (lookAhead (string "let")) >> letStatement
, lexpr
]
lwindow :: Parser Node
lwindow = LwindowStatement <$> (lw *> height <* eos)
where
lw = command "l[window]"
height = optionMaybe (wsc *> number)
number = liftA read (many1 digit)
lexpr :: Parser Node
lexpr = LexprStatement
<$> (command "lex[pr]" *> bang <* wsc)
<*> restOfLine
letStatement :: Parser Node
letStatement = LetStatement
<$> (string "let" >> wsc >> lhs)
<*> (optional wsc >> char '=' >> optional wsc *> rhs <* eos)
where
lhs = many1 $ noneOf "\"\n="
rhs = many1 $ noneOf "\n"
unlet :: Parser Node
unlet = UnletStatement
<$> (unl *> bang <* wsc)
<*> word
<* eos
where
unl = command "unl[et]"
quote :: Parser String
quote = string "\"" <?> "quote"
commentStart :: Parser String
commentStart = quote <* (notFollowedBy quote >> optional ws)
docBlockStart :: Parser String
docBlockStart = (string "\"\"" <* optional ws) <?> "\"\""
separator :: Parser Node
separator = Separator <$ (try (string "---") >> optional ws) <?> "wat"
fenced :: Parser Node
fenced = fence >> newline >> Fenced <$> body
where
fence = try $ string "```" >> optional ws
body = do
lines' <- manyTill line (try $ (commentStart <|> docBlockStart) >> optional ws >> fence)
let indent = foldr countLeadingSpaces infinity lines'
return $ map (trimLeadingSpace indent) lines'
where
countLeadingSpaces line' = min (length (takeWhile (' ' ==) line'))
trimLeadingSpace count' = if count' > 0
then drop count'
else id
infinity = maxBound :: Int
line = (commentStart' <|> docBlockStart') >> restOfLine <* newline
commentStart' = quote <* notFollowedBy quote
docBlockStart' = string "\"\"" <?> "\"\""
blockquote :: Parser Node
blockquote = lookAhead (char '>')
>> Blockquote
<$> paragraph' `sepBy1` blankLine
where
paragraph' = Paragraph <$> body
body = paragraphBody firstLine otherLine
firstLine = char '>'
>> optional ws
>> many1 (choice [phrasing, whitespace])
otherLine = try $ newline
>> (commentStart <|> docBlockStart)
>> firstLine
blankLine = try $ newline
>> (commentStart <|> docBlockStart)
>> many1 (try $ char '>'
>> optional ws
>> newline
>> (commentStart <|> docBlockStart))
list :: Parser Node
list = lookAhead (char '-' >> notFollowedBy (char '-'))
>> List
<$> listItem `sepBy1` separator'
where
separator' = try $ newline
>> (commentStart <|> docBlockStart)
>> optional ws
>> lookAhead (char '-')
listItem :: Parser Node
listItem = lookAhead (char '-' >> notFollowedBy (char '-'))
>> ListItem
<$> body
where
body = paragraphBody firstLine otherLine
firstLine = char '-' >> optional ws >> many1 (choice [phrasing, whitespace])
otherLine = try $ newline
>> (commentStart <|> docBlockStart)
>> optional ws
>> lookAhead (noneOf "-")
>> many1 (choice [phrasing, whitespace])
newline :: Parser ()
newline = (char '\n' >> optional ws) <|> eof
newlines :: Parser [()]
newlines = many1 (char '\n' >> optional ws)
<|> (eof >> return [()])
ws :: Parser String
ws = many1 (oneOf " \t")
wsc :: Parser String
wsc = many1 $ choice [whitespace', continuation]
where
whitespace' = oneOf " \t"
continuation = try $ char '\n' >> ws >> char '\\'
comment :: Parser ()
comment = try
$ quote
>> notFollowedBy quote
>> restOfLine
>> skipMany (char '\n' >> optional ws)
bang :: Parser Bool
bang = option False (True <$ char '!')
eos :: Parser ()
eos = optional ws >> choice [bar, ws', skipMany1 comment]
where
bar = char '|' >> optional wsc
ws' = newlines >> notFollowedBy wsc
node :: Parser Node
node = choice [ docBlock
, vimL
]
<* optional skippable
docBlock :: Parser Node
docBlock = lookAhead docBlockStart
>> (DocBlock <$> many1 blockElement)
<* trailingBlankCommentLines
where
blockElement = try $ start
>> skipMany emptyLines
*> choice [ annotation
, try subheading
, heading
, linkTargets
, separator
, list
, blockquote
, fenced
, paragraph
]
<* next
start = try docBlockStart <|> commentStart
emptyLines = try $ newline >> start
next = optional ws >> newline
trailingBlankCommentLines = skipMany $ start >> newline
paragraph :: Parser Node
paragraph = Paragraph <$> body
where
body = paragraphBody firstLine otherLine
firstLine = many1 $ choice [phrasing, whitespace]
otherLine = try $ newline
>> (commentStart <|> docBlockStart)
>> optional ws
>> notFollowedBy special
>> firstLine
paragraphBody :: Parser [Node] -> Parser [Node] -> Parser [Node]
paragraphBody firstLine otherLine = do
first <- firstLine
rest <- many otherLine
let nodes = concatMap appendWhitespace (first:rest)
let compressed = compress nodes
return ( if last compressed == Whitespace
then init compressed
else compressed )
special :: Parser String
special = choice [ string "-" <* notFollowedBy (char '-')
, string ">"
, string "---"
, string "-" <* string "--"
, string "```"
, string "`" <* string "``"
, string "@"
, string "#"
]
phrasing :: Parser Node
phrasing = choice [ br
, link
, code
, plaintext
]
appendWhitespace :: [Node] -> [Node]
appendWhitespace xs = xs ++ [Whitespace]
compress :: [Node] -> [Node]
compress = map prioritizeBreakTag . group
where
group = groupBy fn
fn BreakTag Whitespace = True
fn Whitespace BreakTag = True
fn Whitespace Whitespace = True
fn _ _ = False
prioritizeBreakTag xs = if hasBreakTag xs
then BreakTag
else head xs
hasBreakTag = elem BreakTag
plaintext :: Parser Node
plaintext = Plaintext <$> wordChars
where
wordChars = many1 $ choice [ try $ char '<' <* notFollowedBy (string' "br")
, noneOf " \n\t<|`"
]
char' :: Char -> Parser Char
char' c = satisfy $ \x -> toUpper x == toUpper c
string' :: String -> Parser String
string' s = mapM_ char' s >> pure s <?> s
whitespace :: Parser Node
whitespace = Whitespace <$ ws
br :: Parser Node
br = BreakTag <$ (try htmlTag <|> try xhtmlTag) <?> "<br />"
where
htmlTag = string' "<br>"
xhtmlTag = string' "<br" >> optional ws >> string "/>"
link :: Parser Node
link = Link <$> (bar *> linkText <* bar)
where
bar = char '|'
linkText = many1 $ noneOf " \t\n|"
code :: Parser Node
code = Code <$> (backtick *> codeText <* backtick)
where
backtick = char '`'
codeText = many $ noneOf "\n`"
linkTargets :: Parser Node
linkTargets = LinkTargets <$> many1 (star *> target <* (star >> optional ws))
where
star = char '*'
target = many1 $ noneOf " \t\n*"
vimL :: Parser Node
vimL = choice [ block
, statement
]
block :: Parser Node
block = choice [ function ]
statement :: Parser Node
statement = choice [ lStatement
, unlet
, genericStatement
]
genericStatement :: Parser Node
genericStatement = do
notFollowedBy endfunction
atoms <- sepEndBy1 word (optional wsc)
eos
return $ GenericStatement $ unwords atoms
restOfLine :: Parser String
restOfLine = do
rest <- many (noneOf "\n")
return $ rstrip rest
strip :: String -> String
strip = lstrip . rstrip
lstrip :: String -> String
lstrip = dropWhile (`elem` " \n\t")
rstrip :: String -> String
rstrip = reverse . lstrip . reverse
heading :: Parser Node
heading = char '#'
>> notFollowedBy (char '#')
>> optional ws
>> HeadingAnnotation <$> restOfLine
subheading :: Parser Node
subheading = string "##"
>> optional ws
>> SubheadingAnnotation <$> restOfLine
word :: Parser String
word = many1 (noneOf " \n\t")
annotation :: Parser Node
annotation = char '@' *> annotationName
where
annotationName =
choice [ try $ string "commands" >> pure CommandsAnnotation
, command'
, string "dedent" >> pure DedentAnnotation
, try $ string "footer" >> pure FooterAnnotation
, try $ string "functions" >> pure FunctionsAnnotation
, function'
, string "indent" >> pure IndentAnnotation
, try $ string "mappings" >> pure MappingsAnnotation
, mapping
, try $ string "options" >> pure OptionsAnnotation
, option'
, plugin
]
command' = string "command" >> ws >> CommandAnnotation <$> commandName <*> commandParameters
commandName = char ':' *> many1 alphaNum <* optional ws
commandParameters = optionMaybe $ many1 (noneOf "\n")
function' = string "function" >> ws >> FunctionAnnotation <$> word <* optional ws
mapping = string "mapping" >> ws >> MappingAnnotation <$> mappingName
mappingName = word <* optional ws
option' = string "option" >> ws >> OptionAnnotation <$> optionName <*> optionType <*> optionDefault
optionName = many1 (alphaNum <|> char ':') <* ws <?> "option name"
optionType = many1 alphaNum <* optional ws <?> "option type"
optionDefault = optionMaybe word <?> "option default value"
plugin = string "plugin" >> ws >> PluginAnnotation <$> pluginName <*> plugInDescription
pluginName = many1 alphaNum <* ws
plugInDescription = restOfLine
unit :: Parser Node
unit = Unit
<$> (skippable >> many node)
<* eof
skippable :: Parser [()]
skippable = many $ choice [ comment
, skipMany1 ws
, skipMany1 (char '\n')
]
parse :: String -> IO Node
parse fileName = parseFromFile unit fileName >>= either report return
where
report err = do
hPutStrLn stderr $ "Error: " ++ show err
exitFailure