Static website from org-roam : Hakyll or other generator

Hi,
I am just getting into org-roam and would be interested to know how to generate a static website with Hakyll.
The main issue is that links between nodes uses ID instead of filename so link in the generated HTML do not work out of the box.

Did someone managed to make it work with Hakyll ? I think it could be doable by reading org-roam database.

Otherwise, I’m open to other suggestions. Ox-hugo has been suggested elsewhere but I don’t like the idea to switch to another format.

Thanks,

I do not know how Hakyll works, but wondered if you had a look at org-roam-publish extension.

I think this would let you publish html files with the built-in org-export — not sure how Hakyll can be used in the process, though. Just an idea.

Thanks, I was not aware of this extension.

Hakyll is basically a wrapper around pandoc to generate a blog. After posting, I found this tutorial to correct org-roam link with pandoc : Publishing org-roam notes with pandoc.

Update: I managed to write a filter for pandoc to replace internal links to link to the actual file.
Note: for publishing, the final path are prefixed with “/”. Here is the code:

#!/usr/bin/env runhaskell
{-# LANGUAGE TemplateHaskell            #-}
{-# LANGUAGE QuasiQuotes                #-}
{-# LANGUAGE TypeFamilies               #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE GADTs                      #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RecordWildCards            #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE DerivingStrategies         #-}
{-# LANGUAGE StandaloneDeriving         #-}
{-# LANGUAGE UndecidableInstances       #-}
{-# LANGUAGE DataKinds #-}

import qualified Database.Persist.TH as PTH
import Database.Persist (Entity(..))
import Database.Persist.Sql (toSqlKey)
import qualified Data.Text as T
import Database.Persist.Sqlite
import Control.Monad.IO.Class
import Control.Monad.Logger
import Text.Pandoc.JSON
import System.FilePath (addExtension, dropExtension, makeRelative)
import System.Directory (getCurrentDirectory)

PTH.share [PTH.mkPersist PTH.sqlSettings, PTH.mkMigrate "migrateAll"] [PTH.persistLowerCase|
  Node sql=nodes
    Id T.Text sql=id
    file T.Text
    title T.Text
    deriving Show
|]

path =  "/home/alex/.emacs.d/.local/cache/org-roam.db"

unescape :: T.Text -> T.Text
unescape = T.replace "\"" ""

-- From "id:XXXX" search in org-roam database for path to file
-- If there is no id, just return the string unchanged
pathFromID :: T.Text -> IO (T.Text)
pathFromID id = runSqlite path $ do
    -- Get id and add (escaped) quote
    let s = T.concat ["\"", last (T.splitOn "id:" id), "\""]
    test <- get (NodeKey s)
    let res = case test of
                Just x -> unescape . nodeFile $ x
                Nothing -> id
    return res

-- Change link to HTML version for publishing it
-- Link is transformed from absolute to relative
-- And we add the root folder for publishing
-- FIXME this will not work locally...
htmlLink :: FilePath -> FilePath -> FilePath
htmlLink f pwd = "/" ++ makeRelative pwd (addExtension (dropExtension f) ".html")

-- Replace org-mode internal link to link to the full path of the file
replaceLink :: Inline -> IO (Inline)
replaceLink (Link attr xs t) = do
  p <- pathFromID (fst t)
  pwd <- getCurrentDirectory
  let p' = htmlLink (T.unpack p) pwd
  return $ Link attr xs (T.pack p', snd t)
replaceLink x = return x


main :: IO ()
main = toJSONFilter replaceLink

With chmod +x filterOrgRoam.hs, you should be able to test it. For example:
pandoc test.org -t native --filter ./filterOrgRoam

For publishing, you can use Shakefile (an Haskell alternative to Makefile, or Makefile iteslf). Here’s how I do it. In Shakefile.hs, place


import Development.Shake
import Development.Shake.Command
import Development.Shake.FilePath
import Development.Shake.Util

filterExe = "_build/filterOrgRoam"


main :: IO ()
main = shakeArgs shakeOptions{shakeFiles="_build"} $ do
    want ["_build/notes/index.html"]

    "_build/notes/index.html" %> \out -> do
        let src = "notes/index.org"
        -- Only org roam notes (starting with the date)
        org <- getDirectoryFiles "" ["notes/2*.org"]
        let html = ["_build" </> n -<.> "html" | n <- org]
        need $ html ++ [filterExe]
        cmd "pandoc" src "--filter " filterExe "-s  --css /css/default.css -o" [out]

    "_site/notes/*.html" %> \out -> do
        let org = dropDirectory1 $ out -<.> "org"
        cmd "pandoc" [org] "--filter " filterExe "-s --css /css/default.css -o" [out]

    filterExe  %> \out -> do
      cmd_ "ghc --make -o" [out] ["src/filterOrgRoam.hs"]

Then in build.sh

#!/bin/sh
mkdir -p _shake
ghc --make Shakefile.hs -rtsopts -threaded -with-rtsopts=-I0 -outputdir=_shake -o _shake/build && _shake/build "$@"

Finally, run bash build.sh. Output files will be in _build, ready to be uploaded.