diff options
author | Gregor Kleen <gkleen@yggdrasil.li> | 2015-04-09 01:41:37 +0200 |
---|---|---|
committer | Gregor Kleen <gkleen@yggdrasil.li> | 2015-04-09 01:41:37 +0200 |
commit | 7170488c37105691f4a690cbcf1e43000d779b59 (patch) | |
tree | 107521b56e65a6b9228506c95a7bdf95db7900fa /build | |
parent | ea177ce261fbe2cc1d5529e974b15a2077897821 (diff) | |
download | dirty-haskell.org-7170488c37105691f4a690cbcf1e43000d779b59.tar dirty-haskell.org-7170488c37105691f4a690cbcf1e43000d779b59.tar.gz dirty-haskell.org-7170488c37105691f4a690cbcf1e43000d779b59.tar.bz2 dirty-haskell.org-7170488c37105691f4a690cbcf1e43000d779b59.tar.xz dirty-haskell.org-7170488c37105691f4a690cbcf1e43000d779b59.zip |
Minor code cleanup
Diffstat (limited to 'build')
-rwxr-xr-x | build/generate-rss.hs | 31 |
1 files changed, 19 insertions, 12 deletions
diff --git a/build/generate-rss.hs b/build/generate-rss.hs index f6ecfa6..2263ba8 100755 --- a/build/generate-rss.hs +++ b/build/generate-rss.hs | |||
@@ -25,8 +25,16 @@ type FeedState = (Feed, Maybe T.ClockTime) | |||
25 | 25 | ||
26 | feedKind = RSSKind $ Just "2.0" | 26 | feedKind = RSSKind $ Just "2.0" |
27 | 27 | ||
28 | baseurl = "http://dirty-haskell.org" | ||
29 | |||
30 | description = "dirty-haskell.org — a blog" | ||
31 | |||
32 | mkUrl' :: FilePath -> String | ||
33 | mkUrl' path = (++) (baseurl ++ "/posts/") $ (flip FP.replaceExtension) "html" $ FP.takeFileName path | ||
34 | |||
35 | |||
28 | extract_title :: Pandoc -> String | 36 | extract_title :: Pandoc -> String |
29 | extract_title d@(Pandoc m _) = do | 37 | extract_title (Pandoc m _) = do |
30 | title <- render Nothing $ cat $ map pretty (docTitle m) | 38 | title <- render Nothing $ cat $ map pretty (docTitle m) |
31 | return title | 39 | return title |
32 | where pretty :: Inline -> Doc | 40 | where pretty :: Inline -> Doc |
@@ -38,9 +46,13 @@ main :: IO () | |||
38 | main = do | 46 | main = do |
39 | (title:entries) <- getArgs | 47 | (title:entries) <- getArgs |
40 | currentTime <- T.getClockTime | 48 | currentTime <- T.getClockTime |
41 | let feed = withFeedHome "http://dirty-haskell.org" $ withFeedTitle title $ newFeed feedKind | 49 | let feed = foldl1 (.) |
50 | [ withFeedDescription description | ||
51 | , withFeedHome baseurl | ||
52 | , withFeedTitle title | ||
53 | ] $ newFeed feedKind | ||
42 | (populatedFeed, itemTime) <- S.execStateT (sequence $ map addItem' entries) (feed, Nothing) | 54 | (populatedFeed, itemTime) <- S.execStateT (sequence $ map addItem' entries) (feed, Nothing) |
43 | let populatedFeed' = withFeedDate (toFeedDateString feedKind $ fromMaybe currentTime itemTime) populatedFeed | 55 | let populatedFeed' = withFeedPubDate (toFeedDateString feedKind $ fromMaybe currentTime itemTime) $ withFeedLastUpdate (toFeedDateString feedKind currentTime) $ populatedFeed |
44 | putStrLn $ X.ppElement $ xmlFeed populatedFeed' | 56 | putStrLn $ X.ppElement $ xmlFeed populatedFeed' |
45 | 57 | ||
46 | addItem' :: FilePath -> S.StateT FeedState IO () | 58 | addItem' :: FilePath -> S.StateT FeedState IO () |
@@ -54,11 +66,13 @@ addItem' mdFile = do | |||
54 | (feed, time) <- S.get | 66 | (feed, time) <- S.get |
55 | let fileTime = maximum ([F.modificationTime, F.statusChangeTime] <-> fileStatus) :: System.Posix.Types.EpochTime | 67 | let fileTime = maximum ([F.modificationTime, F.statusChangeTime] <-> fileStatus) :: System.Posix.Types.EpochTime |
56 | fileTime' = T.TOD (toInteger $ fromEnum fileTime) 0 | 68 | fileTime' = T.TOD (toInteger $ fromEnum fileTime) 0 |
57 | let item = [ withItemTitle title | 69 | let item = foldl1 (.) |
70 | [ withItemTitle title | ||
58 | , withItemLink url | 71 | , withItemLink url |
72 | , withItemId True url | ||
59 | , withItemDate $ toFeedDateString feedKind fileTime' | 73 | , withItemDate $ toFeedDateString feedKind fileTime' |
60 | , withItemDescription contents | 74 | , withItemDescription contents |
61 | ] <--> (newItem feedKind) :: Item | 75 | ] $ newItem feedKind :: Item |
62 | S.put (addItem item feed, if (Just fileTime' > time) then Just fileTime' else time) | 76 | S.put (addItem item feed, if (Just fileTime' > time) then Just fileTime' else time) |
63 | 77 | ||
64 | mkUrl :: FilePath -> IO String | 78 | mkUrl :: FilePath -> IO String |
@@ -69,13 +83,6 @@ mkUrl link = do | |||
69 | mkUrl $ FP.combine (FP.takeDirectory link) target | 83 | mkUrl $ FP.combine (FP.takeDirectory link) target |
70 | else | 84 | else |
71 | return $ mkUrl' link | 85 | return $ mkUrl' link |
72 | mkUrl' :: FilePath -> String | ||
73 | mkUrl' path = (++) "http://dirty-haskell.org/posts/" $ (flip FP.replaceExtension) "html" $ FP.takeFileName path | ||
74 | |||
75 | (<->) :: [(a -> b)] -> a -> [b] | 86 | (<->) :: [(a -> b)] -> a -> [b] |
76 | [] <-> _ = [] | 87 | [] <-> _ = [] |
77 | (f:fs) <-> x = (f x:fs <-> x) | 88 | (f:fs) <-> x = (f x:fs <-> x) |
78 | |||
79 | (<-->) :: [(a -> a)] -> a -> a | ||
80 | [] <--> x = x | ||
81 | (f:fs) <--> x = fs <--> (f x) | ||