-- An utility to split a source Haskell file -- generated by hsffig into smaller parts as guided -- by the special comments found in the file. module Main where import Prelude hiding (putStrLn, readFile) import Data.List import System.Directory import System.FilePath import System.Environment.UTF8 import System.IO (openFile, IOMode(..), hClose) import System.IO.UTF8 import Control.Monad import Maybe import Data.SplitBounds main = do args <- getArgs case args of [] -> usage other -> splitModule $ head args -- Print the usage information. usage = putStrLn "Usage: splitter filename" -- Do the actual module split. The file name is expected -- to be in the form [path/]MODULENAME[.suffix]. Path will be preserved. -- Suffix will be replaced with .hs. Names of modules will be derived from -- MODULENAME and be treated relativeky to the current directory. splitModule fn = do -- Open the file src <- (readFile fn) let srcln = lines src procLines Nothing "" srcln return () -- Line-by-line processor. procLines _ _ [] = return () procLines handle fnpath (l:ls) = do let derivefn app = fnpath app' <.> "hs" where app' = concat $ intersperse "/" $ parts (== '.') app skipline = do procLines handle fnpath ls return () startfile app = do let path = derivefn app dir = fst $ splitFileName path createDirectoryIfMissing True dir handle' <- openFile path WriteMode procLines (Just handle') fnpath ls return () endfile = do when (handle /= Nothing) $ hClose (fromJust handle) procLines Nothing fnpath ls return () nextline = do when (handle /= Nothing) $ hPutStrLn (fromJust handle) l procLines handle fnpath ls return () case l of _ | l == splitOpen -> skipline -- these comments _ | l == splitClose -> skipline -- are removed _ | (takeWhile (/= '/') l) == splitBegin -> startfile $ drop 1 $ dropWhile (/= '/') l _ | l == splitEnd -> endfile other -> nextline return ()