Skip to content

Commit

Permalink
Added substitutions to CCWF
Browse files Browse the repository at this point in the history
  • Loading branch information
alexgerdes committed Mar 18, 2017
1 parent 67215c0 commit c97af1a
Show file tree
Hide file tree
Showing 4 changed files with 17 additions and 5 deletions.
2 changes: 1 addition & 1 deletion CCWF.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
-- | Chalmers course
module CCWF
( -- * Configuring and updating pages
Website (..), Info (..), Materials (..)
Website (..), Info (..), Materials (..), Subst(..)
, URL, Teacher (..), Lecture (..)

-- * Building the website
Expand Down
4 changes: 4 additions & 0 deletions CCWF/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ type URL = String
data Website = Website
{ courseInfo :: Info
, courseMaterials :: Materials
, courseSubst :: Subst
}

-- | Lectures, files and news items: course materials that will likely be
Expand Down Expand Up @@ -82,6 +83,9 @@ data Info = Info
, labDeadlines :: [String]
}

-- | Substitutions allow you to write abbreviations for phrases you often use.
data Subst = Subst [(String, String)]

-- | Bio for the teacher responsible for the course.
-- Name, phone and email are mandatory.
data Teacher = Teacher
Expand Down
9 changes: 6 additions & 3 deletions CCWF/Impl.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE OverloadedStrings, RecordWildCards, TupleSections #-}
module CCWF.Impl where

import Hakyll
import Control.Monad
import Data.Char
Expand All @@ -14,7 +15,7 @@ import CCWF.Config

-- | Build a website from a configuration.
mkWebsite :: Website -> IO ()
mkWebsite (Website (Info{..}) (Materials{..})) = do
mkWebsite (Website (Info{..}) (Materials{..}) (Subst subst)) = do
-- Check that all lecture files are present
let files = [ "./files/" ++ file
| fs <- map lectureFiles lectures
Expand Down Expand Up @@ -76,7 +77,7 @@ mkWebsite (Website (Info{..}) (Materials{..})) = do
-- Context for the page content; contains metadata set in the
-- markdown file for each page, as well as some info set at the
-- top of this file.
ctx = mconcat
ctx = mconcat $
[ constField "year" (show courseYear)
, constField "coursename" courseName
, constField "coursecode" courseCode
Expand Down Expand Up @@ -105,7 +106,9 @@ mkWebsite (Website (Info{..}) (Materials{..})) = do
else mempty
, listField "latestnews" defaultContext (pure $ take 3 newsItemItems)
, defaultContext
]
] ++
-- Substitution context
[ constField k v | (k, v) <- subst]
applyMeAsTemplate ctx ctx
where
newsItemItems = map (Item (fromFilePath "")) newsItems
Expand Down
7 changes: 6 additions & 1 deletion website.hs
Original file line number Diff line number Diff line change
Expand Up @@ -125,4 +125,9 @@ info = Info
]
}

main = mkWebsite (Website info materials)
subst = Subst
[ ("javalette", "[Javalette](/project#javalette)")
, ("timeedit" , "[TimeEdit](/schedule))")
]

main = mkWebsite (Website info materials subst)

0 comments on commit c97af1a

Please sign in to comment.