Use Clay CSS domain specific language instead of including a raw CSS file

This commit is contained in:
2024-02-25 11:06:49 -06:00
parent fa54723934
commit 83ea5b77e9
6 changed files with 144 additions and 106 deletions

View File

@ -25,9 +25,7 @@ main postNames = do
-- These Middlewares are executed before any routes are reached.
preProcessors :: [Middleware]
preProcessors = [ logStdoutDev
, staticPolicy $ noDots >-> addBase "data/assets/public"
]
preProcessors = [ logStdoutDev ]
-- These Middlewares are executed after all other routes are exhausted
postProcessors :: [Middleware]
@ -38,12 +36,13 @@ postProcessors = []
automatically build an index of posts available to view. -}
routes :: [FilePath] -> [Middleware]
routes postNames =
[ get "/" Handle.index
, get "/posts" $ Handle.postsIndex postNames
] ++ handleDynamicPosts ++
[ get "/contact" Handle.contact
, get "/feed" $ Handle.feed postNames
, get "/atom.xml" $ Handle.feed postNames
[ get "/" Handle.index
, get "/posts" $ Handle.postsIndex postNames
, get "/style.css" $ Handle.theme
] ++ handleDynamicPosts ++
[ get "/contact" Handle.contact
, get "/feed" $ Handle.feed postNames
, get "/atom.xml" $ Handle.feed postNames
] where
handleDynamicPosts = (buildMdRoutes postNames)

View File

@ -1,8 +1,9 @@
module Core.Handlers where
import qualified Core.Configuration as Conf
import Core.Rendering
import Core.Feed (Post(..), autoFeed, renderFeed)
import Core.Rendering
import Core.Styles as S
import Fragments.Base
import Fragments.NotFound
@ -73,7 +74,7 @@ feed postNames = do
-- YYYY-MM-DD HH:MM | 2024-02-24 16:36
timeFormat :: UTCTime -> String
timeFormat x = formatTime defaultTimeLocale "%Y-%m-%d %H:%M" x
-- Refer to index comments
contact :: ResponderM a
contact = do
@ -82,6 +83,9 @@ contact = do
footerMd <- liftIO $ mdFileToLucid "./data/posts/footer.md"
sendLucidFragment $ basePage title (baseContact contactMd) footerMd
-- Respond with primary processed CSS
theme :: ResponderM a
theme = send $ css $ LTE.encodeUtf8 $ S.cssRender S.composedStyles
-- Helper function for responding in ResponderM from Html
sendLucidFragment :: Html () -> ResponderM a

127
src/Core/Styles.hs Normal file
View File

@ -0,0 +1,127 @@
module Core.Styles where
import Clay hiding (main_)
import qualified Clay.Media as M
import Data.Text.Lazy hiding (center)
import Prelude hiding (div)
cssRender :: Css -> Text
cssRender css = renderWith compact [] css
priColor, secColor, terColor :: Color
priColor = "#f1f6f0"
secColor = "#222323"
terColor = "#6D92AD"
composedStyles :: Css
composedStyles = do
core_
main_
notFound_
postList_
nav_
mobileFriendly_
core_ :: Css
core_ = do
a_
body_
footer_
html_
p_
a_ :: Css
a_ = do
a ? do
textDecoration none
color terColor
body_ :: Css
body_ = do
body ? do
fontFamily [] [monospace]
fontSize $ em 1.25
fontWeight $ weight 300
textAlign start
margin (em 0) auto (em 0) auto
strong ? do
fontWeight $ weight 600
li ? do
listStyleType $ other "~> "
footer_ :: Css
footer_ = do
footer ? do
position absolute
margin (em 0) (em 0) (em 0) (em 0)
bottom (em 0)
width $ pct 100
backgroundColor $ rgba 109 146 173 0.3
textAlign center
padding (em 1) (em 0) (em 1) (em 0)
boxSizing borderBox
p ? do
fontSize $ em 0.75
margin (em 0) (em 2) (em 0) (em 2)
color priColor
a ? do
color priColor
html_ :: Css
html_ = do
html ? do
backgroundColor priColor
color secColor
p_ :: Css
p_ = do
p ? do
margin (em 0.4) (em 0) (em 0.4) (em 0)
main_ :: Css
main_ = do
".main" ? do
margin (em 0) auto (em 0) auto
maxWidth $ pct 60
notFound_ :: Css
notFound_ = do
".notFound" ? do
margin (em 0) auto (em 0) auto
textAlign center
h1 ? do
fontSize $ pct 500
fontWeight $ weight 200
color terColor
postList_ :: Css
postList_ = do
".postList" ? do
fontSize (em 1.5)
nav_ :: Css
nav_ = do
".navContainer" ? do
margin (em 1.5) (em 0) (em 1.5) (em 0)
width $ pct 100
textAlign center
".mainNav" ? do
margin (em 0) auto (em 0) auto
padding (em 0) (em 0) (em 0) (em 0)
overflow hidden
boxShadow . pure $ bsColor "#ccc" $
shadowWithBlur (px 4) (px 4) (px 6)
display inlineFlex
li ? do
listStyleType none
a ? do
display block
textAlign center
padding (em 0.25) (em 0.3) (em 0.25) (em 0.3)
textTransform lowercase
mobileFriendly_ :: Css
mobileFriendly_ = query M.screen [M.maxWidth 768] $ do
".main" ? do
margin (em 1) auto (em 1) auto
maxWidth $ pct 95