]> git.netwichtig.de Git - user/henk/code/haskell/diddohs.git/blobdiff - diddohs.hs
On branch master
[user/henk/code/haskell/diddohs.git] / diddohs.hs
index b96b491ff8815e8fbd2517bd92bfb45d210a74e3..0444e22aaec24fdc98ea57636160933adf4e7329 100644 (file)
+import Control.Applicative( (<$>) )
+import Control.Monad( unless )
+import qualified Data.Map as Map
+import Data.Time.Clock( UTCTime(..) )
+import Diddo( DiddoEntry(..), LogEntry(..), parseDiddoLogline, formatDiddoEntry, timestamp, logToDiddoEntry )
+import System.Console.GetOpt
 import System.Environment( getArgs )
-import Data.Time.Git( approxidate )
-import Data.Time.LocalTime( utcToLocalTime, getTimeZone )
-import Data.Time.Clock.POSIX( posixSecondsToUTCTime )
-import Data.List.Split( splitOn )
-import Data.List( zip4, intersperse )
-import Data.Maybe( fromJust )
-import Control.Monad( forM_ )
-import Text.Printf
+import System.Exit( exitSuccess, exitFailure )
+import System.IO( stderr, hPutStr )
 
-main = do
-  logfile_name : _ <- getArgs
-  logfile_content <- readFile logfile_name
-  let loglines                = lines logfile_content
-      loglines_split          = map (splitOn ";") loglines
-
-      entries                 = map (head . tail) loglines_split
+data Opt = Opt
+    { optVerbose        :: Bool
+    , optVersion        :: Bool
+    , optHelp           :: Bool
+    , optInputFiles     :: [String]
+    , optOutputFile     :: String
+    , optInputFormat    :: String
+    , optOutputFormat   :: String
+    , optStartDate      :: String
+    , optEndDate        :: String
+    }
 
-      timestrings_finish      = map head loglines_split
-      timestrings_start       = "" : init timestrings_finish
+defaultOpts :: Opt
+defaultOpts = Opt
+    { optVerbose = False
+    , optVersion = False
+    , optHelp = False
+    , optInputFiles = []
+    , optOutputFile = ""
+    , optInputFormat = "%FT%T%z"
+    , optOutputFormat = "%FT%T%z"
+    , optStartDate = ""
+    , optEndDate = ""
+    }
 
-      timestamps_finish       = map timestringToEpoch timestrings_finish
-      timestamps_start        = 0 : init timestamps_finish
+availableOptions :: [OptDescr (Opt -> IO Opt)]
+availableOptions =
+    [ Option ['h']    ["help"]
+        (NoArg (\_ -> putStrLn (usageInfo "Usage: diddohs [OPTION...]" availableOptions) >> exitSuccess))
+        "Display program help"
+    , Option ['v']    ["verbose"]
+        (NoArg (\opts -> return opts { optVerbose = True }))
+        "More detailed output"
+    , Option ['V']    ["version"]
+        (NoArg (\opts -> return opts { optVersion = True }))
+        "Display program version"
+    , Option ['f']    ["file"]
+        (ReqArg (\arg opts -> return opts { optInputFiles = optInputFiles opts ++ [arg]}) "FILE" )
+        "Read from FILE"
+    , Option ['w']    ["output"]
+        (ReqArg (\arg opts -> return opts { optOutputFile = arg }) "FILE")
+        "Write to FILE"
+    , Option ['i']    ["informat"]
+        (ReqArg (\arg opts -> return opts { optInputFormat = arg }) "FORMAT")
+        "Timeformat used in input"
+    , Option ['o']    ["outformat"]
+        (ReqArg (\arg opts -> return opts { optOutputFormat = arg }) "FORMAT")
+        "Timeformat used in output"
+    , Option ['s']    ["start"]
+        (ReqArg (\arg opts -> return opts { optStartDate = arg }) "DATE")
+        "Start of reporting period"
+    , Option ['e']    ["end"]
+        (ReqArg (\arg opts -> return opts { optEndDate = arg }) "DATE")
+        "End of reporting period"
+    ]
 
-      timestamps_deltas       = zipWith (-) timestamps_finish timestamps_start
-      timestamps_deltas_HMMSS = map secondsToHMMSS timestamps_deltas
+-- SECTION: Map of logentries to Map of DiddoEntries
+mapToDiddoEntries :: Map.Map UTCTime Diddo.LogEntry -> Map.Map UTCTime Diddo.DiddoEntry
+mapToDiddoEntries logmap = Map.mapWithKey toDddEntry logmap
+    where
+        toDddEntry key value = Diddo.logToDiddoEntry (preceedingTimestamp key) value
+        preceedingTimestamp x = case Map.lookupLT x logmap of
+            Just y          -> fst y
+            Nothing         -> fst $ Map.findMin logmap
+-- SECTION: Map of logentries to Map of DiddoEntries
 
-      delta_entry_tuples      = zip timestamps_deltas_HMMSS entries
-      summaries               = zip4 (map show timestrings_start) (map show timestrings_finish) timestamps_deltas_HMMSS entries
+main :: IO ()
+main = do
+    -- SECTION: option processing
+    (givenOptions,args,errs) <- getArgs >>= return . getOpt Permute availableOptions
 
-  forM_ summaries $ \(start, finish, delta, entry) ->
-    putStrLn $ concat $ intersperse ";" [start, finish, delta, entry]
+    unless (null errs) $ do
+        mapM_ (hPutStr stderr) errs
+        exitFailure
 
-timestringToEpoch :: String -> Integer
-timestringToEpoch = fromJust . approxidate
+    effectiveOptions <- foldl (>>=) (return defaultOpts) givenOptions
+    -- SECTION: option processing
 
-secondsToHMMSS :: (Num seconds, Show seconds, Integral seconds, Text.Printf.PrintfArg seconds) => seconds -> String
-secondsToHMMSS seconds = printf "%d:%02d:%02d" h m s
-  where
-    (mLeft, s) = seconds `divMod` 60
-    (h, m) = mLeft `divMod` 60
+    dddLogEntries <-
+        map Diddo.parseDiddoLogline <$> case optInputFiles effectiveOptions of
+            files@(_:_)         -> lines . concat <$> mapM readFile files
+            []                  -> lines <$> getContents
 
-getStartOfDay :: Num t => t -> t
-getStartOfDay time = 0
+    let
+        dddLogEntryMap      = Map.fromList $ map (\diddo -> (Diddo.timestamp diddo, diddo)) dddLogEntries
+        diddoEntriesMap     = mapToDiddoEntries dddLogEntryMap
+        inDateFmt           = optInputFormat effectiveOptions
+        outDateFmt          = optOutputFormat effectiveOptions
 
---epochToTimestring :: Num t => t -> String
---epochToTimestring epochtime = let getTZ = getTimeZone utctime in utcToLocalTime getTZ utctime
---  where
---    tz = getTimeZone utctime
---    utctime = posixSecondsToUTCTime epochtime
+    -- DEBUG
+    mapM_ putStrLn args
+    -- DEBUG
 
---getTZ time = do
---  getTimeZone time
+    mapM_ (putStrLn . snd) $ Map.toAscList $ Map.map (Diddo.formatDiddoEntry outDateFmt) diddoEntriesMap