Styled the navigation bar.
authorsabadev <saba@sabadev.xyz>
Sun, 28 Mar 2021 00:02:46 +0000 (20:02 -0400)
committersabadev <dev@sabadev.xyz>
Tue, 13 Apr 2021 01:16:44 +0000 (21:16 -0400)
src/Html.hs
src/StyleSheet.hs

index 7d58c26..ee8444c 100644 (file)
@@ -21,11 +21,15 @@ htmlContainer theme contents = do
       meta_ [name_ "description", content_ "width=device-width"]
       link_ [rel_ "stylesheet", href_ $ safeStylingLink theme]
     body_ $ do
-      nav
       div_ [role_ "main"] contents
+      nav
 
 navigation :: (MonadIO m) => Maybe Theme -> m (Html ())
-navigation theme = blogList theme >>= pure . div_ [role_ "navigation"] . ul_ [class_ "blog-links"]
+navigation theme = do
+  blogListItems <- blogList theme >>= pure . ul_ [class_ "blog-links"]
+  pure $ div_ [role_ "navigation"] $ do
+    h2_ "Articles:"
+    blogListItems
 
 blogList :: (MonadIO m) => Maybe Theme -> m (Html ())
 blogList theme = liftIO $ getDirectoryContents staticPath >>= pure . foldMap (blogListItem theme) . filter (T.isSuffixOf markdownExtension) . fmap T.pack
index 2683ae6..377b68a 100644 (file)
@@ -2,7 +2,7 @@ module StyleSheet where
 
 import Clay
 import Data.Monoid
-import Prelude hiding (rem)
+import Prelude hiding (div, rem)
 
 type ColorAction = Float -> Color -> Color
 
@@ -20,6 +20,7 @@ makeStyle colorAction themeColor = do
   codeStyle
   headerStyle
   linkStyle colorAction themeColor
+  navigationStyle
 
 bodyStyle :: ColorAction -> Color -> Css
 bodyStyle action themeColor = body ? do
@@ -72,3 +73,12 @@ codeStyle = do
   pre ? do
     padding (rem 0.5) (rem 0.5) (rem 0.5) (rem 0.5)
     overflowX scroll
+
+navigationStyle :: Css
+navigationStyle = do
+  div # ("role" @= "navigation") |> h2 ? smallHeaderStyle
+  where
+    smallHeaderStyle = do
+      fontSize $ rem 1.414
+      paddingBottom $ rem 0
+      textAlign inherit