Better naming scheme.

This commit is contained in:
Jasper Van der Jeugt 2010-01-31 11:19:57 +01:00
parent 73d6b1d661
commit 7afabf5c09
14 changed files with 48 additions and 48 deletions

View file

@ -26,7 +26,7 @@ main = hakyll $ do
renderPostList "posts.html" "All posts" renderablePosts
-- Render post list per category
mapM_ (\(category, posts) -> renderPostList (categoryToURL category) ("Posts about " ++ category) posts)
mapM_ (\(category, posts) -> renderPostList (categoryToUrl category) ("Posts about " ++ category) posts)
(toList categoryMap)
-- Render index, including recent posts.
@ -51,12 +51,12 @@ main = hakyll $ do
where postManipulation :: ContextManipulation
postManipulation = renderDate "date" "%B %e, %Y" "Date unknown"
categoryToURL category = "$root/categories/" ++ removeSpaces category ++ ".html"
categoryToUrl category = "$root/categories/" ++ removeSpaces category ++ ".html"
categoryList :: TagMap -> String
categoryList = uncurry categoryListItem <=< toList
categoryListItem category posts = "<li>" ++ link category (categoryToURL category)
categoryListItem category posts = "<li>" ++ link category (categoryToUrl category)
++ " - " ++ show (length posts) ++ " items.</li>"
renderPostList url title posts = do

View file

@ -80,7 +80,7 @@ Combining two `Renderable`s, but setting a different `url` is quite common, so
there is another function that helps us here:
~~~~~{.haskell}
combineWithURL :: (Renderable a, Renderable b)
combineWithUrl :: (Renderable a, Renderable b)
=> FilePath -> a -> b -> CombinedRenderable a b
~~~~~

View file

@ -130,7 +130,7 @@ clickable. We can again solve this with a `ContextManipulation`. We have a
function that produces an url for a given tag:
~~~~~{.haskell}
tagToURL tag = "$root/tags/" ++ removeSpaces tag ++ ".html"
tagToUrl tag = "$root/tags/" ++ removeSpaces tag ++ ".html"
~~~~~
`removeSpaces` is an auxiliary function from `Text.Hakyll.File`. Now, there is
@ -142,7 +142,7 @@ for a given tag - the function we just wrote. Let's extend our
~~~~~{.haskell}
postManipulation :: ContextManipulation
postManipulation = renderDate "date" "%B %e, %Y" "Unknown date"
. renderTagLinks tagToURL
. renderTagLinks tagToUrl
~~~~~
So, the `renderTagLinks` function replaces the `$tags` value from
@ -167,7 +167,7 @@ needs this so it can cache the tags.
~~~~~{.haskell}
tagMap <- readTagMap "postTags" postPaths
let renderListForTag (tag, posts) =
renderPostList (tagToURL tag)
renderPostList (tagToUrl tag)
("Posts tagged " ++ tag)
mapM_ renderListForTag (toList tagMap)
~~~~~
@ -193,7 +193,7 @@ Then, we give a minimum and a maximum font size in percent, and we get the
tag cloud back. We can add this to our index:
~~~~~{.haskell}
let tagCloud = renderTagCloud tagMap tagToURL 100 200
let tagCloud = renderTagCloud tagMap tagToUrl 100 200
index = createListingWith postManipulation "index.html"
"templates/postitem.html"
(take 3 renderablePosts)

View file

@ -65,7 +65,7 @@ a list item for one category:
~~~~~{.haskell}
categoryListItem category posts =
"<li>" ++ link category (categoryToURL category)
"<li>" ++ link category (categoryToUrl category)
++ " - " ++ show (length posts) ++ " items.</li>"
~~~~~

View file

@ -26,11 +26,11 @@ main = hakyll $ do
renderPostList "posts.html" "All posts" renderablePosts
-- Render post list per tag
mapM_ (\(tag, posts) -> renderPostList (tagToURL tag) ("Posts tagged " ++ tag) posts)
mapM_ (\(tag, posts) -> renderPostList (tagToUrl tag) ("Posts tagged " ++ tag) posts)
(toList tagMap)
-- Render index, including recent posts.
let tagCloud = renderTagCloud tagMap tagToURL 100 200
let tagCloud = renderTagCloud tagMap tagToUrl 100 200
index = createListingWith postManipulation "index.html"
"templates/postitem.html"
(take 3 renderablePosts)
@ -51,9 +51,9 @@ main = hakyll $ do
where postManipulation :: ContextManipulation
postManipulation = renderDate "date" "%B %e, %Y" "Date unknown"
. renderTagLinks tagToURL
. renderTagLinks tagToUrl
tagToURL tag = "$root/tags/" ++ removeSpaces tag ++ ".html"
tagToUrl tag = "$root/tags/" ++ removeSpaces tag ++ ".html"
renderPostList url title posts = do
let list = createListingWith postManipulation url "templates/postitem.html" posts [("title", title)]

View file

@ -49,6 +49,6 @@ library
Text.Hakyll.Util
Text.Hakyll.Tags
Text.Hakyll.Internal.Cache
Text.Hakyll.Internal.CompressCSS
Text.Hakyll.Internal.CompressCss
Text.Hakyll.Internal.Render
Text.Hakyll.Internal.Template

View file

@ -3,7 +3,7 @@
module Text.Hakyll.File
( toDestination
, toCache
, toURL
, toUrl
, toRoot
, removeSpaces
, makeDirectories
@ -46,8 +46,8 @@ toCache path = do dir <- askHakyll cacheDirectory
return $ dir </> removeLeadingSeparator path
-- | Get the url for a given page.
toURL :: FilePath -> FilePath
toURL path = if takeExtension path `elem` [ ".markdown"
toUrl :: FilePath -> FilePath
toUrl path = if takeExtension path `elem` [ ".markdown"
, ".md"
, ".mdn"
, ".mdwn"

View file

@ -1,7 +1,7 @@
-- | Module used for CSS compression. The compression is currently in a simple
-- state, but would typically reduce the number of bytes by about 25%.
module Text.Hakyll.Internal.CompressCSS
( compressCSS
module Text.Hakyll.Internal.CompressCss
( compressCss
) where
import Data.List (isPrefixOf)
@ -9,8 +9,8 @@ import Data.List (isPrefixOf)
import Text.Hakyll.Regex (substituteRegex)
-- | Compress CSS to speed up your site.
compressCSS :: String -> String
compressCSS = compressSeparators
compressCss :: String -> String
compressCss = compressSeparators
. stripComments
. compressWhitespace

View file

@ -65,4 +65,4 @@ writePage page = do
liftIO $ writeFile destination $ finalSubstitute (fromString $ getBody page)
context
where
url = getURL page
url = getUrl page

View file

@ -43,8 +43,8 @@ getValue str (Page page) = fromMaybe [] $ M.lookup str page
-- | Get the URL for a certain page. This should always be defined. If
-- not, it will error.
getPageURL :: Page -> String
getPageURL (Page page) = fromMaybe (error "No page url") $ M.lookup "url" page
getPageUrl :: Page -> String
getPageUrl (Page page) = fromMaybe (error "No page url") $ M.lookup "url" page
-- | Get the original page path.
getPagePath :: Page -> String
@ -134,7 +134,7 @@ readPageFromFile path = do
return page
where
url = toURL path
url = toUrl path
category = let dirs = splitDirectories $ takeDirectory path
in [("category", last dirs) | not (null dirs)]
@ -153,7 +153,7 @@ readPage path = do
-- Make pages renderable.
instance Renderable Page where
getDependencies = (:[]) . getPagePath
getURL = getPageURL
getUrl = getPageUrl
toContext (Page page) = return page
-- Make pages serializable.

View file

@ -22,7 +22,7 @@ import Text.Hakyll.Page
import Text.Hakyll.Renderable
import Text.Hakyll.File
import Text.Hakyll.Internal.Template (readTemplate)
import Text.Hakyll.Internal.CompressCSS
import Text.Hakyll.Internal.CompressCss
import Text.Hakyll.Internal.Render
-- | Execute an IO action only when the cache is invalid.
@ -101,7 +101,7 @@ renderChain = renderChainWith id
renderChainWith :: Renderable a
=> ContextManipulation -> [FilePath] -> a -> Hakyll ()
renderChainWith manipulation templatePaths renderable =
depends (getURL renderable) dependencies render'
depends (getUrl renderable) dependencies render'
where
dependencies = getDependencies renderable ++ templatePaths
render' = do
@ -126,4 +126,4 @@ css source = do destination <- toDestination source
where
css' destination = do contents <- liftIO $ readFile source
makeDirectories destination
liftIO $ writeFile destination (compressCSS contents)
liftIO $ writeFile destination (compressCss contents)

View file

@ -1,5 +1,5 @@
module Text.Hakyll.Renderable
( Renderable(toContext, getDependencies, getURL)
( Renderable(toContext, getDependencies, getUrl)
) where
import Text.Hakyll.Hakyll (Hakyll)
@ -15,4 +15,4 @@ class Renderable a where
getDependencies :: a -> [FilePath]
-- | Get the destination for the renderable.
getURL :: a -> FilePath
getUrl :: a -> FilePath

View file

@ -7,7 +7,7 @@ module Text.Hakyll.Renderables
, createPagePath
, CombinedRenderable
, combine
, combineWithURL
, combineWithUrl
) where
import qualified Data.Map as M
@ -25,7 +25,7 @@ import Text.Hakyll.Render
-- | A custom page.
data CustomPage = CustomPage
{ customPageURL :: String,
{ customPageUrl :: String,
customPageDependencies :: [FilePath],
customPageContext :: [(String, Either String (Hakyll String))]
}
@ -85,11 +85,11 @@ createListingWith manipulation url template renderables additional =
instance Renderable CustomPage where
getDependencies = customPageDependencies
getURL = customPageURL
getUrl = customPageUrl
toContext page = do
values <- mapM (either return id . snd) (customPageContext page)
let pairs = zip (map fst $ customPageContext page) values
return $ M.fromList $ ("url", customPageURL page) : pairs
return $ M.fromList $ ("url", customPageUrl page) : pairs
-- | PagePath is a class that wraps a FilePath. This is used to render Pages
-- without reading them first through use of caching.
@ -102,7 +102,7 @@ createPagePath = PagePath
-- We can render filepaths
instance Renderable PagePath where
getDependencies (PagePath path) = return path
getURL (PagePath path) = toURL path
getUrl (PagePath path) = toUrl path
toContext (PagePath path) = readPage path >>= toContext
-- We can serialize filepaths
@ -112,7 +112,7 @@ instance Binary PagePath where
-- | A combination of two other renderables.
data CombinedRenderable a b = CombinedRenderable a b
| CombinedRenderableWithURL FilePath a b
| CombinedRenderableWithUrl FilePath a b
-- | Combine two renderables. The url will always be taken from the first
-- @Renderable@. Also, if a `$key` is present in both renderables, the
@ -125,12 +125,12 @@ combine = CombinedRenderable
-- | Combine two renderables and set a custom URL. This behaves like @combine@,
-- except that for the @url@ field, the given URL is always chosen.
combineWithURL :: (Renderable a, Renderable b)
combineWithUrl :: (Renderable a, Renderable b)
=> FilePath
-> a
-> b
-> CombinedRenderable a b
combineWithURL = CombinedRenderableWithURL
combineWithUrl = CombinedRenderableWithUrl
-- Render combinations.
instance (Renderable a, Renderable b)
@ -139,18 +139,18 @@ instance (Renderable a, Renderable b)
-- Add the dependencies.
getDependencies (CombinedRenderable a b) =
getDependencies a ++ getDependencies b
getDependencies (CombinedRenderableWithURL _ a b) =
getDependencies (CombinedRenderableWithUrl _ a b) =
getDependencies a ++ getDependencies b
-- Take the url from the first renderable, or the specified URL.
getURL (CombinedRenderable a _) = getURL a
getURL (CombinedRenderableWithURL url _ _) = url
getUrl (CombinedRenderable a _) = getUrl a
getUrl (CombinedRenderableWithUrl url _ _) = url
-- Take a union of the contexts.
toContext (CombinedRenderable a b) = do
c1 <- toContext a
c2 <- toContext b
return $ c1 `M.union` c2
toContext (CombinedRenderableWithURL url a b) = do
toContext (CombinedRenderableWithUrl url a b) = do
c <- toContext (CombinedRenderable a b)
return $ M.singleton "url" url `M.union` c

View file

@ -1,7 +1,7 @@
-- | Miscellaneous text manipulation functions.
module Text.Hakyll.Util
( trim
, stripHTML
, stripHtml
, link
) where
@ -14,11 +14,11 @@ trim = reverse . trim' . reverse . trim'
trim' = dropWhile isSpace
-- | Strip html tags from the given string.
stripHTML :: String -> String
stripHTML [] = []
stripHTML str = let (beforeTag, rest) = break (== '<') str
stripHtml :: String -> String
stripHtml [] = []
stripHtml str = let (beforeTag, rest) = break (== '<') str
(_, afterTag) = break (== '>') rest
in beforeTag ++ stripHTML (tail' afterTag)
in beforeTag ++ stripHtml (tail' afterTag)
where
-- We need a failsafe tail function.
tail' [] = []