mirror of
https://github.com/srid/rib.git
synced 2024-11-26 13:50:31 +03:00
Obelisk -> static site generator (#3)
* Drop obelisk files * Add example of Slick * Add articles to Slick's layout * remove chris * develop instructions
This commit is contained in:
parent
78a72b51a1
commit
65f1dfa5c4
3
.gitignore
vendored
3
.gitignore
vendored
@ -5,3 +5,6 @@ result-ios
|
|||||||
result-exe
|
result-exe
|
||||||
.attr-cache
|
.attr-cache
|
||||||
ghcid-output.txt
|
ghcid-output.txt
|
||||||
|
|
||||||
|
.shake
|
||||||
|
dist
|
||||||
|
@ -1,7 +0,0 @@
|
|||||||
# DO NOT HAND-EDIT THIS FILE
|
|
||||||
import ((import <nixpkgs> {}).fetchFromGitHub (
|
|
||||||
let json = builtins.fromJSON (builtins.readFile ./github.json);
|
|
||||||
in { inherit (json) owner repo rev sha256;
|
|
||||||
private = json.private or false;
|
|
||||||
}
|
|
||||||
))
|
|
@ -1,7 +0,0 @@
|
|||||||
{
|
|
||||||
"owner": "obsidiansystems",
|
|
||||||
"repo": "obelisk",
|
|
||||||
"branch": "develop",
|
|
||||||
"rev": "86a9584c6d7648bd5324ef57d62421fed1bf1978",
|
|
||||||
"sha256": "1lbii87j5530ncm6brfbzkd3wg16mgxazsf3l56zzv4c8cydilmh"
|
|
||||||
}
|
|
14
README.md
14
README.md
@ -8,15 +8,21 @@ would explain the various Haskell concepts that I have come to understand since
|
|||||||
|
|
||||||
- [x] Think of first article to write
|
- [x] Think of first article to write
|
||||||
- [ ] DOING: Write it
|
- [ ] DOING: Write it
|
||||||
- [ ] DOING: Develop backend & frontend to serve an article
|
- [ ] DOING: Static site generation (Slick)
|
||||||
- [ ] Deploy to production
|
- [ ] Deploy to production
|
||||||
- [ ] Share and get feedback on first article
|
- [ ] Share and get feedback on first article
|
||||||
|
|
||||||
- [ ] Upgrade mmark (thus megaparsec, etc.)
|
|
||||||
|
|
||||||
## Article Ideas
|
## Article Ideas
|
||||||
|
|
||||||
See articles/ for existing stubs. In addition, consider these ideas:
|
See site/drafts/ for existing stubs. In addition, consider these ideas:
|
||||||
|
|
||||||
- Github CI for OSS haskell projects
|
- Github CI for OSS haskell projects
|
||||||
-
|
-
|
||||||
|
|
||||||
|
## Running
|
||||||
|
|
||||||
|
```
|
||||||
|
nix-build
|
||||||
|
./result/bin/ExplainingHaskell-exe site
|
||||||
|
nix-shell -p nodePackages.serve --run 'serve dist'
|
||||||
|
```
|
||||||
|
131
app/Main.hs
Normal file
131
app/Main.hs
Normal file
@ -0,0 +1,131 @@
|
|||||||
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
{-# LANGUAGE DuplicateRecordFields #-}
|
||||||
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
|
|
||||||
|
module Main where
|
||||||
|
|
||||||
|
import Control.Lens
|
||||||
|
import Data.Aeson as A
|
||||||
|
import Data.Aeson.Lens
|
||||||
|
import Data.Function (on)
|
||||||
|
import Data.List (sortBy)
|
||||||
|
import Data.Map as M
|
||||||
|
import Data.Monoid
|
||||||
|
import Data.Set as S
|
||||||
|
import qualified Data.Text as T
|
||||||
|
import Data.Text.Lens
|
||||||
|
import Data.Time
|
||||||
|
import GHC.Generics (Generic)
|
||||||
|
|
||||||
|
import Development.Shake
|
||||||
|
import Development.Shake.Classes
|
||||||
|
import Development.Shake.FilePath
|
||||||
|
import Slick
|
||||||
|
|
||||||
|
main :: IO ()
|
||||||
|
main =
|
||||||
|
shakeArgs shakeOptions {shakeVerbosity = Chatty} $
|
||||||
|
-- Set up caches
|
||||||
|
do
|
||||||
|
postCache <- jsonCache' loadPost
|
||||||
|
-- Require all the things we need to build the whole site
|
||||||
|
"site" ~> need ["static", "posts", "dist/index.html"]
|
||||||
|
-- Require all static assets
|
||||||
|
"static" ~> do
|
||||||
|
staticFiles <-
|
||||||
|
getDirectoryFiles "." ["site/css//*", "site/js//*", "site/images//*"]
|
||||||
|
need (("dist" </>) . dropDirectory1 <$> staticFiles)
|
||||||
|
-- Rule for handling static assets, just copy them from source to dest
|
||||||
|
["dist/css//*", "dist/js//*", "dist/images//*"] |%> \out -> do
|
||||||
|
copyFileChanged ("site" </> dropDirectory1 out) out
|
||||||
|
-- Find and require every post to be built
|
||||||
|
"posts" ~> requirePosts
|
||||||
|
-- build the main table of contents
|
||||||
|
"dist/index.html" %> buildIndex postCache
|
||||||
|
-- rule for actually building posts
|
||||||
|
"dist/posts//*.html" %> buildPost postCache
|
||||||
|
|
||||||
|
-- | Represents the template dependencies of the index page
|
||||||
|
data IndexInfo = IndexInfo
|
||||||
|
{ posts :: [Post]
|
||||||
|
} deriving (Generic, Show)
|
||||||
|
|
||||||
|
instance FromJSON IndexInfo
|
||||||
|
|
||||||
|
instance ToJSON IndexInfo
|
||||||
|
|
||||||
|
-- | A JSON serializable representation of a post's metadata
|
||||||
|
data Post = Post
|
||||||
|
{ title :: String
|
||||||
|
, author :: String
|
||||||
|
, content :: String
|
||||||
|
, url :: String
|
||||||
|
, date :: String
|
||||||
|
, image :: Maybe String
|
||||||
|
} deriving (Generic, Eq, Ord, Show)
|
||||||
|
|
||||||
|
instance FromJSON Post
|
||||||
|
|
||||||
|
instance ToJSON Post
|
||||||
|
|
||||||
|
|
||||||
|
-- A simple wrapper data-type which implements 'ShakeValue';
|
||||||
|
-- Used as a Shake Cache key to build a cache of post objects.
|
||||||
|
newtype PostFilePath =
|
||||||
|
PostFilePath String
|
||||||
|
deriving (Show, Eq, Hashable, Binary, NFData)
|
||||||
|
|
||||||
|
-- | Discover all available post source files
|
||||||
|
postNames :: Action [FilePath]
|
||||||
|
postNames = getDirectoryFiles "." ["site/posts//*.md"]
|
||||||
|
|
||||||
|
-- | convert 'build' filepaths into source file filepaths
|
||||||
|
destToSrc :: FilePath -> FilePath
|
||||||
|
destToSrc p = "site" </> dropDirectory1 p
|
||||||
|
|
||||||
|
-- | convert source filepaths into build filepaths
|
||||||
|
srcToDest :: FilePath -> FilePath
|
||||||
|
srcToDest p = "dist" </> dropDirectory1 p
|
||||||
|
|
||||||
|
-- | convert a source file path into a URL
|
||||||
|
srcToURL :: FilePath -> String
|
||||||
|
srcToURL = ("/" ++) . dropDirectory1 . (-<.> ".html")
|
||||||
|
|
||||||
|
-- | Given a post source-file's file path as a cache key, load the Post object
|
||||||
|
-- for it. This is used with 'jsonCache' to provide post caching.
|
||||||
|
loadPost :: PostFilePath -> Action Post
|
||||||
|
loadPost (PostFilePath postPath) = do
|
||||||
|
let srcPath = destToSrc postPath -<.> "md"
|
||||||
|
postData <- readFile' srcPath >>= markdownToHTML . T.pack
|
||||||
|
let postURL = T.pack . srcToURL $ postPath
|
||||||
|
withURL = _Object . at "url" ?~ String postURL
|
||||||
|
withSrc = _Object . at "srcPath" ?~ String (T.pack srcPath)
|
||||||
|
convert . withSrc . withURL $ postData
|
||||||
|
|
||||||
|
-- | given a cache of posts this will build a table of contents
|
||||||
|
buildIndex :: (PostFilePath -> Action Post) -> FilePath -> Action ()
|
||||||
|
buildIndex postCache out = do
|
||||||
|
posts <- postNames >>= traverse (postCache . PostFilePath)
|
||||||
|
indexT <- compileTemplate' "site/templates/index.html"
|
||||||
|
let indexInfo = IndexInfo {posts}
|
||||||
|
indexHTML = T.unpack $ substitute indexT (toJSON indexInfo)
|
||||||
|
writeFile' out indexHTML
|
||||||
|
|
||||||
|
-- | Find all post source files and tell shake to build the corresponding html
|
||||||
|
-- pages.
|
||||||
|
requirePosts :: Action ()
|
||||||
|
requirePosts = do
|
||||||
|
pNames <- postNames
|
||||||
|
need ((\p -> srcToDest p -<.> "html") <$> pNames)
|
||||||
|
|
||||||
|
-- Build an html file for a given post given a cache of posts.
|
||||||
|
buildPost :: (PostFilePath -> Action Post) -> FilePath -> Action ()
|
||||||
|
buildPost postCache out = do
|
||||||
|
let srcPath = destToSrc out -<.> "md"
|
||||||
|
postURL = srcToURL srcPath
|
||||||
|
post <- postCache (PostFilePath srcPath)
|
||||||
|
template <- compileTemplate' "site/templates/post.html"
|
||||||
|
writeFile' out . T.unpack $ substitute template (toJSON post)
|
@ -1,49 +0,0 @@
|
|||||||
name: backend
|
|
||||||
version: 0.1
|
|
||||||
cabal-version: >= 1.8
|
|
||||||
build-type: Simple
|
|
||||||
|
|
||||||
library
|
|
||||||
hs-source-dirs: src
|
|
||||||
if impl(ghcjs)
|
|
||||||
buildable: False
|
|
||||||
build-depends: base
|
|
||||||
, common
|
|
||||||
, frontend
|
|
||||||
, obelisk-backend
|
|
||||||
, obelisk-route
|
|
||||||
, text
|
|
||||||
, mmark
|
|
||||||
, modern-uri
|
|
||||||
, yaml
|
|
||||||
, reflex-dom-core
|
|
||||||
, aeson
|
|
||||||
, foldl
|
|
||||||
, profunctors
|
|
||||||
, snap
|
|
||||||
, megaparsec
|
|
||||||
exposed-modules:
|
|
||||||
Backend
|
|
||||||
Backend.Markdown
|
|
||||||
ghc-options: -Wall
|
|
||||||
|
|
||||||
executable backend
|
|
||||||
main-is: main.hs
|
|
||||||
hs-source-dirs: src-bin
|
|
||||||
if impl(ghcjs)
|
|
||||||
buildable: False
|
|
||||||
build-depends: base
|
|
||||||
, backend
|
|
||||||
, common
|
|
||||||
, frontend
|
|
||||||
, obelisk-backend
|
|
||||||
, text
|
|
||||||
, mmark
|
|
||||||
, modern-uri
|
|
||||||
, yaml
|
|
||||||
, reflex-dom-core
|
|
||||||
, aeson
|
|
||||||
, foldl
|
|
||||||
, profunctors
|
|
||||||
, snap
|
|
||||||
, megaparsec
|
|
@ -1 +0,0 @@
|
|||||||
../frontend-js/bin/frontend.jsexe
|
|
@ -1 +0,0 @@
|
|||||||
../../frontend-js/bin/frontend.jsexe
|
|
@ -1,6 +0,0 @@
|
|||||||
import Backend
|
|
||||||
import Frontend
|
|
||||||
import Obelisk.Backend
|
|
||||||
|
|
||||||
main :: IO ()
|
|
||||||
main = runBackend backend frontend
|
|
@ -1,34 +0,0 @@
|
|||||||
{-# LANGUAGE EmptyCase #-}
|
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
|
||||||
{-# LANGUAGE LambdaCase #-}
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# LANGUAGE RankNTypes #-}
|
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
|
||||||
module Backend where
|
|
||||||
|
|
||||||
import qualified Data.Aeson as Aeson
|
|
||||||
import Control.Monad.IO.Class (liftIO)
|
|
||||||
import qualified Data.Text as T
|
|
||||||
import qualified Data.Text.IO as T
|
|
||||||
import qualified Data.Text.Encoding as T
|
|
||||||
|
|
||||||
import Obelisk.Backend
|
|
||||||
import Obelisk.Route
|
|
||||||
import Snap
|
|
||||||
import Reflex.Dom.Core
|
|
||||||
|
|
||||||
import Common.Route
|
|
||||||
import Backend.Markdown
|
|
||||||
|
|
||||||
backend :: Backend BackendRoute FrontendRoute
|
|
||||||
backend = Backend
|
|
||||||
{ _backend_run = \serve -> serve $ \case
|
|
||||||
BackendRoute_Missing :/ () ->
|
|
||||||
pure ()
|
|
||||||
BackendRoute_GetArticle :/ articleName -> do
|
|
||||||
let articlePath = "articles/" <> articleName <> ".md"
|
|
||||||
c <- liftIO (T.readFile $ T.unpack articlePath)
|
|
||||||
(_, bs) <- liftIO $ renderStatic $ elMarkdown c
|
|
||||||
writeLBS $ Aeson.encode $ T.decodeUtf8 bs
|
|
||||||
, _backend_routeEncoder = backendRouteEncoder
|
|
||||||
}
|
|
@ -1,108 +0,0 @@
|
|||||||
{-# LANGUAGE DataKinds #-}
|
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
|
||||||
{-# LANGUAGE GADTs #-}
|
|
||||||
{-# LANGUAGE LambdaCase #-}
|
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
|
||||||
{-# LANGUAGE StandaloneDeriving #-}
|
|
||||||
{-# LANGUAGE TypeApplications #-}
|
|
||||||
|
|
||||||
module Backend.Markdown where
|
|
||||||
|
|
||||||
import Control.Foldl hiding (mapM_, mconcat)
|
|
||||||
import Control.Monad
|
|
||||||
import Control.Monad.IO.Class (MonadIO, liftIO)
|
|
||||||
import Data.Aeson
|
|
||||||
import Data.Bifunctor (first)
|
|
||||||
import qualified Data.List.NonEmpty as NE
|
|
||||||
import Data.Maybe
|
|
||||||
import Data.Text (Text)
|
|
||||||
import qualified Data.Text as T
|
|
||||||
import qualified Data.Text.IO as T
|
|
||||||
import qualified Data.Yaml as Yaml
|
|
||||||
|
|
||||||
import Text.Megaparsec.Error (ParseErrorBundle, errorBundlePretty)
|
|
||||||
import Text.MMark (MMark, MMarkErr)
|
|
||||||
import qualified Text.MMark as MMark
|
|
||||||
import Text.MMark.Extension (Block (..), Inline (..))
|
|
||||||
import qualified Text.URI as URI
|
|
||||||
|
|
||||||
import Reflex.Dom.Core hiding (Link)
|
|
||||||
|
|
||||||
|
|
||||||
elMarkdown :: DomBuilder t m => Text -> m ()
|
|
||||||
elMarkdown = markdownView . MMark.parse "<file>"
|
|
||||||
|
|
||||||
-- | WIP: Render markdown content as reflex dom.
|
|
||||||
markdownView :: DomBuilder t m => Either (ParseErrorBundle Text MMarkErr) MMark -> m ()
|
|
||||||
markdownView = \case
|
|
||||||
Left errs -> elClass "tt" "markdown-error" $ do
|
|
||||||
el "h2" $ text "Error parsing markdown:"
|
|
||||||
text $ T.pack $ errorBundlePretty errs
|
|
||||||
Right r ->
|
|
||||||
MMark.runScannerM r $ FoldM (const renderBlock) blank pure
|
|
||||||
where
|
|
||||||
renderBlocks = mapM_ renderBlock
|
|
||||||
renderBlock = \case
|
|
||||||
ThematicBreak -> el "tt" $ text "TODO: ThematicBreak"
|
|
||||||
Heading1 xs -> el "h1" $ renderInlines xs
|
|
||||||
Heading2 xs -> el "h2" $ renderInlines xs
|
|
||||||
Heading3 xs -> el "h3" $ renderInlines xs
|
|
||||||
Heading4 xs -> el "h4" $ renderInlines xs
|
|
||||||
Heading5 xs -> el "h5" $ renderInlines xs
|
|
||||||
Heading6 xs -> el "h6" $ renderInlines xs
|
|
||||||
CodeBlock info xs -> el "pre" $ elClass "code" (fromMaybe "" info) $ text xs
|
|
||||||
Naked xs -> do
|
|
||||||
-- text $ "TODO: Naked"
|
|
||||||
renderInlines xs
|
|
||||||
Paragraph xs -> el "p" $ renderInlines xs
|
|
||||||
Blockquote bs -> el "blockquote" $ renderBlocks bs
|
|
||||||
OrderedList _start bs -> el "ol" $ do
|
|
||||||
-- TODO: What to do with 'start'?
|
|
||||||
forM_ bs $ \b -> do
|
|
||||||
el "li" $ renderBlocks b
|
|
||||||
UnorderedList bs -> el "ul" $ do
|
|
||||||
forM_ bs $ \b -> do
|
|
||||||
el "li" $ renderBlocks b
|
|
||||||
Table _ _ -> el "tt" $ text "TODO: Table"
|
|
||||||
renderInlines = mapM_ renderInline . NE.toList
|
|
||||||
renderInline = \case
|
|
||||||
Plain s -> text s
|
|
||||||
LineBreak -> el "tt" $ text "TODO: LineBreak"
|
|
||||||
Emphasis xs -> el "em" $ renderInlines xs
|
|
||||||
Strong xs -> el "strong" $ renderInlines xs
|
|
||||||
Strikeout xs -> el "strike" $ renderInlines xs
|
|
||||||
Subscript xs -> el "sub" $ renderInlines xs
|
|
||||||
Superscript xs -> el "sup" $ renderInlines xs
|
|
||||||
CodeSpan s -> el "code" $ text s
|
|
||||||
Link xs dest title -> referringElement "a" "href" "title" dest title $ renderInlines xs
|
|
||||||
Image xs dest title -> referringElement "img" "src" "alt" dest title $ renderInlines xs
|
|
||||||
referringElement t refAttr titleAttr dest title = elAttr t attrs
|
|
||||||
where
|
|
||||||
attrs = mconcat $ catMaybes
|
|
||||||
[ Just $ refAttr =: URI.render dest
|
|
||||||
, (titleAttr =:) <$> title
|
|
||||||
]
|
|
||||||
|
|
||||||
-- This code is unused now
|
|
||||||
|
|
||||||
data Page = Page
|
|
||||||
{ _page_title :: Text
|
|
||||||
, _page_content :: MMark.MMark
|
|
||||||
}
|
|
||||||
deriving Show
|
|
||||||
|
|
||||||
parsePage :: MonadIO m => Text -> m (Either Text Page)
|
|
||||||
parsePage articleName = do
|
|
||||||
let articlePath = T.unpack $ "articles/" <> articleName <> ".md"
|
|
||||||
content <- liftIO $ T.readFile articlePath
|
|
||||||
case MMark.parse (T.unpack articleName) content of
|
|
||||||
Left err -> pure $ Left $ T.pack $ errorBundlePretty err
|
|
||||||
Right v -> case MMark.projectYaml v of
|
|
||||||
Nothing -> pure $ Left "No Yaml found"
|
|
||||||
Just doc -> do
|
|
||||||
let f = Yaml.withObject "metadata" $ \metadata -> do
|
|
||||||
title <- metadata .: "title"
|
|
||||||
pure $ Page title v
|
|
||||||
pure $ first T.pack $ Yaml.parseEither f doc
|
|
@ -1 +0,0 @@
|
|||||||
../static
|
|
@ -1,2 +0,0 @@
|
|||||||
optional-packages:
|
|
||||||
*
|
|
@ -1,17 +0,0 @@
|
|||||||
name: common
|
|
||||||
version: 0.1
|
|
||||||
cabal-version: >= 1.2
|
|
||||||
build-type: Simple
|
|
||||||
|
|
||||||
library
|
|
||||||
hs-source-dirs: src
|
|
||||||
build-depends: base
|
|
||||||
, obelisk-route
|
|
||||||
, mtl
|
|
||||||
, text
|
|
||||||
default-extensions:
|
|
||||||
TypeFamilies
|
|
||||||
PolyKinds
|
|
||||||
exposed-modules:
|
|
||||||
Common.Api
|
|
||||||
Common.Route
|
|
@ -1,4 +0,0 @@
|
|||||||
module Common.Api where
|
|
||||||
|
|
||||||
commonStuff :: String
|
|
||||||
commonStuff = "Here is a string defined in code common to the frontend and backend."
|
|
@ -1,54 +0,0 @@
|
|||||||
{-# LANGUAGE EmptyCase #-}
|
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
|
||||||
{-# LANGUAGE GADTs #-}
|
|
||||||
{-# LANGUAGE KindSignatures #-}
|
|
||||||
{-# LANGUAGE LambdaCase #-}
|
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# LANGUAGE RankNTypes #-}
|
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
|
||||||
|
|
||||||
module Common.Route where
|
|
||||||
|
|
||||||
{- -- You will probably want these imports for composing Encoders.
|
|
||||||
import Prelude hiding (id, (.))
|
|
||||||
import Control.Category
|
|
||||||
-}
|
|
||||||
|
|
||||||
import Data.Functor.Identity
|
|
||||||
import Data.Functor.Sum
|
|
||||||
import Data.Text (Text)
|
|
||||||
|
|
||||||
import Obelisk.Route
|
|
||||||
import Obelisk.Route.TH
|
|
||||||
|
|
||||||
data BackendRoute :: * -> * where
|
|
||||||
-- | Used to handle unparseable routes.
|
|
||||||
BackendRoute_Missing :: BackendRoute ()
|
|
||||||
-- You can define any routes that will be handled specially by the backend here.
|
|
||||||
-- i.e. These do not serve the frontend, but do something different, such as serving static files.
|
|
||||||
BackendRoute_GetArticle :: BackendRoute Text
|
|
||||||
|
|
||||||
data FrontendRoute :: * -> * where
|
|
||||||
FrontendRoute_Main :: FrontendRoute ()
|
|
||||||
FrontendRoute_Article :: FrontendRoute Text
|
|
||||||
-- This type is used to define frontend routes, i.e. ones for which the backend will serve the frontend.
|
|
||||||
|
|
||||||
backendRouteEncoder
|
|
||||||
:: Encoder (Either Text) Identity (R (Sum BackendRoute (ObeliskRoute FrontendRoute))) PageName
|
|
||||||
backendRouteEncoder = handleEncoder (const (InL BackendRoute_Missing :/ ())) $
|
|
||||||
pathComponentEncoder $ \case
|
|
||||||
InL backendRoute -> case backendRoute of
|
|
||||||
BackendRoute_Missing -> PathSegment "missing" $ unitEncoder mempty
|
|
||||||
BackendRoute_GetArticle -> PathSegment "get-article" singlePathSegmentEncoder
|
|
||||||
InR obeliskRoute -> obeliskRouteSegment obeliskRoute $ \case
|
|
||||||
-- The encoder given to PathEnd determines how to parse query parameters,
|
|
||||||
-- in this example, we have none, so we insist on it.
|
|
||||||
FrontendRoute_Main -> PathEnd $ unitEncoder mempty
|
|
||||||
FrontendRoute_Article -> PathSegment "article" singlePathSegmentEncoder
|
|
||||||
|
|
||||||
concat <$> mapM deriveRouteComponent
|
|
||||||
[ ''BackendRoute
|
|
||||||
, ''FrontendRoute
|
|
||||||
]
|
|
@ -1 +0,0 @@
|
|||||||
http://localhost:8000
|
|
@ -1,9 +0,0 @@
|
|||||||
### Config
|
|
||||||
|
|
||||||
Obelisk projects should contain a config folder with the following subfolders: common, frontend, and backend.
|
|
||||||
|
|
||||||
Things that should never be transmitted to the frontend belong in backend/ (e.g., email credentials)
|
|
||||||
|
|
||||||
Frontend-only configuration belongs in frontend/.
|
|
||||||
|
|
||||||
Shared configuration files (e.g., the route config) belong in common/
|
|
35
default.nix
35
default.nix
@ -1,34 +1,3 @@
|
|||||||
{ obelisk ? import ./.obelisk/impl {
|
(import <nixpkgs> { }).haskellPackages.developPackage {
|
||||||
system = builtins.currentSystem;
|
root = ./.;
|
||||||
iosSdkVersion = "10.2";
|
|
||||||
# You must accept the Android Software Development Kit License Agreement at
|
|
||||||
# https://developer.android.com/studio/terms in order to build Android apps.
|
|
||||||
# Uncomment and set this to `true` to indicate your acceptance:
|
|
||||||
# config.android_sdk.accept_license = false;
|
|
||||||
}
|
}
|
||||||
}:
|
|
||||||
with obelisk;
|
|
||||||
project ./. ({ pkgs, hackGet, ... }: {
|
|
||||||
android.applicationId = "ca.srid.ExplainingHaskell";
|
|
||||||
android.displayName = "Explaining Haskell";
|
|
||||||
ios.bundleIdentifier = "ca.srid.ExplainingHaskell";
|
|
||||||
ios.bundleName = "Explaining Haskell";
|
|
||||||
|
|
||||||
packages = {
|
|
||||||
# Newer mmark requires newer version of certain dependencies as well
|
|
||||||
mmark = hackGet ./dep/mmark;
|
|
||||||
megaparsec = hackGet ./dep/megaparsec;
|
|
||||||
hspec-megaparsec = hackGet ./dep/hspec-megaparsec;
|
|
||||||
modern-uri = hackGet ./dep/modern-uri;
|
|
||||||
|
|
||||||
# Use a version of neat-interpolation that works with the megaparsec version
|
|
||||||
# used by mmark above.
|
|
||||||
neat-interpolation = hackGet ./dep/neat-interpolation;
|
|
||||||
};
|
|
||||||
|
|
||||||
overrides = self: super: with pkgs.haskell.lib; {
|
|
||||||
mmark = dontHaddock (dontCheck super.mmark); # Haddock fails on ghcjs
|
|
||||||
megaparsec = dontCheck super.megaparsec;
|
|
||||||
email-validate = dontCheck super.email-validate;
|
|
||||||
};
|
|
||||||
})
|
|
||||||
|
@ -1,7 +0,0 @@
|
|||||||
# DO NOT HAND-EDIT THIS FILE
|
|
||||||
import ((import <nixpkgs> {}).fetchFromGitHub (
|
|
||||||
let json = builtins.fromJSON (builtins.readFile ./github.json);
|
|
||||||
in { inherit (json) owner repo rev sha256;
|
|
||||||
private = json.private or false;
|
|
||||||
}
|
|
||||||
))
|
|
@ -1,7 +0,0 @@
|
|||||||
{
|
|
||||||
"owner": "mrkkrp",
|
|
||||||
"repo": "hspec-megaparsec",
|
|
||||||
"branch": "master",
|
|
||||||
"rev": "5a60b42441782c6c091c39ac62b2ebaa54d14f6d",
|
|
||||||
"sha256": "0lryy03wswi0a20g0hhwls7bsprcpich4jrpfr277wh38cirqcrg"
|
|
||||||
}
|
|
@ -1,7 +0,0 @@
|
|||||||
# DO NOT HAND-EDIT THIS FILE
|
|
||||||
import ((import <nixpkgs> {}).fetchFromGitHub (
|
|
||||||
let json = builtins.fromJSON (builtins.readFile ./github.json);
|
|
||||||
in { inherit (json) owner repo rev sha256;
|
|
||||||
private = json.private or false;
|
|
||||||
}
|
|
||||||
))
|
|
@ -1,7 +0,0 @@
|
|||||||
{
|
|
||||||
"owner": "srid",
|
|
||||||
"repo": "megaparsec",
|
|
||||||
"branch": "some-master",
|
|
||||||
"rev": "3472a39ec635d27195b20cbddce186ebdb6cf8af",
|
|
||||||
"sha256": "1ypcld9qx48c83nrsghzcjh05hcwyx2yr90lcxnlh73cpfmsflfp"
|
|
||||||
}
|
|
@ -1,7 +0,0 @@
|
|||||||
# DO NOT HAND-EDIT THIS FILE
|
|
||||||
import ((import <nixpkgs> {}).fetchFromGitHub (
|
|
||||||
let json = builtins.fromJSON (builtins.readFile ./github.json);
|
|
||||||
in { inherit (json) owner repo rev sha256;
|
|
||||||
private = json.private or false;
|
|
||||||
}
|
|
||||||
))
|
|
@ -1,7 +0,0 @@
|
|||||||
{
|
|
||||||
"owner": "mmark-md",
|
|
||||||
"repo": "mmark",
|
|
||||||
"branch": "master",
|
|
||||||
"rev": "66510f3fe2ca2d320de8c58e815782f06099cfdd",
|
|
||||||
"sha256": "0y8y8wcfmc04j4jwf439g9y24i49naia5jg9jssi3hp0a1srpmnk"
|
|
||||||
}
|
|
@ -1,7 +0,0 @@
|
|||||||
# DO NOT HAND-EDIT THIS FILE
|
|
||||||
import ((import <nixpkgs> {}).fetchFromGitHub (
|
|
||||||
let json = builtins.fromJSON (builtins.readFile ./github.json);
|
|
||||||
in { inherit (json) owner repo rev sha256;
|
|
||||||
private = json.private or false;
|
|
||||||
}
|
|
||||||
))
|
|
@ -1,7 +0,0 @@
|
|||||||
{
|
|
||||||
"owner": "mrkkrp",
|
|
||||||
"repo": "modern-uri",
|
|
||||||
"branch": "master",
|
|
||||||
"rev": "c237a242fe0eada9cc7cf6132e6ce7232203ebcd",
|
|
||||||
"sha256": "0jyx96nnq861i50jq3prlz6889w8gq5sivxqddld83l505xyirpi"
|
|
||||||
}
|
|
@ -1,7 +0,0 @@
|
|||||||
# DO NOT HAND-EDIT THIS FILE
|
|
||||||
import ((import <nixpkgs> {}).fetchFromGitHub (
|
|
||||||
let json = builtins.fromJSON (builtins.readFile ./github.json);
|
|
||||||
in { inherit (json) owner repo rev sha256;
|
|
||||||
private = json.private or false;
|
|
||||||
}
|
|
||||||
))
|
|
@ -1,7 +0,0 @@
|
|||||||
{
|
|
||||||
"owner": "nikita-volkov",
|
|
||||||
"repo": "neat-interpolation",
|
|
||||||
"branch": "master",
|
|
||||||
"rev": "95c009643e89dd5db67d715078a007f7de79de27",
|
|
||||||
"sha256": "0c7wqym619nq13xrf43w6bay0yl4jnxjaj4a0akmfw3srdcz07yf"
|
|
||||||
}
|
|
@ -1,32 +0,0 @@
|
|||||||
name: frontend
|
|
||||||
version: 0.1
|
|
||||||
cabal-version: >= 1.8
|
|
||||||
build-type: Simple
|
|
||||||
|
|
||||||
library
|
|
||||||
hs-source-dirs: src
|
|
||||||
build-depends: base
|
|
||||||
, common
|
|
||||||
, obelisk-frontend
|
|
||||||
, obelisk-route
|
|
||||||
, reflex-dom
|
|
||||||
, obelisk-generated-static
|
|
||||||
, text
|
|
||||||
exposed-modules:
|
|
||||||
Frontend
|
|
||||||
ghc-options: -Wall
|
|
||||||
|
|
||||||
executable frontend
|
|
||||||
main-is: main.hs
|
|
||||||
hs-source-dirs: src-bin
|
|
||||||
build-depends: base
|
|
||||||
, common
|
|
||||||
, obelisk-frontend
|
|
||||||
, obelisk-route
|
|
||||||
, reflex-dom
|
|
||||||
, obelisk-generated-static
|
|
||||||
, frontend
|
|
||||||
--TODO: Make these ghc-options optional
|
|
||||||
ghc-options: -threaded
|
|
||||||
if os(darwin)
|
|
||||||
ghc-options: -dynamic
|
|
@ -1,10 +0,0 @@
|
|||||||
import Frontend
|
|
||||||
import Common.Route
|
|
||||||
import Obelisk.Frontend
|
|
||||||
import Obelisk.Route.Frontend
|
|
||||||
import Reflex.Dom
|
|
||||||
|
|
||||||
main :: IO ()
|
|
||||||
main = do
|
|
||||||
let Right validFullEncoder = checkEncoder backendRouteEncoder
|
|
||||||
run $ runFrontend validFullEncoder frontend
|
|
@ -1,74 +0,0 @@
|
|||||||
{-# LANGUAGE DataKinds #-}
|
|
||||||
{-# LANGUAGE LambdaCase #-}
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
|
||||||
{-# LANGUAGE TypeApplications #-}
|
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
|
||||||
module Frontend where
|
|
||||||
|
|
||||||
import Control.Monad
|
|
||||||
import Data.Functor.Identity
|
|
||||||
import Data.Functor.Sum
|
|
||||||
import Data.Text (Text)
|
|
||||||
-- import qualified Data.Text as T
|
|
||||||
|
|
||||||
import Obelisk.Frontend
|
|
||||||
import Obelisk.Route
|
|
||||||
import Obelisk.Route.Frontend
|
|
||||||
import Reflex.Dom.Core
|
|
||||||
|
|
||||||
import Common.Route
|
|
||||||
|
|
||||||
frontend :: Frontend (R FrontendRoute)
|
|
||||||
frontend = Frontend
|
|
||||||
{ _frontend_head = do
|
|
||||||
el "title" $ text "Explaining Haskell"
|
|
||||||
elAttr "link" ("rel" =: "stylesheet" <> "href" =: semuiCdnUrl "semantic.min.css") blank
|
|
||||||
|
|
||||||
, _frontend_body = divClass "ui container" $ do
|
|
||||||
subRoute_ $ \case
|
|
||||||
FrontendRoute_Main -> do
|
|
||||||
elClass "h1" "ui header" $ text "Explaining Haskell"
|
|
||||||
|
|
||||||
elClass "h2" "ui header" $ do
|
|
||||||
text "Purpose of this site"
|
|
||||||
divClass "sub header" $ text "Else why do it?"
|
|
||||||
el "p" $ text "The purpose of this site is twofold:"
|
|
||||||
el "ol" $ do
|
|
||||||
el "li" $ text "Record everything I learn in regards to Haskell for future reference"
|
|
||||||
el "li" $ text "Attempt to teach what I understand to others in the hopes of strengthening my own understanding"
|
|
||||||
|
|
||||||
elClass "h2" "ui header" $ do
|
|
||||||
text "Game plan"
|
|
||||||
divClass "sub header" $ text "How I plan to finish this"
|
|
||||||
el "p" $ text "See README.md"
|
|
||||||
|
|
||||||
elClass "h2" "ui header" $ text "List of articles"
|
|
||||||
el "ul" $
|
|
||||||
el "li" $ routeLink (FrontendRoute_Article :/ "NixTutorial") $ text "Nix Tutorial"
|
|
||||||
FrontendRoute_Article -> do
|
|
||||||
articleContent <- getArticle =<< askRoute
|
|
||||||
prerender_ (text "JavaScript is required to view this page") blank
|
|
||||||
widgetHold_ (el "div" $ text "Loading") $ ffor articleContent $ \case
|
|
||||||
Nothing -> text "nope"
|
|
||||||
Just s -> divClass "ui segment" $ do
|
|
||||||
prerender_ blank $
|
|
||||||
void $ elDynHtml' "div" $ constDyn s
|
|
||||||
}
|
|
||||||
where
|
|
||||||
semuiVersion :: Text
|
|
||||||
semuiVersion = "2.4.2"
|
|
||||||
semuiCdnUrl :: Text -> Text
|
|
||||||
semuiCdnUrl file = "https://cdn.jsdelivr.net/npm/semantic-ui@" <> semuiVersion <> "/dist/" <> file
|
|
||||||
|
|
||||||
|
|
||||||
getArticle
|
|
||||||
:: (MonadHold t m, PostBuild t m, Prerender js t m)
|
|
||||||
=> Dynamic t Text -> m (Event t (Maybe Text))
|
|
||||||
getArticle articleName =
|
|
||||||
fmap switchDyn $ prerender (pure never) $ do
|
|
||||||
pb <- getPostBuild
|
|
||||||
getAndDecode $ ffor (tag (current articleName) pb) $ \an ->
|
|
||||||
renderBackendRoute enc (BackendRoute_GetArticle :/ an)
|
|
||||||
where
|
|
||||||
Right (enc :: Encoder Identity Identity (R (Sum BackendRoute (ObeliskRoute FrontendRoute))) PageName) = checkEncoder backendRouteEncoder
|
|
42
package.yaml
Normal file
42
package.yaml
Normal file
@ -0,0 +1,42 @@
|
|||||||
|
name: ExplainingHaskell
|
||||||
|
version: 0.1.0.0
|
||||||
|
github: "srid/ExplainingHaskell"
|
||||||
|
license: BSD3
|
||||||
|
author: "Sridhar Ratnakumar"
|
||||||
|
maintainer: "srid@srid.ca"
|
||||||
|
copyright: "2019 Sridhar Ratnakumar"
|
||||||
|
|
||||||
|
extra-source-files:
|
||||||
|
- README.md
|
||||||
|
|
||||||
|
# Metadata used when publishing your package
|
||||||
|
# synopsis: Short description of your package
|
||||||
|
# category: Web
|
||||||
|
|
||||||
|
# To avoid duplicated efforts in documentation and dealing with the
|
||||||
|
# complications of embedding Haddock markup inside cabal files, it is
|
||||||
|
# common to point users to the README.md file.
|
||||||
|
description: Please see the README on GitHub at <https://github.com/srid/ExplainingHaskell>
|
||||||
|
|
||||||
|
executables:
|
||||||
|
ExplainingHaskell-exe:
|
||||||
|
main: Main.hs
|
||||||
|
source-dirs: app
|
||||||
|
ghc-options:
|
||||||
|
- -threaded
|
||||||
|
- -rtsopts
|
||||||
|
- -with-rtsopts=-N
|
||||||
|
dependencies:
|
||||||
|
- shake
|
||||||
|
- slick
|
||||||
|
- base >= 4.7 && < 5
|
||||||
|
- aeson
|
||||||
|
- lens-aeson
|
||||||
|
- lens
|
||||||
|
- pandoc
|
||||||
|
- text
|
||||||
|
- binary
|
||||||
|
- bytestring
|
||||||
|
- containers
|
||||||
|
- mustache
|
||||||
|
- time
|
568
site/css/style.css
Normal file
568
site/css/style.css
Normal file
@ -0,0 +1,568 @@
|
|||||||
|
/* CSS Reset */
|
||||||
|
html, body, div, span, object, h1, h2, h3, h4, h5, h6, p, a, abbr, acronym, em, img, ol, ul, li {
|
||||||
|
border: 0;
|
||||||
|
font-weight: inherit;
|
||||||
|
font-style: inherit;
|
||||||
|
font-size: 100%;
|
||||||
|
font-family: inherit;
|
||||||
|
vertical-align: baseline;
|
||||||
|
margin: 0;
|
||||||
|
padding: 0; }
|
||||||
|
|
||||||
|
html {
|
||||||
|
box-sizing: border-box; }
|
||||||
|
|
||||||
|
*, *:before, *:after {
|
||||||
|
box-sizing: inherit; }
|
||||||
|
|
||||||
|
/* Variables */
|
||||||
|
html {
|
||||||
|
font-family: georgia, serif;
|
||||||
|
color: #333;
|
||||||
|
background: #FFFFFC;
|
||||||
|
background: -webkit-linear-gradient(top, #EEE 0%, #FFF 10%, #FFF 90%, #EEE 100%);
|
||||||
|
background: linear-gradient(to bottom, #EEE 0%, #FFF 10%, #FFF 90%, #EEE 100%);
|
||||||
|
background-attachment: fixed;
|
||||||
|
height: 100%;
|
||||||
|
width: 100%;
|
||||||
|
z-index: -10; }
|
||||||
|
html.dark {
|
||||||
|
background: #333;
|
||||||
|
background: -webkit-linear-gradient(top, #2a2a2a 0%, #333 10%, #333 90%, #2a2a2a 100%);
|
||||||
|
background: linear-gradient(to bottom, #2a2a2a 0%, #333 10%, #333 90%, #2a2a2a 100%);
|
||||||
|
background-attachment: fixed;
|
||||||
|
width: 100%;
|
||||||
|
height: 100%;
|
||||||
|
color: #DDD; }
|
||||||
|
|
||||||
|
body {
|
||||||
|
display: -webkit-box;
|
||||||
|
display: -webkit-flex;
|
||||||
|
display: -ms-flexbox;
|
||||||
|
display: flex;
|
||||||
|
-webkit-flex-flow: column nowrap;
|
||||||
|
-ms-flex-flow: column nowrap;
|
||||||
|
flex-flow: column nowrap;
|
||||||
|
-webkit-box-pack: center;
|
||||||
|
-webkit-justify-content: center;
|
||||||
|
-ms-flex-pack: center;
|
||||||
|
justify-content: center; }
|
||||||
|
|
||||||
|
h2 {
|
||||||
|
font-family: inherit;
|
||||||
|
font-size: 1.25em;
|
||||||
|
font-variant: small-caps;
|
||||||
|
text-align: center;
|
||||||
|
width: 80%;
|
||||||
|
margin: 0 auto 0;
|
||||||
|
border-top: 1px solid #777;
|
||||||
|
margin-top: 1em;
|
||||||
|
padding: 1em 0 0 0; }
|
||||||
|
|
||||||
|
h3 {
|
||||||
|
font-size: 1.4em;
|
||||||
|
margin: 0.5em 0;
|
||||||
|
text-align: center; }
|
||||||
|
|
||||||
|
blockquote {
|
||||||
|
width: 90%;
|
||||||
|
margin: 0.7em auto;
|
||||||
|
text-align: center;
|
||||||
|
padding-left: 0.5em;
|
||||||
|
font-size: 1.1em;
|
||||||
|
font-style: italic;
|
||||||
|
display: -webkit-box;
|
||||||
|
display: -webkit-flex;
|
||||||
|
display: -ms-flexbox;
|
||||||
|
display: flex;
|
||||||
|
-webkit-flex-flow: row nowrap;
|
||||||
|
-ms-flex-flow: row nowrap;
|
||||||
|
flex-flow: row nowrap;
|
||||||
|
-webkit-box-pack: center;
|
||||||
|
-webkit-justify-content: center;
|
||||||
|
-ms-flex-pack: center;
|
||||||
|
justify-content: center; }
|
||||||
|
blockquote > p {
|
||||||
|
padding-left: 7px;
|
||||||
|
border-left: 5px solid rgba(76, 76, 76, 0.9);
|
||||||
|
margin: auto; }
|
||||||
|
|
||||||
|
ul, ol {
|
||||||
|
list-style-position: inside;
|
||||||
|
margin: 1em 0 1em 2em; }
|
||||||
|
|
||||||
|
li {
|
||||||
|
margin-bottom: 0.7em;
|
||||||
|
}
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
em {
|
||||||
|
font-weight: bold;
|
||||||
|
font-style: italic; }
|
||||||
|
|
||||||
|
img {
|
||||||
|
margin: auto; }
|
||||||
|
|
||||||
|
a, a:visited, a:hover {
|
||||||
|
color: #EB005B;
|
||||||
|
text-decoration: none;
|
||||||
|
-webkit-transition: color 0.1s;
|
||||||
|
transition: color 0.1s; }
|
||||||
|
a:hover, a:visited:hover, a:hover:hover {
|
||||||
|
color: #EB0978;
|
||||||
|
text-decoration: underline; }
|
||||||
|
|
||||||
|
header {
|
||||||
|
position: fixed;
|
||||||
|
/*color: $night-white;*/
|
||||||
|
top: 0;
|
||||||
|
height: 4em;
|
||||||
|
width: 100%; }
|
||||||
|
|
||||||
|
footer {
|
||||||
|
font-size: 0.8em;
|
||||||
|
min-height: 200px;
|
||||||
|
padding: 1em;
|
||||||
|
color: #888;
|
||||||
|
text-align: center;
|
||||||
|
clear: both; }
|
||||||
|
|
||||||
|
.photo {
|
||||||
|
border-radius: 25px;
|
||||||
|
border: 1px solid black; }
|
||||||
|
|
||||||
|
.blog {
|
||||||
|
display: table;
|
||||||
|
width: 100%;
|
||||||
|
height: 100%;
|
||||||
|
margin: auto; }
|
||||||
|
|
||||||
|
.title {
|
||||||
|
font-family: "Quicksand", helvetica, sans-serif;
|
||||||
|
font-weight: 400;
|
||||||
|
font-size: 3em;
|
||||||
|
text-transform: capitalize; }
|
||||||
|
|
||||||
|
.byline {
|
||||||
|
font-family: helvetica, sans-serif;
|
||||||
|
font-style: italic;
|
||||||
|
font-weight: 100;
|
||||||
|
font-size: 1em; }
|
||||||
|
|
||||||
|
.wrapper {
|
||||||
|
width: 100%;
|
||||||
|
display: -webkit-box;
|
||||||
|
display: -webkit-flex;
|
||||||
|
display: -ms-flexbox;
|
||||||
|
display: flex;
|
||||||
|
-webkit-flex-flow: column nowrap;
|
||||||
|
-ms-flex-flow: column nowrap;
|
||||||
|
flex-flow: column nowrap;
|
||||||
|
-webkit-box-pack: center;
|
||||||
|
-webkit-justify-content: center;
|
||||||
|
-ms-flex-pack: center;
|
||||||
|
justify-content: center;
|
||||||
|
-webkit-box-align: center;
|
||||||
|
-webkit-align-items: center;
|
||||||
|
-ms-flex-align: center;
|
||||||
|
align-items: center; }
|
||||||
|
|
||||||
|
.masthead {
|
||||||
|
display: -webkit-box;
|
||||||
|
display: -webkit-flex;
|
||||||
|
display: -ms-flexbox;
|
||||||
|
display: flex;
|
||||||
|
-webkit-flex-flow: column nowrap;
|
||||||
|
-ms-flex-flow: column nowrap;
|
||||||
|
flex-flow: column nowrap;
|
||||||
|
-webkit-box-pack: center;
|
||||||
|
-webkit-justify-content: center;
|
||||||
|
-ms-flex-pack: center;
|
||||||
|
justify-content: center;
|
||||||
|
-webkit-box-align: space-around;
|
||||||
|
-webkit-align-items: space-around;
|
||||||
|
-ms-flex-align: space-around;
|
||||||
|
align-items: space-around;
|
||||||
|
width: 100%;
|
||||||
|
min-height: 400px;
|
||||||
|
padding: 2em 10px;
|
||||||
|
text-align: center;
|
||||||
|
margin: auto; }
|
||||||
|
|
||||||
|
.post-image {
|
||||||
|
height: auto;
|
||||||
|
width: 400px;
|
||||||
|
max-width: 400px; }
|
||||||
|
|
||||||
|
.metadata {
|
||||||
|
text-align: center; }
|
||||||
|
|
||||||
|
.date {
|
||||||
|
color: rgba(128, 128, 128, 0.5);
|
||||||
|
font-size: 0.9em;
|
||||||
|
font-style: italic;
|
||||||
|
line-height: 2em;
|
||||||
|
font-family: helvetica, sans-serif; }
|
||||||
|
|
||||||
|
.categories, .tags {
|
||||||
|
color: rgba(128, 128, 128, 0.5);
|
||||||
|
font-size: 0.9em;
|
||||||
|
font-style: italic;
|
||||||
|
line-height: 2em;
|
||||||
|
font-family: helvetica, sans-serif;
|
||||||
|
width: 100%;
|
||||||
|
max-width: 500px;
|
||||||
|
display: block;
|
||||||
|
margin: auto; }
|
||||||
|
|
||||||
|
a.tag, a.category {
|
||||||
|
padding: 0px 8px;
|
||||||
|
margin: 2px 1px;
|
||||||
|
border-radius: 4px;
|
||||||
|
display: inline-block;
|
||||||
|
color: #333;
|
||||||
|
border: 1px solid rgba(76, 76, 76, 0.9);
|
||||||
|
-webkit-transition: 0.3s;
|
||||||
|
transition: 0.3s; }
|
||||||
|
a.tag:hover, a.category:hover {
|
||||||
|
background: #333;
|
||||||
|
color: #FFFFFC;
|
||||||
|
text-decoration: none; }
|
||||||
|
.dark a.tag, .dark a.category {
|
||||||
|
color: #DDD; }
|
||||||
|
.dark a.tag:hover, .dark a.category:hover {
|
||||||
|
background: #DDD;
|
||||||
|
color: #333;
|
||||||
|
text-decoration: none; }
|
||||||
|
|
||||||
|
.post {
|
||||||
|
display: -webkit-box;
|
||||||
|
display: -webkit-flex;
|
||||||
|
display: -ms-flexbox;
|
||||||
|
display: flex;
|
||||||
|
-webkit-flex-flow: column nowrap;
|
||||||
|
-ms-flex-flow: column nowrap;
|
||||||
|
flex-flow: column nowrap;
|
||||||
|
width: auto;
|
||||||
|
min-width: 100px;
|
||||||
|
max-width: 720px;
|
||||||
|
/*min-height: 100%;*/
|
||||||
|
padding: 0px 20px;
|
||||||
|
margin: 3em auto;
|
||||||
|
-webkit-transition: color 2s;
|
||||||
|
transition: color 2s;
|
||||||
|
font-size: 1.1em; }
|
||||||
|
.post p {
|
||||||
|
line-height: 1.6em;
|
||||||
|
letter-spacing: 0.02em;
|
||||||
|
margin: 0.5em 0 0 0;
|
||||||
|
-webkit-hyphens: auto;
|
||||||
|
-moz-hyphens: auto;
|
||||||
|
-ms-hyphens: auto;
|
||||||
|
hyphens: auto;
|
||||||
|
word-break: break-word; }
|
||||||
|
.post p + p {
|
||||||
|
margin-top: 1em; }
|
||||||
|
.post > p:first-of-type:first-letter {
|
||||||
|
font-size: 8em;
|
||||||
|
line-height: 0.1em;
|
||||||
|
padding-right: 0.06em; }
|
||||||
|
.post ul {
|
||||||
|
list-style-type: disc;
|
||||||
|
text-indent: -1em; }
|
||||||
|
.post ul li {
|
||||||
|
line-height: 1.3em;
|
||||||
|
letter-spacing: 0.05em;
|
||||||
|
margin: 0.5em 0 0 0;
|
||||||
|
-webkit-hyphens: auto;
|
||||||
|
-moz-hyphens: auto;
|
||||||
|
-ms-hyphens: auto;
|
||||||
|
hyphens: auto;
|
||||||
|
word-break: break-word; }
|
||||||
|
|
||||||
|
.post img {
|
||||||
|
max-width: 100%;
|
||||||
|
margin: auto;
|
||||||
|
display: block;
|
||||||
|
}
|
||||||
|
|
||||||
|
.table-of-contents {
|
||||||
|
clear: both;
|
||||||
|
width: 100%; }
|
||||||
|
.table-of-contents h1 {
|
||||||
|
font-size: 3em;
|
||||||
|
text-align: center;
|
||||||
|
font-family: "Quicksand", helvetica, sans-serif; }
|
||||||
|
.table-of-contents ul {
|
||||||
|
margin: 3em 0;
|
||||||
|
list-style: none; }
|
||||||
|
.table-of-contents li {
|
||||||
|
width: 100%; }
|
||||||
|
.table-of-contents li a {
|
||||||
|
color: #333;
|
||||||
|
font-weight: normal;
|
||||||
|
box-sizing: border-box;
|
||||||
|
border-top: 1px solid #444;
|
||||||
|
display: block;
|
||||||
|
width: 50%;
|
||||||
|
min-width: 300px;
|
||||||
|
margin: 0 auto;
|
||||||
|
padding: 1em 0.5em 1em 0;
|
||||||
|
-webkit-transition: color 0.7s, background 0.7s, padding 0.5s;
|
||||||
|
transition: color 0.7s, background 0.7s, padding 0.5s; }
|
||||||
|
.table-of-contents li a .date {
|
||||||
|
float: right;
|
||||||
|
margin-top: -0.25em;
|
||||||
|
color: rgba(128, 128, 128, 0.8); }
|
||||||
|
.table-of-contents li a:hover {
|
||||||
|
background: #333;
|
||||||
|
color: #FFFFFC;
|
||||||
|
text-decoration: none;
|
||||||
|
padding-left: 2em; }
|
||||||
|
.dark .table-of-contents ul a {
|
||||||
|
color: #DDD; }
|
||||||
|
.dark .table-of-contents ul a:hover {
|
||||||
|
background: #DDD;
|
||||||
|
color: #333;
|
||||||
|
padding-left: 2em; }
|
||||||
|
|
||||||
|
.arrow {
|
||||||
|
display: -webkit-box;
|
||||||
|
display: -webkit-flex;
|
||||||
|
display: -ms-flexbox;
|
||||||
|
display: flex;
|
||||||
|
-webkit-flex-flow: column nowrap;
|
||||||
|
-ms-flex-flow: column nowrap;
|
||||||
|
flex-flow: column nowrap;
|
||||||
|
-webkit-box-pack: center;
|
||||||
|
-webkit-justify-content: center;
|
||||||
|
-ms-flex-pack: center;
|
||||||
|
justify-content: center;
|
||||||
|
-webkit-box-align: center;
|
||||||
|
-webkit-align-items: center;
|
||||||
|
-ms-flex-align: center;
|
||||||
|
align-items: center;
|
||||||
|
font-size: 1.5em;
|
||||||
|
width: 1.5em;
|
||||||
|
height: 1.5em;
|
||||||
|
background: #DDD;
|
||||||
|
/*display: table-cell;*/
|
||||||
|
/*vertical-align: middle;*/
|
||||||
|
text-align: center;
|
||||||
|
/*padding-top: 0.14em;*/
|
||||||
|
box-sizing: border-box;
|
||||||
|
border-radius: 0.75em;
|
||||||
|
opacity: 0.7;
|
||||||
|
-webkit-transition: background 0.5s, opacity 0.5s, width 0.5s;
|
||||||
|
transition: background 0.5s, opacity 0.5s, width 0.5s;
|
||||||
|
cursor: pointer; }
|
||||||
|
.arrow:hover {
|
||||||
|
box-sizing: border-box;
|
||||||
|
width: 2em;
|
||||||
|
color: #EB005B;
|
||||||
|
border: 1px solid #EB005B;
|
||||||
|
opacity: 0.9;
|
||||||
|
background: #FFFFFC;
|
||||||
|
-webkit-transition: background 0.5s, opacity 0.5s, width 0.5s;
|
||||||
|
transition: background 0.5s, opacity 0.5s, width 0.5s;
|
||||||
|
text-decoration: none; }
|
||||||
|
.dark .arrow {
|
||||||
|
background: #222; }
|
||||||
|
.dark .arrow:hover {
|
||||||
|
color: #C00762;
|
||||||
|
border-color: #C00762; }
|
||||||
|
|
||||||
|
.social-buttons {
|
||||||
|
display: -webkit-box;
|
||||||
|
display: -webkit-flex;
|
||||||
|
display: -ms-flexbox;
|
||||||
|
display: flex;
|
||||||
|
-webkit-flex-flow: row nowrap;
|
||||||
|
-ms-flex-flow: row nowrap;
|
||||||
|
flex-flow: row nowrap;
|
||||||
|
-webkit-box-pack: center;
|
||||||
|
-webkit-justify-content: center;
|
||||||
|
-ms-flex-pack: center;
|
||||||
|
justify-content: center;
|
||||||
|
margin: 1em 0; }
|
||||||
|
.social-buttons > div {
|
||||||
|
/*margin: 0 1em;*/ }
|
||||||
|
.social-buttons .twitter-share-button {
|
||||||
|
max-width: 90px;
|
||||||
|
margin-right: 5px; }
|
||||||
|
|
||||||
|
.center {
|
||||||
|
text-align: center;
|
||||||
|
margin: auto; }
|
||||||
|
|
||||||
|
.monochrome {
|
||||||
|
color: #333; }
|
||||||
|
.dark .monochrome {
|
||||||
|
color: #DDD; }
|
||||||
|
|
||||||
|
.gem-info {
|
||||||
|
display: -webkit-box;
|
||||||
|
display: -webkit-flex;
|
||||||
|
display: -ms-flexbox;
|
||||||
|
display: flex;
|
||||||
|
-webkit-flex-flow: column nowrap;
|
||||||
|
-ms-flex-flow: column nowrap;
|
||||||
|
flex-flow: column nowrap;
|
||||||
|
margin: auto;
|
||||||
|
-webkit-box-align: center;
|
||||||
|
-webkit-align-items: center;
|
||||||
|
-ms-flex-align: center;
|
||||||
|
align-items: center; }
|
||||||
|
.gem-info table {
|
||||||
|
border: 1px solid #333;
|
||||||
|
border-collapse: collapse; }
|
||||||
|
.gem-info table td {
|
||||||
|
border: 1px solid #333;
|
||||||
|
padding: 0.4em 1em; }
|
||||||
|
.dark .gem-info table {
|
||||||
|
border: 1px solid #DDD; }
|
||||||
|
.dark .gem-info table td {
|
||||||
|
border: 1px solid #DDD; }
|
||||||
|
|
||||||
|
.pager-title {
|
||||||
|
display: -webkit-box;
|
||||||
|
display: -webkit-flex;
|
||||||
|
display: -ms-flexbox;
|
||||||
|
display: flex;
|
||||||
|
-webkit-flex-flow: column nowrap;
|
||||||
|
-ms-flex-flow: column nowrap;
|
||||||
|
flex-flow: column nowrap;
|
||||||
|
-webkit-box-align: center;
|
||||||
|
-webkit-align-items: center;
|
||||||
|
-ms-flex-align: center;
|
||||||
|
align-items: center; }
|
||||||
|
.pager-title span {
|
||||||
|
text-align: center; }
|
||||||
|
|
||||||
|
.pager article {
|
||||||
|
margin-top: 2em; }
|
||||||
|
|
||||||
|
.dark #disqus_thread {
|
||||||
|
color: #DDD; }
|
||||||
|
|
||||||
|
#page {
|
||||||
|
margin: 4em 0; }
|
||||||
|
|
||||||
|
#theme-button {
|
||||||
|
text-transform: uppercase;
|
||||||
|
font-family: "Quicksand", helvetica, sans-serif;
|
||||||
|
font-size: 1.5em;
|
||||||
|
font-weight: bold;
|
||||||
|
text-align: right;
|
||||||
|
cursor: pointer;
|
||||||
|
-webkit-transition: opacity 0.5s, color 2s;
|
||||||
|
transition: opacity 0.5s, color 2s;
|
||||||
|
opacity: 0.6; }
|
||||||
|
#theme-button:hover {
|
||||||
|
opacity: 1; }
|
||||||
|
.dark #theme-button {
|
||||||
|
color: #DDD; }
|
||||||
|
|
||||||
|
#beacon {
|
||||||
|
font-family: "Oswald", helvetica, sans-serif;
|
||||||
|
font-size: 4em;
|
||||||
|
height: 1.5em;
|
||||||
|
width: 1.5em;
|
||||||
|
text-align: center;
|
||||||
|
margin: 0.1em;
|
||||||
|
position: absolute;
|
||||||
|
border-radius: 0.1em;
|
||||||
|
opacity: 0.4;
|
||||||
|
-webkit-transition: opacity 0.5s;
|
||||||
|
transition: opacity 0.5s;
|
||||||
|
color: inherit; }
|
||||||
|
#beacon path {
|
||||||
|
fill: currentColor; }
|
||||||
|
#beacon .logo {
|
||||||
|
width: 100%;
|
||||||
|
height: 100%; }
|
||||||
|
#beacon:hover {
|
||||||
|
opacity: 1;
|
||||||
|
text-decoration: none; }
|
||||||
|
|
||||||
|
#home-text {
|
||||||
|
font-size: 0.8em;
|
||||||
|
}
|
||||||
|
|
||||||
|
#leftarrow {
|
||||||
|
position: fixed;
|
||||||
|
left: 5px;
|
||||||
|
top: calc(50% - 15px);
|
||||||
|
text-decoration: none; }
|
||||||
|
|
||||||
|
#rightarrow {
|
||||||
|
position: fixed;
|
||||||
|
right: 10px;
|
||||||
|
top: calc(50% - 15px);
|
||||||
|
text-decoration: none; }
|
||||||
|
|
||||||
|
@media only screen and (max-width: 750px) {
|
||||||
|
header {
|
||||||
|
color: #FFFFFC;
|
||||||
|
height: 3em;
|
||||||
|
background: rgba(76, 76, 76, 0.9); }
|
||||||
|
|
||||||
|
#beacon {
|
||||||
|
color: #FFFFFC;
|
||||||
|
font-size: 2em;
|
||||||
|
margin: 0; }
|
||||||
|
|
||||||
|
#theme-button {
|
||||||
|
color: #FFFFFC;
|
||||||
|
font-size: 1.5em;
|
||||||
|
top: 0.5em;
|
||||||
|
right: 0.2em;
|
||||||
|
opacity: 0.5; } }
|
||||||
|
@media only screen and (min-device-width: 320px) and (max-device-width: 480px) {
|
||||||
|
/* Styles */
|
||||||
|
h2 {
|
||||||
|
border-top: 3px solid #777; }
|
||||||
|
|
||||||
|
.page {
|
||||||
|
min-width: none;
|
||||||
|
max-width: none;
|
||||||
|
width: auto;
|
||||||
|
padding: 0 1em;
|
||||||
|
margin: 0;
|
||||||
|
box-sizing: border-box; }
|
||||||
|
|
||||||
|
.page p {
|
||||||
|
padding-bottom: 1em;
|
||||||
|
font-size: 1em;
|
||||||
|
line-height: 1.8em; }
|
||||||
|
|
||||||
|
.post-image {
|
||||||
|
height: auto;
|
||||||
|
width: auto;
|
||||||
|
max-width: 280px; }
|
||||||
|
|
||||||
|
.page > p:first-of-type:first-letter {
|
||||||
|
font-size: 4em;
|
||||||
|
line-height: 0.1em; } }
|
||||||
|
@media only screen and (max-height: 450px) {
|
||||||
|
.masthead {
|
||||||
|
min-height: 350px; } }
|
||||||
|
|
||||||
|
.ext-link img {
|
||||||
|
width: 32px;
|
||||||
|
height: 32px;
|
||||||
|
}
|
||||||
|
|
||||||
|
.right-sidebar {
|
||||||
|
position: absolute;
|
||||||
|
top: 0.75em;
|
||||||
|
right: 0.7em;
|
||||||
|
display: flex;
|
||||||
|
}
|
||||||
|
|
||||||
|
.right-sidebar > * {
|
||||||
|
margin-left: 12px;
|
||||||
|
}
|
||||||
|
|
||||||
|
/*# sourceMappingURL=style.css.map */
|
32
site/css/syntax.css
Normal file
32
site/css/syntax.css
Normal file
@ -0,0 +1,32 @@
|
|||||||
|
pre {
|
||||||
|
background-color: #F5FCFF;
|
||||||
|
}
|
||||||
|
|
||||||
|
code {
|
||||||
|
background-color: #F5FCFF;
|
||||||
|
color: #268BD2;
|
||||||
|
}
|
||||||
|
|
||||||
|
/* KeyWordTok */
|
||||||
|
.sourceCode .kw { color: #600095; }
|
||||||
|
/* DataTypeTok */
|
||||||
|
.sourceCode .dt { color: #268BD2; }
|
||||||
|
|
||||||
|
/* DecValTok (decimal value), BaseNTok, FloatTok */
|
||||||
|
.sourceCode .dv, .sourceCode .bn, .sourceCode .fl { color: #AE81FF; }
|
||||||
|
/* CharTok */
|
||||||
|
.sourceCode .ch { color: #37ad2d; }
|
||||||
|
/* StringTok */
|
||||||
|
.sourceCode .st { color: #37ad2d; }
|
||||||
|
/* CommentTok */
|
||||||
|
.sourceCode .co { color: #7E8E91; }
|
||||||
|
/* OtherTok */
|
||||||
|
.sourceCode .ot { color: #EB005B; }
|
||||||
|
/* AlertTok */
|
||||||
|
.sourceCode .al { color: #A6E22E; font-weight: bold; }
|
||||||
|
/* FunctionTok */
|
||||||
|
.sourceCode .fu { color: #333; }
|
||||||
|
/* RegionMarkerTok */
|
||||||
|
.sourceCode .re { }
|
||||||
|
/* ErrorTok */
|
||||||
|
.sourceCode .er { color: #E6DB74; font-weight: bold; }
|
BIN
site/images/battleship.jpg
Normal file
BIN
site/images/battleship.jpg
Normal file
Binary file not shown.
After Width: | Height: | Size: 73 KiB |
0
site/js/.gitkeep
Normal file
0
site/js/.gitkeep
Normal file
@ -1,4 +1,11 @@
|
|||||||
# Nix tutorial for Haskellers
|
---
|
||||||
|
title: "Nix tutorial for Haskellers"
|
||||||
|
author: Sridhar Ratnakumar
|
||||||
|
date: Jul 19, 2019
|
||||||
|
tags: [nix]
|
||||||
|
description: How to develop Haskell projects using Nix
|
||||||
|
image: battleship.jpg
|
||||||
|
---
|
||||||
|
|
||||||
The goal of this article is to get you comfortable managing simple Haskell
|
The goal of this article is to get you comfortable managing simple Haskell
|
||||||
programs and projects using the **Nix** package manager.
|
programs and projects using the **Nix** package manager.
|
8
site/templates/footer.html
Normal file
8
site/templates/footer.html
Normal file
@ -0,0 +1,8 @@
|
|||||||
|
<footer>
|
||||||
|
Built with Haskell ❤️
|
||||||
|
</footer>
|
||||||
|
|
||||||
|
<link href='https://fonts.googleapis.com/css?family=Quicksand:300,400' rel='stylesheet' type='text/css'>
|
||||||
|
<link href='https://fonts.googleapis.com/css?family=Oswald' rel='stylesheet' type='text/css'>
|
||||||
|
</body>
|
||||||
|
</html>
|
18
site/templates/header.html
Normal file
18
site/templates/header.html
Normal file
@ -0,0 +1,18 @@
|
|||||||
|
<header>
|
||||||
|
<nav>
|
||||||
|
<a id="beacon" href="/">
|
||||||
|
<div id="home-text"> HOME </div>
|
||||||
|
</a>
|
||||||
|
</nav>
|
||||||
|
|
||||||
|
<div class="right-sidebar">
|
||||||
|
<a class="ext-link" href="https://github.com/srid">
|
||||||
|
<img src="/images/github-logo.png" alt="Github Profile"/>
|
||||||
|
</a>
|
||||||
|
|
||||||
|
<a class="ext-link" href="https://twitter.com/carnivivre">
|
||||||
|
<img src="/images/twitter-logo.png" alt="Twitter Profile"/>
|
||||||
|
</a>
|
||||||
|
<div id="theme-button">DAY</div>
|
||||||
|
</div>
|
||||||
|
</header>
|
23
site/templates/index.html
Normal file
23
site/templates/index.html
Normal file
@ -0,0 +1,23 @@
|
|||||||
|
<!DOCTYPE html>
|
||||||
|
<html lang="en">
|
||||||
|
<head profile="http://www.w3.org/2005/10/profile">
|
||||||
|
<meta charset="UTF-8">
|
||||||
|
<meta name="description" content="Explaining Haskell and related concepts as understood by Sridhar Ratnakumar">
|
||||||
|
<meta name="author" content="Sridhar Ratnakumar">
|
||||||
|
<meta name=viewport content="width=device-width, initial-scale=1">
|
||||||
|
<title>Explaining Haskell</title>
|
||||||
|
<link rel="icon" type="image/png" href="/images/favicon.png">
|
||||||
|
<link rel="stylesheet" href="/css/style.css">
|
||||||
|
</head>
|
||||||
|
<body>
|
||||||
|
{{>site/templates/header.html}}
|
||||||
|
<div id="page">
|
||||||
|
<section class="table-of-contents">
|
||||||
|
<h1>All Posts</h1>
|
||||||
|
<div class="metadata">
|
||||||
|
</div>
|
||||||
|
{{>site/templates/post-list.html}}
|
||||||
|
</section>
|
||||||
|
</div>
|
||||||
|
|
||||||
|
{{>site/templates/footer.html}}
|
5
site/templates/meta-data.html
Normal file
5
site/templates/meta-data.html
Normal file
@ -0,0 +1,5 @@
|
|||||||
|
<meta name="twitter:card" content="summary_large_image">
|
||||||
|
<meta name="twitter:site" content="@carnivivre">
|
||||||
|
<meta name="twitter:creator" content="@carnivivre">
|
||||||
|
<meta name="twitter:title" content="{{title}}">
|
||||||
|
<meta name="twitter:description" content="{{description}}">
|
7
site/templates/post-list.html
Normal file
7
site/templates/post-list.html
Normal file
@ -0,0 +1,7 @@
|
|||||||
|
<ul>
|
||||||
|
{{#posts}}
|
||||||
|
<li>
|
||||||
|
<a href="{{url}}">{{title}} <span class="date">{{date}}</span> </a>
|
||||||
|
</li>
|
||||||
|
{{/posts}}
|
||||||
|
</ul>
|
46
site/templates/post.html
Normal file
46
site/templates/post.html
Normal file
@ -0,0 +1,46 @@
|
|||||||
|
<!DOCTYPE html>
|
||||||
|
<html lang="en">
|
||||||
|
<head profile="http://www.w3.org/2005/10/profile">
|
||||||
|
<meta charset="UTF-8">
|
||||||
|
<meta name="description" content="{{description}}">
|
||||||
|
<meta name="author" content="{{author}}">
|
||||||
|
<meta name=viewport content="width=device-width, initial-scale=1">
|
||||||
|
{{>site/templates/meta-data.html}}
|
||||||
|
<title>{{title}}</title>
|
||||||
|
<link rel="stylesheet" href="/css/style.css">
|
||||||
|
<link rel="stylesheet" href="/css/syntax.css">
|
||||||
|
</head>
|
||||||
|
<body>
|
||||||
|
{{>site/templates/header.html}}
|
||||||
|
|
||||||
|
<div id="page">
|
||||||
|
<div class="wrapper">
|
||||||
|
<div class="masthead">
|
||||||
|
<span class="title">
|
||||||
|
{{title}}
|
||||||
|
</span>
|
||||||
|
<br>
|
||||||
|
|
||||||
|
{{#image}}
|
||||||
|
<img class="post-image" src="/images/{{image}}">
|
||||||
|
{{/image}}
|
||||||
|
<br>
|
||||||
|
{{#author}}
|
||||||
|
<span class="byline">by {{author}}</span>
|
||||||
|
{{/author}}
|
||||||
|
<br>
|
||||||
|
<span class="date">{{date}}</span>
|
||||||
|
<br>
|
||||||
|
<div class="metadata">
|
||||||
|
</div>
|
||||||
|
</div>
|
||||||
|
</div>
|
||||||
|
<article class="post">
|
||||||
|
{{{content}}}
|
||||||
|
<br>
|
||||||
|
<br>
|
||||||
|
</article>
|
||||||
|
|
||||||
|
</div>
|
||||||
|
|
||||||
|
{{>site/templates/footer.html}}
|
Binary file not shown.
Before Width: | Height: | Size: 17 KiB |
Loading…
Reference in New Issue
Block a user