Code cleanup; name changes and hiding functions
parent
b9a1657171
commit
e6e53be35b
|
@ -1,9 +1,7 @@
|
||||||
#! /usr/bin/env nix-shell
|
#! /usr/bin/env nix-shell
|
||||||
#! nix-shell -p "haskellPackages.ghcWithPackages (ps: with ps; [dhall neat-interpolation random])"
|
#! nix-shell -p "haskellPackages.ghcWithPackages (ps: with ps; [dhall neat-interpolation random])"
|
||||||
#! nix-shell -i runghc
|
#! nix-shell -i runghc
|
||||||
{-
|
|
||||||
Must be run in folder containing the source code
|
|
||||||
-}
|
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE QuasiQuotes #-}
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
|
@ -53,7 +51,7 @@ main = do
|
||||||
putStrLn "Validated config successfully"
|
putStrLn "Validated config successfully"
|
||||||
|
|
||||||
createDirectoryIfMissing True postsOutputPath'
|
createDirectoryIfMissing True postsOutputPath'
|
||||||
unsafeGenerateAllBlogs config
|
generateAllBlogPosts config
|
||||||
putStrLn $ "Generated blog posts successfully to " <> postsOutputPath'
|
putStrLn $ "Generated blog posts successfully to " <> postsOutputPath'
|
||||||
|
|
||||||
|
|
||||||
|
@ -61,18 +59,20 @@ main = do
|
||||||
For all the blog posts
|
For all the blog posts
|
||||||
Write them to file
|
Write them to file
|
||||||
-}
|
-}
|
||||||
unsafeGenerateAllBlogs :: Config -> IO ()
|
generateAllBlogPosts :: Config -> IO ()
|
||||||
unsafeGenerateAllBlogs config =
|
generateAllBlogPosts config = forM_ allBlogPosts' writeToFile'
|
||||||
forM_ (allBlogPosts config) (writeToFile config)
|
where
|
||||||
|
allBlogPosts' = allBlogPosts config
|
||||||
|
writeToFile' = writeToFile config
|
||||||
|
|
||||||
allBlogPosts :: Config -> [(FilePath, Text)]
|
allBlogPosts :: Config -> [(FilePath, Text)]
|
||||||
allBlogPosts config = map f zippedDates
|
allBlogPosts config = map createSealText zippedDates
|
||||||
where
|
where
|
||||||
f = uncurry $ sealText config
|
createSealText = uncurry $ sealText config
|
||||||
zippedDates = zip [1..] (allDatesSince (startDate config))
|
zippedDates = zip [1..] (allDatesSince (startDate config))
|
||||||
|
|
||||||
allDatesSince :: Day -> [Day]
|
allDatesSince :: Day -> [Day]
|
||||||
allDatesSince startDate = map (`addDays` startDate) [0..daysSinceStart]
|
allDatesSince startDate = map (`addDays` startDate) [0..daysSinceStart]
|
||||||
where
|
where
|
||||||
daysSinceStart = diffDays today startDate
|
daysSinceStart = diffDays today startDate
|
||||||
{-# NOINLINE today #-}
|
{-# NOINLINE today #-}
|
||||||
|
@ -119,7 +119,7 @@ blogPost title see adj1 adj2 seal date imagesPath =
|
||||||
Returns a filePath, and a corresponding random blog post
|
Returns a filePath, and a corresponding random blog post
|
||||||
-}
|
-}
|
||||||
sealText :: Config -> Integer -> Day -> (FilePath, Text)
|
sealText :: Config -> Integer -> Day -> (FilePath, Text)
|
||||||
sealText config n date = ( fileName', bp)
|
sealText config n date = ( fileName', bp )
|
||||||
where
|
where
|
||||||
fileName' =
|
fileName' =
|
||||||
show date <> "-"
|
show date <> "-"
|
||||||
|
@ -129,6 +129,7 @@ sealText config n date = ( fileName', bp)
|
||||||
date' = T.pack . show $ date
|
date' = T.pack . show $ date
|
||||||
title = T.pack $ "Seal Post Number " <> show n
|
title = T.pack $ "Seal Post Number " <> show n
|
||||||
title' = T.replace " " "-" title
|
title' = T.replace " " "-" title
|
||||||
|
sealImagesPath' = sealImagesPath config
|
||||||
|
|
||||||
bp = blogPost' (toGregorian date)
|
bp = blogPost' (toGregorian date)
|
||||||
|
|
||||||
|
@ -141,7 +142,7 @@ sealText config n date = ( fileName', bp)
|
||||||
"older"
|
"older"
|
||||||
"birthdaySeal.jpg"
|
"birthdaySeal.jpg"
|
||||||
date
|
date
|
||||||
(sealImagesPath config)
|
sealImagesPath'
|
||||||
|
|
||||||
blogPost' (_, 04, 01) =
|
blogPost' (_, 04, 01) =
|
||||||
blogPost
|
blogPost
|
||||||
|
@ -151,7 +152,7 @@ sealText config n date = ( fileName', bp)
|
||||||
"supermodel, singing"
|
"supermodel, singing"
|
||||||
"singerSeal.jpg"
|
"singerSeal.jpg"
|
||||||
date
|
date
|
||||||
(sealImagesPath config)
|
sealImagesPath'
|
||||||
|
|
||||||
blogPost' (_, _, _) =
|
blogPost' (_, _, _) =
|
||||||
blogPost
|
blogPost
|
||||||
|
@ -159,30 +160,31 @@ sealText config n date = ( fileName', bp)
|
||||||
(randomPull $ looks config)
|
(randomPull $ looks config)
|
||||||
(randomPull $ adjectives1 config)
|
(randomPull $ adjectives1 config)
|
||||||
(randomPull $ adjectives2 config)
|
(randomPull $ adjectives2 config)
|
||||||
(randomPull $ unsafeListDirContents $ sealImagesPath config)
|
(randomPull $ unsafeListDirContents sealImagesPath')
|
||||||
date
|
date
|
||||||
(sealImagesPath config)
|
sealImagesPath'
|
||||||
|
|
||||||
|
|
||||||
{-
|
{-
|
||||||
Utils
|
Utils
|
||||||
-}
|
-}
|
||||||
{-
|
|
||||||
Gives a random number between from and to
|
|
||||||
Uses unsafeIO to get the number out of IO
|
|
||||||
It's safe because we're only shuffling
|
|
||||||
-}
|
|
||||||
randomNum :: Random a => a -> a -> a
|
|
||||||
randomNum from to = unsafePerformIO $ randomRIO (from, to)
|
|
||||||
|
|
||||||
{-
|
{-
|
||||||
Given a list, returns a random element
|
Given a list, returns a random element
|
||||||
-}
|
-}
|
||||||
randomPull :: [a] -> a
|
randomPull :: [a] -> a
|
||||||
randomPull lst = lst !! r'
|
randomPull lst = lst !! r'
|
||||||
where r' = randomNum 0 l
|
where
|
||||||
|
r' = randomNum 0 l
|
||||||
l = length lst - 1
|
l = length lst - 1
|
||||||
|
|
||||||
|
{-
|
||||||
|
Gives a random number between from and to
|
||||||
|
Uses unsafeIO to get the number out of IO
|
||||||
|
It's safe because we're only shuffling
|
||||||
|
-}
|
||||||
|
randomNum :: Random a => a -> a -> a
|
||||||
|
randomNum from to = unsafePerformIO $ randomRIO (from, to)
|
||||||
|
|
||||||
unsafeListDirContents :: FilePath -> [Text]
|
unsafeListDirContents :: FilePath -> [Text]
|
||||||
unsafeListDirContents = map T.pack . sort . unsafePerformIO . listDirectory
|
unsafeListDirContents = map T.pack . sort . unsafePerformIO . listDirectory
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue