]> git.wincent.com - docvim.git/blobdiff - lib/Text/Docvim/Printer/Vim.hs
Tweak function and command output in Vim help printer to stand out more
[docvim.git] / lib / Text / Docvim / Printer / Vim.hs
index 2fd82127a02467622ecd82f379559319f5814039..c9353c1db0eba95a2a99b32841814b922da6e498 100644 (file)
@@ -1,5 +1,11 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE MultiWayIf #-}
+
 module Text.Docvim.Printer.Vim (vimHelp) where
 
+#if !MIN_VERSION_base(4,8,0)
+import Control.Applicative ((<$>))
+#endif
 import Control.Arrow
 import Control.Monad
 import Control.Monad.Reader
@@ -12,7 +18,6 @@ import Data.Tuple
 import Text.Docvim.AST
 import Text.Docvim.Parse
 import Text.Docvim.Visitor.Plugin
-import Text.Docvim.Visitor.Symbol
 
 -- TODO: add indentation here (using local, or just stick it in Context)
 
@@ -33,7 +38,9 @@ textwidth :: Int
 textwidth = 78
 
 vimHelp :: Node -> String
-vimHelp n = suppressTrailingWhitespace output ++ "\n"
+vimHelp n = if null suppressTrailingWhitespace
+            then ""
+            else suppressTrailingWhitespace ++ "\n"
   where metadata = Metadata (getPluginName n)
         context = Context defaultLineBreak ""
         operations = evalState (runReaderT (node n) metadata) context
@@ -43,7 +50,7 @@ vimHelp n = suppressTrailingWhitespace output ++ "\n"
         reduce acc (Slurp atom) = if atom `isSuffixOf` acc
                                   then take (length acc - length atom) acc
                                   else acc
-        suppressTrailingWhitespace str = rstrip $ intercalate "\n" (map rstrip (splitOn "\n" str))
+        suppressTrailingWhitespace = rstrip $ intercalate "\n" (map rstrip (splitOn "\n" output))
 
 -- | Helper function that appends and updates `partialLine` context,
 -- hard-wrapping if necessary to remain under `textwidth`.
@@ -123,8 +130,9 @@ node n = case n of
   CommandsAnnotation         -> heading "commands"
   DocBlock d                 -> nodes d
   Fenced f                   -> fenced f
-  FunctionsAnnotation        -> heading "functions"
+  FunctionAnnotation {}      -> function n
   FunctionDeclaration {}     -> nodes $ functionBody n
+  FunctionsAnnotation        -> heading "functions"
   HeadingAnnotation h        -> heading h
   Link l                     -> append $ link l
   LinkTargets l              -> linkTargets l True
@@ -145,12 +153,18 @@ node n = case n of
   Whitespace                 -> whitespace
   _                          -> append ""
 
--- TODO: add {name}.txt to the symbol table?
 plugin :: String -> String -> Env
-plugin name desc = append $
-  "*" ++ name ++ ".txt*" ++
-  "    " ++ desc ++ "      " ++
-  "*" ++ name ++ "*" ++ "\n\n"
+plugin name desc = appendNoWrap $
+    center filename desc (target normalized) " " " " ++ "\n\n"
+  where
+    filename = "*" ++ normalized ++ ".txt*"
+    normalized = map toLower name
+    center a b c s1 s2 =
+        if | renderedWidth str >= textwidth -> str
+           | odd $ renderedWidth str        -> center a b c (s1 ++ " ") s2
+           | otherwise                      -> center a b c s1 (s2 ++ " ")
+      where
+        str = a ++ s1 ++ b ++ s2 ++ c
 
 -- | Append a newline.
 nl :: [Operation] -> Env
@@ -192,17 +206,25 @@ toc t = do
 
 command :: Node -> Env
 command (CommandAnnotation name params) = do
+  target' <- linkTargets [":" ++ name] False
   lhs <- append $ concat [":", name, " ", fromMaybe "" params]
-  ws <- append " "
-  target <- linkTargets [":" ++ name] False
-  trailing <- append "\n"
-  return $ concat [lhs, ws, target, trailing]
+  trailing <- append " ~\n\n"
+  return $ concat [target', lhs, trailing]
 -- TODO indent what follows until next annotation...
 -- will require us to hoist it up inside CommandAnnotation
 -- (and do similar for other sections)
 -- once that is done, drop the extra newline above
 command _ = invalidNode
 
+function :: Node -> Env
+function (FunctionAnnotation name) = do
+  target' <- linkTargets [name ++ "()"] False
+  lhs <- append $ name ++ "()"
+  trailing <- append " ~\n\n"
+  return $ concat [target', lhs, trailing]
+-- TODO indent what follows
+function _ = invalidNode
+
 mapping :: String -> Env
 mapping name = linkTargets [name] True
 
@@ -253,9 +275,9 @@ heading :: String -> Env
 heading h = do
   metadata <- ask
   heading' <- appendNoWrap $ map toUpper h ++ " "
-  target <- maybe (append "\n") (\x -> linkTargets [target' x] False) (pluginName metadata)
+  targ <- maybe (append "\n") (\x -> linkTargets [target' x] False) (pluginName metadata)
   trailing <- append "\n"
-  return $ concat [heading', target, trailing]
+  return $ concat [heading', targ, trailing]
   where
     target' x = normalize $ x ++ "-" ++ h
 
@@ -268,6 +290,9 @@ sanitize x = if isSpace x then '-' else x
 link :: String -> String
 link l = "|" ++ l ++ "|"
 
+target :: String -> String
+target t = "*" ++ t ++ "*"
+
 -- TODO: be prepared to wrap these if there are a lot of them
 -- TODO: fix code smell of passing in `wrap` bool here
 linkTargets :: [String] -> Bool -> Env