aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--MakeManPage.hs25
1 files changed, 3 insertions, 22 deletions
diff --git a/MakeManPage.hs b/MakeManPage.hs
index 31d643e49..c78fb7d77 100644
--- a/MakeManPage.hs
+++ b/MakeManPage.hs
@@ -7,11 +7,6 @@ import Control.Monad
import System.FilePath
import System.Environment (getArgs)
import Text.Pandoc.Shared (normalize)
-import System.Directory (getModificationTime)
-import System.IO.Error (isDoesNotExistError)
-import System.Time (ClockTime(..))
-import Data.Maybe (catMaybes)
-import qualified Control.Exception as E
main = do
rmContents <- liftM toString $ B.readFile "README"
@@ -29,12 +24,9 @@ main = do
makeManPage :: Bool -> FilePath -> Meta -> [Block] -> IO ()
makeManPage verbose page meta blocks = do
let templ = page <.> "template"
- modDeps <- modifiedDependencies page ["README", templ]
- unless (null modDeps) $ do
- manTemplate <- liftM toString $ B.readFile templ
- writeManPage page manTemplate (Pandoc meta blocks)
- when verbose $
- putStrLn $ "Created " ++ page
+ manTemplate <- liftM toString $ B.readFile templ
+ writeManPage page manTemplate (Pandoc meta blocks)
+ when verbose $ putStrLn $ "Created " ++ page
writeManPage :: FilePath -> String -> Pandoc -> IO ()
writeManPage page templ doc = do
@@ -45,17 +37,6 @@ writeManPage page templ doc = do
bottomUp capitalizeHeaders doc
B.writeFile page $ fromString manPage
--- | Returns a list of 'dependencies' that have been modified after 'file'.
-modifiedDependencies :: FilePath -> [FilePath] -> IO [FilePath]
-modifiedDependencies file dependencies = do
- fileModTime <- E.catch (getModificationTime file) $
- \e -> if isDoesNotExistError e
- then return (TOD 0 0) -- the minimum ClockTime
- else ioError e
- depModTimes <- mapM getModificationTime dependencies
- let modified = zipWith (\dep time -> if time > fileModTime then Just dep else Nothing) dependencies depModTimes
- return $ catMaybes modified
-
removeLinks :: Inline -> [Inline]
removeLinks (Link l _) = l
removeLinks x = [x]