User:Duplode/Haskell/PrintVersion.hs

A simple script for generating the print version which builds upon Kowey's original, mvs-backed, program. To run it under Linux, save the code block contents as a Haskell source file (say, PrintVersion.hs) and follow the instructions in the comments. Other notes:

#!/usr/bin/env runhaskell

-- PrintVersion.hs - A simple script for generating the print version
-- of the Haskell Wikibook.
 
-- Originally written in 2007 by Eric Kow and in 2012 by Daniel Mlot.
-- For further information visit
-- <http://en.wikibooks.org/wiki/User:Duplode/Haskell/PrintVersion.hs>.

-- To the extent possible under law, the author(s) have dedicated all
-- copyright and related and neighboring rights to this software to the
-- public domain worldwide. This software is distributed without any
-- warranty. 

-- You should have received a copy of the CC0 Public Domain Dedication
-- along with this software. If not, see
-- <http://creativecommons.org/publicdomain/zero/1.0/>. 


-- Making the print version of the Haskell tutorial wikibook can be a
-- slight pain, so it's nice to automate it.

-- Note that to use this script you will need a copy of mw, which is
-- responsible for talking to the Wikibooks server. mw can be obtained
-- from https://github.com/ianweller/mw . It depends on bzrlib (from
-- bzr, the Bazaar VCS) and python-simplemediawiki 
-- (see https://github.com/ianweller/python-simplemediawiki).
-- Both deps can be found, e.g., on the Fedora repositories).

-- Setting it up
-- -------------
-- mkdir haskell-wikibook
-- cp PrintVersion.hs haskell-wikibook
-- cd haskell-wikibook
-- mw init http://en.wikibooks.org/w/api.php
-- mw pull 'Haskell!Print_version.wiki'

-- Running it
-- ----------
-- cd haskell-wikibook
-- ./PrintVersion.hs
-- mw login
-- mw commit -m "update print version" 

module Main where

import Data.List  (isInfixOf)
import Data.Maybe (mapMaybe)
import System.Process (runCommand, waitForProcess)

main :: IO ()
main = 
 do ps <- extractFrom navFile              -- parts
    cs <- mapM (extractFrom . partPath) ps -- chapters
    writeFile printVersionFile $ toPrintVersion ps cs
 where
  extractFrom f =
    withMw ("pull " ++ f) $ extract `fmap` readFile f
  withMw cmd' a =
    do let cmd = "mw " ++ cmd'
       x <- waitForProcess =<< runCommand cmd
       x `seq` a -- we're being sloppy, and don't care what mw does

navFile, printVersionFile :: FilePath
navFile          = "Template:Haskell!Navigation.wiki"
printVersionFile = "Haskell!Print_version.wiki"

partPath :: String -> FilePath
partPath  s = "Template:Haskell_chapter!" ++ map tweak s ++ ".wiki"
 where tweak ' ' = '_'
       tweak c   = c

-- ---------------------------------------------------------------------
-- Input
-- ---------------------------------------------------------------------

extract :: String -> [String]
extract = map degunk . filter isPC . lines

degunk :: String -> String
degunk = takeWhile notEnd . tail . dropWhile (/= '/')
 where notEnd x = x /= '|' && x /= ']'

isPC :: String -> Bool
isPC s = "Haskell/" `isInfixOf` s

-- ---------------------------------------------------------------------
-- Output
-- ---------------------------------------------------------------------

toPrintVersion :: [String] -> [[String]] -> String
toPrintVersion parts chapters =
  unlines $ [ "__NOTOC__ __NOEDITSECTION__"
            , "{{Print version notice|Haskell|Haskell/Print_version}}"
            , ""
            , "= Table Of Contents =" ]
            ++ concatMap toc parts
            ++ (concat $ zipWith body parts chapters)
  where
   toc c = [ "== " ++ c ++ " =="
           , ""
           , ":{{Haskell chapter/" ++ c ++ "|sep="
           , ":}}"
           , "" ]
   body p cs = [ "----"
               , "= " ++ p ++ " ="
               , "----"
               , "" ]
               ++ concatMap bodyC cs
   bodyC c = [ "= " ++ c ++ " ="
             , "{{:Haskell/" ++ c ++ "}}"
             , "" ]