aboutsummaryrefslogtreecommitdiffstats
path: root/scripts
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2009-10-12 06:49:18 +0200
committerAdam Vogt <vogt.adam@gmail.com>2009-10-12 06:49:18 +0200
commitef19913d068fda500962542191b1a53e3067a3b5 (patch)
tree9c832d4155df050712b89af8184710a8a2645df0 /scripts
parentbc47160271c0c3e8df73b918ca4b928aa6a54479 (diff)
downloadXMonadContrib-ef19913d068fda500962542191b1a53e3067a3b5.tar.gz
XMonadContrib-ef19913d068fda500962542191b1a53e3067a3b5.tar.xz
XMonadContrib-ef19913d068fda500962542191b1a53e3067a3b5.zip
Update D.Extending module lists with help of a script (also added)
Ignore-this: c280d3047355be962e8ef706d598aa43 darcs-hash:20091012044918-1499c-9761fe0833b9ad47cd65bfd70059b6bb64d2c59c.gz
Diffstat (limited to 'scripts')
-rwxr-xr-xscripts/grabDescriptions.hs37
1 files changed, 37 insertions, 0 deletions
diff --git a/scripts/grabDescriptions.hs b/scripts/grabDescriptions.hs
new file mode 100755
index 0000000..f6c0bbf
--- /dev/null
+++ b/scripts/grabDescriptions.hs
@@ -0,0 +1,37 @@
+#!/usr/bin/env runhaskell
+
+import Control.Applicative
+import Control.Arrow
+import Control.Monad
+import Data.Char
+import Data.List
+import Data.Maybe
+import System.Directory
+import System.Environment
+
+-- needs haskell-src-exts
+import qualified Language.Haskell.Exts.Annotated as H
+
+getComments = (fmap . fmap) (map (\(H.Comment _ _ x) -> x) . snd)
+ . H.parseFileWithComments H.defaultParseMode
+
+-- | Used to grab the description fields from all the modules in the current
+-- directory for updating XMonad.Docs.Extending
+main = putStrLn . intercalate "\n"
+ =<< mapM (fmap . handleFailure description <*> getComments) =<< filterM doesFileExist . sort
+ =<< getDirectoryContents . fromMaybe "." . listToMaybe
+ =<< getArgs -- somehow only the "." fallback works...
+
+handleFailure :: (String -> [String] -> String) -> String -> H.ParseResult [String] -> String
+handleFailure f n (H.ParseOk x) = f n x
+handleFailure f n (H.ParseFailed _ msg) = n ++ " Parse Failure: " ++ msg
+
+description :: String -> [String] -> String
+description path xs =
+ let (hs,desc)
+ = uncurry (\x (y,descr) -> (x++y,takeWhile (not . or . sequence [null,("* Usage" `isInfixOf`),all (=='-'),all isSpace]) . dropWhile (all isSpace) $ descr))
+ . second (splitAt 1)
+ . break (isPrefixOf "Portability")
+ . map (dropWhile isSpace) $ concatMap lines xs
+ modName = maybe path (takeWhile (not . isSpace) . dropWhile isSpace . drop 1 . dropWhile (/=':')) $ find ("Module" `isInfixOf`) hs
+ in "* \""++modName++"\":\n"++unlines (map (" "++) desc)