{- Copyright 2007 Dino Morelli This file is part of storylen storylen is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. storylen is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with storylen; if not, write to the Free Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA -} module Main where import Control.Monad import qualified Data.ByteString.Char8 as B import StoryLen.Describe ( describeStory ) import qualified StoryLen.Opts as Opts import qualified System.Environment as Env import System.Posix.Files ( getFileStatus, isRegularFile ) import Text.Printf -- Count the words in the supplied file. countWords :: FilePath -> IO Int countWords path = do contents <- case path of [] -> B.getContents _ -> B.readFile path let lengthInWords = length . B.words $ contents return lengthInWords -- Calculate the maximum column widths needed to display the word count -- and desc columns of the result data. columnWidths :: [(Int, String)] -> (Int, Int) columnWidths r = foldl f (0, 0) r where f (oldCountLength, oldDescLength) (newCount, newDesc) = ((max oldCountLength newCountLength), (max oldDescLength newDescLength)) where newCountLength = length $ show newCount newDescLength = length newDesc -- Displays the formatted results for a specific path. display :: Int -> Int -> (Int, String, FilePath) -> IO () display countWidth descWidth (wordCount, desc, path) = printf "%*d %-*s %s\n" countWidth wordCount descWidth desc path -- Figure out and execute what the user wants based on the supplied args. executeCommands :: ([Opts.Flag], [String]) -> IO () -- User requested help. Display it and that's it executeCommands ((Opts.Help:_), _) = putStrLn Opts.usageText -- User gave us a specific word count to classify executeCommands ((Opts.Number n:_), _) = do let desc = describeStory n display (length . show $ n) (length desc) (n, desc, "") -- Otherwise, calculate results for all paths given executeCommands (_, paths) = do -- Get rid of anything not a regular file from the list of paths rawFilePaths <- filterM (\p -> getFileStatus p >>= return . isRegularFile) paths -- Kind of a hack, to represent STDIN in the list of files let filePaths = case rawFilePaths of [] -> [""] -- This means STDIN _ -> rawFilePaths -- Calculate word counts for these files counts <- mapM countWords filePaths -- Calculate descriptions for these word counts let descs = map describeStory counts -- Calculate display column widths using the above data let (countWidth, descWidth) = columnWidths (zip counts descs) -- Display all results mapM_ (display countWidth descWidth) (zip3 counts descs filePaths) -- It all starts here. -- Parse the args and send them onward. main :: IO () main = do args <- Env.getArgs Opts.parseOpts args >>= executeCommands