Compare commits
	
		
			2 Commits
		
	
	
		
			73b42aafa3
			...
			6afa6d55d4
		
	
	| Author | SHA1 | Date | |
|---|---|---|---|
| 6afa6d55d4 | |||
| d89a2bae5c | 
| @@ -7,5 +7,6 @@ executable site | ||||
|   main-is:          site.hs | ||||
|   build-depends:    base == 4.* | ||||
|                   , hakyll == 4.10.* | ||||
|                   , time | ||||
|   ghc-options:      -threaded | ||||
|   default-language: Haskell2010 | ||||
|   | ||||
							
								
								
									
										58
									
								
								site.hs
									
									
									
									
									
								
							
							
						
						
									
										58
									
								
								site.hs
									
									
									
									
									
								
							| @@ -2,6 +2,8 @@ | ||||
| {-# LANGUAGE OverloadedStrings #-} | ||||
| import           Data.Monoid (mappend) | ||||
| import           Hakyll | ||||
| import           Data.List (sortBy, sortOn) | ||||
| import           Data.Time (formatTime, defaultTimeLocale) | ||||
|  | ||||
|  | ||||
| -------------------------------------------------------------------------------- | ||||
| @@ -25,34 +27,38 @@ main = hakyll $ do | ||||
|             >>= loadAndApplyTemplate "templates/default.html" defaultContext | ||||
|             >>= relativizeUrls | ||||
|  | ||||
|     -- match "posts/*" $ do | ||||
|     --     route $ setExtension "html" | ||||
|     --     compile $ pandocCompiler | ||||
|     --         >>= loadAndApplyTemplate "templates/post.html"    postCtx | ||||
|     --         >>= loadAndApplyTemplate "templates/default.html" postCtx | ||||
|     --         >>= relativizeUrls | ||||
|     match "posts/guides/*" $ do | ||||
|       route $ setExtension "html" | ||||
|       compile $ pandocCompiler | ||||
|         >>= loadAndApplyTemplate "templates/post.html"    postCtx | ||||
|         >>= loadAndApplyTemplate "templates/default.html" postCtx | ||||
|         >>= relativizeUrls | ||||
|  | ||||
|     -- create ["archive.html"] $ do | ||||
|     --     route idRoute | ||||
|     --     compile $ do | ||||
|     --         posts <- recentFirst =<< loadAll "posts/*" | ||||
|     --         let archiveCtx = | ||||
|     --                 listField "posts" postCtx (return posts) `mappend` | ||||
|     --                 constField "title" "Archives"            `mappend` | ||||
|     --                 defaultContext | ||||
|     -- | ||||
|     --         makeItem "" | ||||
|     --             >>= loadAndApplyTemplate "templates/archive.html" archiveCtx | ||||
|     --             >>= loadAndApplyTemplate "templates/default.html" archiveCtx | ||||
|     --             >>= relativizeUrls | ||||
|     match "posts/brainstorming/*" $ do | ||||
|       route $ setExtension "html" | ||||
|       compile $ pandocCompiler | ||||
|         >>= loadAndApplyTemplate "templates/post.html"    postCtx | ||||
|         >>= loadAndApplyTemplate "templates/default.html" postCtx | ||||
|         >>= relativizeUrls | ||||
|  | ||||
|     create ["guides.html"] $ do | ||||
|         route idRoute | ||||
|         compile $ do | ||||
|             posts <- modFirst =<< loadAll "posts/guides/*" | ||||
|             let archiveCtx = | ||||
|                     listField "posts" postCtx (return posts) `mappend` | ||||
|                     constField "title" "Guides"            `mappend` | ||||
|                     defaultContext | ||||
|  | ||||
|             makeItem "" | ||||
|                 >>= loadAndApplyTemplate "templates/guides.html" archiveCtx | ||||
|                 >>= loadAndApplyTemplate "templates/default.html" archiveCtx | ||||
|                 >>= relativizeUrls | ||||
|  | ||||
|     match "index.html" $ do | ||||
|         route idRoute | ||||
|         compile $ do | ||||
|             posts <- recentFirst =<< loadAll "posts/*" | ||||
|             let indexCtx = | ||||
|                     listField "posts" postCtx (return posts) `mappend` | ||||
|                     constField "title" "Home"                `mappend` | ||||
|                     defaultContext | ||||
|  | ||||
| @@ -63,9 +69,19 @@ main = hakyll $ do | ||||
|  | ||||
|     match "templates/*" $ compile templateBodyCompiler | ||||
|  | ||||
| modFirst :: [Item a] -> Compiler [Item a] | ||||
| modFirst = fmap reverse . modified | ||||
|   where | ||||
|     modified = sortByM (getItemModificationTime . itemIdentifier) | ||||
|     sortByM f xs = map fst . sortOn snd <$> mapM (\x -> (,) x <$> f x) xs | ||||
|  | ||||
| -------------------------------------------------------------------------------- | ||||
| postCtx :: Context String | ||||
| postCtx = | ||||
|     dateField "date" "%B %e, %Y" `mappend` | ||||
|     modifiedField "modified" "%B %e, %Y" `mappend` | ||||
|     defaultContext | ||||
|   where | ||||
|     modifiedField key format = field key $ \i -> do | ||||
|       time <- getItemModificationTime $ itemIdentifier i | ||||
|       return $ formatTime defaultTimeLocale format time | ||||
|   | ||||
| @@ -1,2 +0,0 @@ | ||||
| Here you can find all my previous posts: | ||||
| $partial("templates/post-list.html")$ | ||||
| @@ -14,6 +14,7 @@ | ||||
|             </div> | ||||
|             <nav> | ||||
|                 <a href="/">Home</a> | ||||
|                 <a href="/guides.html">Guides</a> | ||||
|                 <a href="/about.html">About</a> | ||||
|                 <a href="/contact.html">Contact</a> | ||||
|             </nav> | ||||
|   | ||||
							
								
								
									
										3
									
								
								templates/guides.html
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										3
									
								
								templates/guides.html
									
									
									
									
									
										Normal file
									
								
							| @@ -0,0 +1,3 @@ | ||||
| A list of small and big guides. | ||||
|  | ||||
| $partial("templates/post-list.html")$ | ||||
| @@ -1,6 +1,6 @@ | ||||
| <article> | ||||
|     <section class="header"> | ||||
|         Posted on $date$ | ||||
|         Posted on $date$, modified on $modified$ | ||||
|         $if(author)$ | ||||
|             by $author$ | ||||
|         $endif$ | ||||
|   | ||||
		Reference in New Issue
	
	Block a user