DEV Community

Cover image for Responsive and sustainable images in markdown (commonmark) using haskell MMark
Injeniero
Injeniero

Posted on • Edited on

Responsive and sustainable images in markdown (commonmark) using haskell MMark

NOTE:

For full article please read https://injeniero.com/en/blog/responsive-sustainable-images-markdown-commonmark-haskell-mmark

Introduction

MMark, created by Mark Karpov, is a great haskell library that uses Commonmark specification to transform Markdown into HTML and is based on the following philosophy:

  1. Strict, explicitly specifying where parsing errors occur and what they are about.

  2. Extensible, where the user can compose extensions that add functionality.

Since it's extensible, it's pretty easy to create useful extensions that can enrich your workflow from Markdown to a website.

Web sustainability is something that is often overlooked by programmers, however, given the non-negligible CO2 emissions of the internet, it is worth mentioning.

Here I post an example of an extension to produce responsive and sustainable images in Markdown.

Feel free to improve on it, and more importantly, consider producing sustainable images in your projects.

Cheers,
Injeniero

Requirements

  1. Some familiarity with the Haskell language
  2. Have GHC and cabal installed

Code

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}

module Main where

import qualified Data.Text.IO      as T
import qualified Data.Text.Lazy.IO as TL
import qualified Text.MMark        as MMark
import qualified Text.Megaparsec   as M
import qualified Text.MMark.Extension as Ex
import qualified Data.Text as Te
import qualified Text.URI as URI
import qualified System.FilePath as FP
import qualified Data.ByteString.Lazy as B
import GHC.Generics
import Lucid.Base (makeAttribute)
import Lucid
import Data.Maybe (fromMaybe)
import Text.URI.Lens (uriPath)
import Lens.Micro ((^.))
import Data.Aeson (ToJSON, FromJSON, decode)
import System.Environment ( getArgs )

-- Define Config data structure
data Config = Config
  { confSizes :: String
  , confSet   :: [Int]
  } deriving (Show, Generic, Eq)

defaultConfig :: Config
defaultConfig = Config {confSizes = "(max-width:600px) 100vw, 850px", confSet = [400,850]}

-- Parsing the Config data
instance FromJSON Config
instance ToJSON Config

-- Function to read the config file
readConfig :: FilePath -> IO (Maybe Config)
readConfig path = do
  jsonData <- B.readFile path
  return (decode jsonData :: Maybe Config)

main :: IO ()
main = do
  args <- getArgs
  let input = head args
  txt <- T.readFile input
  config <- readConfig "config.json"
  let conf = case config of
              Just c -> c
              Nothing -> defaultConfig
  let sizes = confSizes conf
  let set = confSet conf
  case MMark.parse input txt of
    Left bundle -> putStrLn (M.errorBundlePretty bundle)
    Right r -> TL.writeFile (FP.takeBaseName input ++ ".html")
      . renderText -- from Lucid
      . MMark.render
      . MMark.useExtensions
             [ imgLazyExt
             , imgResExt' set sizes
             , audioExt
             ]
      $ r

-- Common function to extract base URL components
extractImageAttributes :: URI.URI -> (String, String, String)
extractImageAttributes url =
  let url' = clearStr $ show $ URI.render url
      file = FP.takeBaseName url'
      ext  = FP.takeExtension url'
      path = FP.takeDirectory url'
  in (file, ext, path)


--EXTENSIONS
-- Adding lazy attribute to images composable
imgLazyExt :: MMark.Extension
imgLazyExt = Ex.inlineRender $ \old inline ->
  case inline of
    l@(Ex.Image txt url (Just attr)) -> fromMaybe (old l) $ do
      let wo = words $ Te.unpack attr
      let mattr = if Te.null attr then Nothing else Just attr
      if "lazy" `elem` wo
        then return $ with (old (Ex.Image txt url mattr)) [loading_ "lazy"]
        else return $ old (Ex.Image txt url mattr)
    other -> old other

-- Adding srcset and sizes attributes to images composable
imgResExt :: [Int] -> String -> MMark.Extension
imgResExt set sizes = Ex.inlineRender $ \old inline ->
  case inline of
    l@(Ex.Image txt url (Just attr)) -> fromMaybe (old l) $ do
      let (file, ext, path) = extractImageAttributes url
      let mattr = if Te.null attr then Nothing else Just attr
      return $ with (old (Ex.Image txt url mattr))
                    [ srcset_ (imgSet file ext path set)
                    , sizes_ (Te.pack sizes)]
    other -> old other
-- Extension for images without title attribute but adding srcset and sizes attributes
imgResExt' :: [Int] -> String -> MMark.Extension
imgResExt' set sizes= Ex.inlineRender $ \old inline ->
  case inline of
    l@(Ex.Image txt url _) -> fromMaybe (old l) $ do
      let (file, ext, path) = extractImageAttributes url
      let src' = URI.render url
      return $ img_ [ alt_ (Ex.asPlainText txt)
                    , src_ src'
                    , srcset_ (imgSet file ext path set)
                    , sizes_ (Te.pack sizes)]
    other -> old other

-- imgSet function
imgSet :: String -> String -> String -> [Int] -> Te.Text
imgSet filebase ext path set = Te.pack $ concatMap formatSize (init set) ++ formatSize (last set)
  where
    comma size =  if size /= last set then "," else ""
    formatSize size = path ++ "/" ++ filebase ++ "_" ++ show size ++ ext ++  " " ++ show size ++ "w" ++ comma size

-- Helper function to create srcset attribute
srcset_ :: Te.Text -> Attribute
srcset_ = makeAttribute "srcset"

-- Clear quotes from string
clearStr :: String -> String
clearStr = filter (not . (`elem` ("\"" :: String)))

-- Bonus: Audio extension to render audio links
audioExt :: MMark.Extension
audioExt = Ex.inlineRender $ \old inline ->
  case inline of
    l@(Ex.Link txt uri _) ->
      case (uri ^. uriPath, Ex.asPlainText txt) of
        ([], _) -> old l
        (_, "audio") ->
          audio_ [controls_ "controls", preload_ "none"] $
               source_ [src_ (URI.render uri), type_ "audio/mp4"]
        (_, _) -> old l
    other -> old other
Enter fullscreen mode Exit fullscreen mode

Use

  1. Create a directory & cd to the directory
  2. Run ‘cabal init’ command in the terminal within the directory
  3. Create a markdown file, example.md or any name and add some images
  4. Copy the sourcecode to the Main.hs file in the /app folder replacing the one created by cabal init Add the dependencies in the.cabal file, line build-depends:

project.cabal

build-depends: base ^>=4.21.0.0, text>=2.1.2, mmark >= 0.0.8.0, megaparsec >= 9.7.0, modern-uri >= 0.3.6.1, filepath >= 1.5.4.0, microlens >= 0.4.14.0, lucid >= 2.11.20250303, aeson >= 2.2.3.0, bytestring >= 0.12.2.0

  1. Run cabal update && cabal build
  2. Run cabal run exes -- yourfile.md
  3. See the yourfile.html file with the resulting HTML

Full code also available on github https://github.com/injeniero-com/injeniero

Injeniera from injeniero.com/en/

Cheers,
Injeniero https://injeniero.com
Best sustainable web development agency

Top comments (0)