]> git.netwichtig.de Git - user/henk/code/haskell/diddohs.git/commitdiff
On branch master
authorHendrik Jaeger <henk@frustcomp>
Sat, 8 Mar 2014 18:55:18 +0000 (19:55 +0100)
committerHendrik Jaeger <henk@frustcomp>
Sat, 8 Mar 2014 18:55:18 +0000 (19:55 +0100)
      modified:   Diddo.hs
      modified:   diddohs.hs
        CHANGED: code cleanup

Diddo.hs
diddohs.hs

index cbbbce0384d17211bc8e0f8320a0d02e0006aee2..e90e6503456d6898bd2262513721f1872d0e1ade 100644 (file)
--- a/Diddo.hs
+++ b/Diddo.hs
@@ -1,84 +1,58 @@
 module Diddo
-( LogLine(LogLine)
-, LogEntry(LogEntry)
+( LogEntry(LogEntry)
 , DiddoEntry(DiddoEntry)
-, DiddoEntry2(DiddoEntry2)
 , parseDiddoLogline
 , formatDiddoEntry
 , timestamp
 , logToDiddoEntry
 ) where
 
-import HMSTime( HMSTime, secondsToHMS )
+import HMSTime( secondsToHMS )
 import Data.List( intercalate )
 import Data.DateTime( diffSeconds )
 import Data.Time.LocalTime( TimeZone() )
 import Data.Time.Clock( UTCTime() )
-import Data.Maybe( fromMaybe, fromJust )
+import Data.Maybe( fromMaybe )
 import Data.Time.Format( parseTime, formatTime )
-import Data.Time.LocalTime( LocalTime(..), ZonedTime(..), TimeZone(..), zonedTimeToUTC, utcToZonedTime, midnight, localDay )
+import Data.Time.LocalTime( ZonedTime(..), zonedTimeToUTC, utcToZonedTime )
 import Data.List.Split( splitOn )
 import System.Locale
 
-data LogLine
-  = LogLine String
-
-instance Show LogLine where
-    show (LogLine x) = x
-
-data LogEntry
-    = LogEntry
-        { timestamp     :: UTCTime
-        , timezone      :: TimeZone
-        , text          :: String
-        }
+data LogEntry = LogEntry
+    { timestamp     :: UTCTime
+    , timezone      :: TimeZone
+    , text          :: String
+    }
 
 instance Show LogEntry where
     show x = (show $ timestamp x) ++ (show $ timezone x) ++ text x
 
-data DiddoEntry = DiddoEntry String String HMSTime String
-
-data DiddoEntry2 = DiddoEntry2
-                    { startTime         :: ZonedTime
-                    , endTime           :: ZonedTime
-                    , comment           :: String
-                    }
+data DiddoEntry = DiddoEntry
+    { startTime         :: ZonedTime
+    , endTime           :: ZonedTime
+    , comment           :: String
+    }
 
 instance Show DiddoEntry where
-  show (DiddoEntry start finish delta entry) = intercalate ";" [start,finish,(show delta),entry]
-
-instance Show DiddoEntry2 where
-  show (DiddoEntry2 start finish entry) = intercalate ";" [show start,show finish,show $ diffSeconds (zonedTimeToUTC finish) (zonedTimeToUTC start),entry]
+  show (DiddoEntry start finish entry) = intercalate ";" [show start,show finish,show $ diffSeconds (zonedTimeToUTC finish) (zonedTimeToUTC start),entry]
 
-formatDiddoEntry :: String -> DiddoEntry2 -> String
-formatDiddoEntry format (DiddoEntry2 start end comment) = (formatTime defaultTimeLocale format start) ++ ";" ++ (formatTime defaultTimeLocale format end) ++ ";" ++ (show $ secondsToHMS $ diffSeconds (zonedTimeToUTC end) (zonedTimeToUTC start)) ++ ";" ++ comment
+formatDiddoEntry :: String -> DiddoEntry -> String
+formatDiddoEntry format entry = (formatTime defaultTimeLocale format (startTime entry)) ++ ";" ++ (formatTime defaultTimeLocale format (endTime entry)) ++ ";" ++ (show $ secondsToHMS $ diffSeconds (zonedTimeToUTC (endTime entry)) (zonedTimeToUTC (startTime entry))) ++ ";" ++ comment entry
 
-logToDiddoEntry :: UTCTime -> LogEntry -> DiddoEntry2
-logToDiddoEntry startutc logentry = DiddoEntry2 startZoned endZoned $ text logentry
+logToDiddoEntry :: UTCTime -> LogEntry -> DiddoEntry
+logToDiddoEntry startutc logentry = DiddoEntry startZoned endZoned $ text logentry
     where
         startZoned = utcToZonedTime (timezone logentry) startutc
         endZoned = utcToZonedTime (timezone logentry) $ timestamp logentry
 
-
-lineToEntry :: LogLine -> LogEntry
-lineToEntry (LogLine line) = LogEntry ts tz text
-    where
-        splitLine           = splitOn ";" line
-        text                = intercalate ";" $ tail splitLine
-        time                = parseISOsecondsTime $ head splitLine
-        (ts,tz)             = (zonedTimeToUTC time, zonedTimeZone time)
-
 parseDiddoLogline :: String -> LogEntry
-parseDiddoLogline line = LogEntry ts tz text
+parseDiddoLogline line = LogEntry ts tz string
     where
         splitLine           = splitOn ";" line
-        text                = intercalate ";" $ tail splitLine
+        string              = intercalate ";" $ tail splitLine
         time                = parseISOsecondsTime $ head splitLine
         (ts,tz)             = (zonedTimeToUTC time, zonedTimeZone time)
 
-
-
-
 parseToZonedTime :: String -> String -> ZonedTime
 parseToZonedTime format string = fromMaybe (error $ "Input data broken: " ++ string) $ parseTime defaultTimeLocale format string
 
index f6a8c8af0c7d5d7c224f0b0e30be2f24751fd820..0444e22aaec24fdc98ea57636160933adf4e7329 100644 (file)
@@ -1,20 +1,12 @@
-import Control.Applicative( (<$>), (<*>) )
-import Control.Monad( when, unless )
-import Data.DateTime( diffSeconds )
-import Data.List.Split( splitOn )
-import Data.List( zipWith4, intercalate )
+import Control.Applicative( (<$>) )
+import Control.Monad( unless )
 import qualified Data.Map as Map
-import Data.Maybe( fromMaybe, fromJust )
 import Data.Time.Clock( UTCTime(..) )
-import Data.Time.Format( parseTime, formatTime )
-import Data.Time.LocalTime( LocalTime(..), ZonedTime(..), TimeZone(..), zonedTimeToUTC, utcToZonedTime, midnight, localDay )
-import Diddo( DiddoEntry(..), DiddoEntry2(..), LogEntry(..), LogLine(..), parseDiddoLogline, formatDiddoEntry, timestamp, logToDiddoEntry )
-import HMSTime( secondsToHMS )
+import Diddo( DiddoEntry(..), LogEntry(..), parseDiddoLogline, formatDiddoEntry, timestamp, logToDiddoEntry )
 import System.Console.GetOpt
 import System.Environment( getArgs )
 import System.Exit( exitSuccess, exitFailure )
-import System.IO( stdin, stdout, stderr, hPutStr, hPutStrLn )
-import System.Locale
+import System.IO( stderr, hPutStr )
 
 data Opt = Opt
     { optVerbose        :: Bool
@@ -72,83 +64,15 @@ availableOptions =
         "End of reporting period"
     ]
 
--- SECTION: parsing to ZonedTime
-parseToZonedTime :: String -> String -> ZonedTime
-parseToZonedTime format string = fromMaybe (error $ "Input data broken: " ++ string) $ parseTime defaultTimeLocale format string
-
-parseISOsecondsTime :: String -> ZonedTime
-parseISOsecondsTime = parseToZonedTime $ iso8601DateFormat $ Just "%T%z"
-
-parseRFC822Time :: String -> ZonedTime
-parseRFC822Time = parseToZonedTime rfc822DateFormat
--- SECTION: parsing to ZonedTime
-
--- SECTION: handling ZonedTime
-formatZonedTime :: String -> ZonedTime -> String
-formatZonedTime = formatTime defaultTimeLocale
-
-startOfDay :: ZonedTime -> ZonedTime
-startOfDay time = ZonedTime (LocalTime day midnight) $ zonedTimeZone time
-    where
-        day = localDay $ zonedTimeToLocalTime time
-
-startOfMonth :: ZonedTime -> ZonedTime
-startOfMonth time = ZonedTime (LocalTime day midnight) $ zonedTimeZone time
-    where
-        day = localDay $ zonedTimeToLocalTime time
--- SECTION: handling ZonedTime
-
--- SECTION: handling UTCTime
-utcTimesDeltas :: [UTCTime] -> [Integer]
-utcTimesDeltas [] = error "Function utcTimesDeltas called with no argument"
-utcTimesDeltas [_] = error "Function utcTimesDeltas called with bougus argument"
-utcTimesDeltas (x:y:[]) = [diffSeconds y x]
-utcTimesDeltas (x:y:xs) = diffSeconds y x : utcTimesDeltas (y:xs)
-
---deltaAndEntry :: Map UTCTime Diddo.LogLine -> DiddoEntry2
---deltaAndEntry dddLoglineMap = Map.mapWithKey findDeltaEntry dddLoglineMap
---    where
---        precEntry = case Map.lookupLT (Diddo.timestamp logentry) dddLoglineMap of
---            Just x      -> x
---            Nothing     -> Diddo.timestamp logentry
---        end = utcToZonedTime (Diddo.timezone logentry) (Diddo.timestamp logentry)
---        start = utcToZonedTime (Diddo.timezone logentry) (fst precEntry)
---        delta = diffSeconds end start
---        comment = Diddo.text logentry
---
---findDeltaEntry timestamp logentry = Diddo.DiddoEntry2 start end delta comment
-
-mapToDiddoEntries :: Map.Map UTCTime Diddo.LogEntry -> Map.Map UTCTime Diddo.DiddoEntry2
+-- 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 timestamp logentry = Diddo.logToDiddoEntry (preceedingTimestamp timestamp) logentry
+        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: handling UTCTime
-
--- SECTION: handling rawinput
-splitToMapOn :: String -> [String] -> Map.Map String [String]
-splitToMapOn sep loglines = Map.fromList $ map (listToTuple . splitOn sep) loglines
-    where listToTuple (x:xs) = (x, xs)
-          listToTuple [] = ("",[""])
-
-logLinesToDiddohs :: String -> [String] -> [DiddoEntry]
-logLinesToDiddohs inDateFmt logLines =
-    let
-        loglineMap            = splitToMapOn ";" logLines
-        zonedtimeEntryMap     = Map.mapKeysMonotonic (parseToZonedTime inDateFmt) loglineMap
-        utctimeEntryMap       = Map.mapKeys zonedTimeToUTC zonedtimeEntryMap
-
-        timeStamps            = Map.keys loglineMap
-        entryTexts            = map (intercalate ";") $ Map.elems loglineMap
-        parsedTimes           = Map.keys zonedtimeEntryMap
-
-        deltasHMS             = map secondsToHMS $ utcTimesDeltas ((zonedTimeToUTC $ startOfDay $ head parsedTimes) : Map.keys utctimeEntryMap)
-    in
-        zipWith4 DiddoEntry (formatZonedTime inDateFmt (startOfDay $ head parsedTimes) : init timeStamps)
-                          timeStamps deltasHMS entryTexts
--- SECTION: handling rawinput
+-- SECTION: Map of logentries to Map of DiddoEntries
 
 main :: IO ()
 main = do
@@ -162,11 +86,6 @@ main = do
     effectiveOptions <- foldl (>>=) (return defaultOpts) givenOptions
     -- SECTION: option processing
 
-    dddLines <-
-        map Diddo.LogLine <$> case optInputFiles effectiveOptions of
-            files@(_:_)         -> lines . concat <$> mapM readFile files
-            []                  -> lines <$> getContents
-
     dddLogEntries <-
         map Diddo.parseDiddoLogline <$> case optInputFiles effectiveOptions of
             files@(_:_)         -> lines . concat <$> mapM readFile files
@@ -182,9 +101,5 @@ main = do
     mapM_ putStrLn args
     -- DEBUG
 
-    mapM_ print $ logLinesToDiddohs inDateFmt (map show dddLines)
---    putStrLn "new code output following"
---    mapM_ (print . snd) $ Map.toAscList diddoEntriesMap
-    putStrLn "new code output following"
     mapM_ (putStrLn . snd) $ Map.toAscList $ Map.map (Diddo.formatDiddoEntry outDateFmt) diddoEntriesMap