aboutsummaryrefslogtreecommitdiff
path: root/src/F2Md/Config.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/F2Md/Config.hs')
-rw-r--r--src/F2Md/Config.hs54
1 files changed, 42 insertions, 12 deletions
diff --git a/src/F2Md/Config.hs b/src/F2Md/Config.hs
index ccb1871..ef209dc 100644
--- a/src/F2Md/Config.hs
+++ b/src/F2Md/Config.hs
@@ -1,15 +1,20 @@
{-# LANGUAGE DeriveGeneric #-}
-module F2Md.Config (getUserdata, FeedUserdata(..)) where
+module F2Md.Config
+ ( getUserdata
+ , FeedUserdata(..)
+ , updateLastUpdated
+ ) where
+import Data.List
import F2Md.Utils
+import F2Md.Types
import Data.Maybe
import Data.Text (Text)
import Data.Time
import GHC.Generics
import qualified Data.HashMap.Strict as HM
import Data.Aeson
-import qualified Data.ByteString.Lazy as BSL
data Config = Config
{ dbPath :: String
@@ -20,22 +25,47 @@ data Config = Config
instance FromJSON Config
data FeedUserdata = FeedUserdata
- { url :: Text
- , lastUpdated :: Maybe ZonedTime } deriving (Generic, Show)
+ { fuUrl :: Text
+ , fuLastUpdated :: Maybe ZonedTime } deriving (Show)
-getUserdata :: FilePath -> IO ([FeedUserdata], Maybe FilePath)
+getUserdata :: FilePath -> IO ([FeedUserdata], Maybe FilePath, Maybe FilePath)
getUserdata file = do
- config <- decode <$> BSL.readFile file
+ config <- decodeFileStrict file
case config of
- Nothing -> return ([], Nothing)
+ Nothing -> return ([], Nothing, Nothing)
Just config' -> do
feedData <- getUserdata' config'
maildir' <- expandPath $ maildir config'
- return (feedData, Just maildir')
+ dbPath' <- expandPath $ dbPath config'
+ return (feedData, Just maildir', Just dbPath')
getUserdata' :: Config -> IO [FeedUserdata]
getUserdata' (Config dbPath _ feeds) = do
- decoded <- decode <$> (BSL.readFile =<< expandPath dbPath)
- let decoded' = fromMaybe (HM.fromList []) decoded
- return $
- map (\url -> FeedUserdata url $ HM.lookup url decoded') feeds
+ decoded <- getLastUpdatedMap dbPath
+ return $ map (\url -> FeedUserdata url $ HM.lookup url decoded) feeds
+
+getLastUpdatedMap :: FilePath -> IO (HM.HashMap Text ZonedTime)
+getLastUpdatedMap dbPath =
+ fromMaybe (HM.fromList []) <$> (decodeFileStrict =<< expandPath dbPath)
+
+updateLastUpdated :: FilePath -> [FeedUserdata] -> [[Message]] -> IO ()
+updateLastUpdated path feeds feedMsgs = do
+ decoded <- getLastUpdatedMap path
+ encodeFile path $ foldl'
+ (\hm (feed, msgs) ->
+ case msgs of
+ [] -> hm
+ h : _ -> HM.insert (fuUrl feed)
+ (utcToZonedTime (zonedTimeZone $ mDate h) . maximum $
+ (zonedTimeToUTC . mDate) <$> msgs)
+ hm)
+ decoded (zip feeds feedMsgs)
+ -- HM.fromList $
+ -- mapMaybe
+ -- (\(feed, msgs) ->
+ -- case msgs of
+ -- [] -> fuLastUpdated feed >>= \date -> return (fuUrl feed, date)
+ -- h : _ ->
+ -- Just (fuUrl feed,
+ -- utcToZonedTime (zonedTimeZone $ mDate h) . maximum $
+ -- (zonedTimeToUTC . mDate) <$> msgs)) $ zip feeds feedMsgs