Data Context

111 views
Skip to first unread message

danem...@gmail.com

unread,
Feb 1, 2015, 9:50:46 AM2/1/15
to hak...@googlegroups.com
Hi, I recently tried asking this question on the IRC channel, but was unable to get a reply, so sorry if this is a rather basic question.

I have a collection of JSON files that each describe a page. I'd like to be able to parse each file, and expose its fields to a template that will handle rendering them. I think I have an incorrect mental model of how the rendering happens, as the Context creation is a bit counter intuitive to me. Here is very rough example that demonstrates my general approach.

import Data.Aeson

data Foo = Foo { foo :: Int
               
, bar :: [Int]
               
, qux :: Bool
               
}
               
deriving Show

fooCtx (Foo{..}) = constField "foo" (show foo)
               
<> constField "qux" (show qux)
               
-- How would I include bar?

main = hakyllWith config $ do
   
match "data/*.json" $ do
       
route $ setExtension "html"
       
compile $ do
           
res <- getResourceLBS
           
dat <- withItemBody (pure . decode) res :: Compiler (Item (Maybe Foo))
           
-- Need to somehow create the correct Context here...

It seems to me that constructing a context this way is incorrect, but I can't see how else you'd go about it.

Thanks a lot

Jasper Van der Jeugt

unread,
Feb 14, 2015, 9:03:36 AM2/14/15
to hak...@googlegroups.com
Hey,

It should be possible to use something like this:

{-# LANGUAGE RecordWildCards #-}
import Hakyll
import Data.Monoid

data Foo = Foo { foo :: Int
, bar :: [Int]
, qux :: Bool
}
deriving Show

fooCtx :: Context Foo
fooCtx =
field "foo" (return . show . foo . itemBody) <>
field "qux" (return . show . qux . itemBody) <>
listFieldWith "bar" intCtx (\i -> mapM makeItem (bar $ itemBody i))

intCtx :: Context Int
intCtx = field "val" (\i -> return $ show $ itemBody i)

The idea is that you won't parse your `Foo` to the context function
directly, but rather use `field` to access it.

As for `bar`, we want to use `listField`/`listFieldWith`, which in turn
requires another context. In your template you will have something like:

$for(bar)$
Value: $val$
$endfor$

The `fooCtx` is used at the top-level, and inside of the `for` loop we
are using the `intCtx`.

Hope this helps,
Peace,
Jasper
> --
> You received this message because you are subscribed to the Google Groups "hakyll" group.
> To unsubscribe from this group and stop receiving emails from it, send an email to hakyll+un...@googlegroups.com.
> For more options, visit https://groups.google.com/d/optout.

Paul

unread,
Jul 5, 2020, 8:09:09 AM7/5/20
to hakyll
Hello,
I also want to generate html files from json (a feature which surprisingly few static site generators support), so I expanded your stub above into a working example (code below). I have a few questions though:

Is there a more elegant and general way to generate the Contexts (and maybe even the data types)? Fortunately my json files are not that complicated, but the current approach feels clumsy and tedious and is not really scalable.

I think using non-String Contexts might have some drawbacks, eg. when chaining templates, my journalCtx can only be used once (and must be the first one). So I guess using Context String might be better, but I don't know how to do that (and how to inject the real data into the context if I'm using a makeItem ""). Any ideas?

thanks in advance
paul

-- journal.json
{ "issue": "1/2020"
, "year" : 2020
, "content":
  [ {"title": "Editorial", "author":"me", "page":2}
  , {"title": "Hakyll Tutorial", "author": "Jasper", "page":4}
  ]
}

-- templates/journal.html
<h1>$title$</h1>
Issue $issue$
<ul>                                                                           
 $for(content)$                                                                 
 <li>Title=$title$ from $author$ (Page $page$)</li>
 $endfor$
</ul>

-- site.hs
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
import Hakyll
import Data.Aeson
import GHC.Generics
import qualified Data.ByteString.Lazy as B
import Data.Maybe

main :: IO ()
main = do
  hakyll $ do
    match "templates/*" $ compile templateBodyCompiler

    match "journal.json" $ do

      route $ setExtension "html"
      compile $ do
        res <- getResourceLBS
        d <- withItemBody (pure . decode) res :: Compiler (Item (Maybe Journal))
        let h = fromJust (itemBody d)
        makeItem h
          >>= loadAndApplyTemplate "templates/journal.html" journalCtx
          >>= loadAndApplyTemplate "templates/default.html" defaultContext
          >>= relativizeUrls

data Journal =
  Journal { issue :: String
          , year :: Int
          , pages :: Int
          , content :: [Article]
          } deriving (Show,Generic,FromJSON,ToJSON)

data Article =
  Article { title :: String
          , author :: String
          , page :: Int
          } deriving (Show,Generic,FromJSON,ToJSON)

articleCtx :: Context Article
articleCtx =
  field "title" (return . title . itemBody)
  <> field "author" (return . author . itemBody)
  <> field "page" (return . show . page . itemBody)

journalCtx :: Context Journal
journalCtx =
  field "issue" (return . issue . itemBody)
  <> field "year" (return . show . year . itemBody)
  <> field "pages" (return . show . pages . itemBody)
  <> listFieldWith "content" articleCtx (return . (\ j ->
      sequence $ Item "article" (content $ itemBody j)))
  <> titleField "title"

pl.gr...@gmail.com

unread,
Jul 9, 2020, 3:57:14 AM7/9/20
to hakyll
Hello,
I've got the same problem, so I expanded your stub above into a working example (code below). Since I'm a novice at both Hakyll and Haskell, I'm looking for any kind of feedback.

Is there a more elegant way to generate the contexts (and possibly even infer the data types from the JSON)? The JSON files I expect are not that complicated, so I'm ok with writing both data types and contexts manually, but this is not really scalable.

Also I think there may be drawbacks using non-String Contexts: when chaining templates, I can only use my journalCtx once (and it has to be first in the chain). So I guess it would maybe be better to switch to String Contexts, but I can't quite figure out how to do that? I think I would  then have to makeItem "" and inject the json data directly into the context – but how?

thanks in advance
paul

-- journal.json
{ "issue": "1/2020"
, "year" : 2020
, "pages": 24

, "content":
  [ {"title": "Editorial", "author":"me", "page":2}
  , {"title": "Everything about Hakyll", "author": "Jasper", "page":4}

  ]
}

-- templates/journal.html
<h1>$title$</h1>
Issue $issue$
<ul>
$for(content)$
  <li>Title=$title$ from $author$ (Page $page$)</li>
$endfor$

-- main.hs
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
import Hakyll
import Data.Aeson
import GHC.Generics
import qualified Data.ByteString.Lazy as B
import Data.Maybe

data Journal =
   Journal { issue :: String
           , year :: Int
           , pages :: Int
           , content :: [Article]
           } deriving (Show,Generic,FromJSON,ToJSON)
data Article =
  Article { title :: String
          , author :: String
          , page :: Int
          } deriving (Show,Generic,FromJSON,ToJSON)

articleCtx :: Context Article
articleCtx =
  field "title" (return . title . itemBody)
  <> field "author" (return . author . itemBody)
  <> field "page" (return . show . page . itemBody)

journalCtx :: Context Journal
journalCtx =
  field "issue" (return . issue . itemBody)
  <> field "year" (return . show . year . itemBody)
  <> field "pages" (return . show . pages . itemBody)
  <> listFieldWith "content" articleCtx (return . (\ j ->
    sequence $ Item "article" (content $ itemBody j)))
  <> titleField "title"

main :: IO ()
main = do
  hakyll $ do
    match "templates/*" $ compile templateBodyCompiler

    match "journal.json" $ do

      route $ setExtension "html"
      compile $ do
        res <- getResourceLBS
Reply all
Reply to author
Forward
0 new messages