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

In this article we show a possible solution to create responsive and sustainable images in Markdown (CommonMark specification) using the MMark library in the Haskell functional language.
NOTE: This article assumes concepts of sustainability and image responsiveness in Markdown. For an introduction to these concepts, read responsive and sustainable images in Markdown
Shortcut for those who want to see full sample code immediately
Introduction
MMark Library, created by Mark Karpov, is a library of the Haskell functional language that uses Commonmark specification to transform Markdown into HTML and is based on the following philosophy:
- Strict, explicitly specifying where parsing errors occur and what they are about.
- Extensible, where the user can compose extensions that add functionality.
If we try to render the following markdown:
MARKDOWN
35 bla bla
36 [](/thisproducesanerror)
The following error is displayed:
error parsing--> content.md:36:2: | 36 | [](/thisproducesanerror) | ^ unexpected ']' expecting inline content
Explaining that a value is required and indicates on which line of the file (36).
Requirements
- Have GHC and cabal installed
- Import the following libraries
{-# 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 )
Principles of this solution
MMark is very flexible and it is possible to create multiple solutions. For the same reason, we will use certain principles in the example solution.
Principle I
Align as much as possible with the Markdown philosophy, i.e. prefer solutions that are easy to write and read within the Markdown file.
For example, a markdown like this:
MARKDOWN

Produce a responsive and sustainable image like this:
HTML
<img alt="description" src="image.avif" width="600" height="600" srcset="image_600.avif 600w, image_856.avif 856w, image_1000.avif 1000w" sizes="(max-width:800px) 90vw, 856px">
Without any new syntax it is preferable.
Or with minimal intervention via “hacks” using attributes such as title
of an image and add HTML responsive and sustainable attributes such as:
MARKDOWN

Produce the following HTML:
HTML
<img alt="alt" src="image.avif" fetchprioroty="high">
Principle II
Ideally, maximize cross compatibility with reasonable trade-offs. At Injeniero one of the advantages we offer is 0 vendor lock-in where the customer can leave whenever they want. In this sense, the ideal is to produce Markdown that is compatible with other libraries/systems where, in case of modified syntax, they are displayed as usable links that do not break the page.
For example, to create an audio element, it is preferable something like this:
MARKDOWN
[audio](music.m4a)
over this:
MARKDOWN
<audio:music.m4a>
Where we only have to create an extension to transform such links elements into audio HTML elements.
Although the library allows us to create extensions to accept both syntaxes, when using the same file in other libraries (e.g cmark library which is also commonmark) respectively result in:
HTML
<p> <a src= "music.m4a"> audio </a> </p>
<p> <a href= "audio:music.m4a"> audio:music.m4a </a> </p>
Since this other library doesn’t have the extensions created then the transformation to an audio element will obviously fail and be rendered as links elements. However the first link works, with the trade-off that is not an audio element but a link to the file with an audio name. However, the second link collapses most browsers so is less preferable.
Moreover, using this principle II, taking advantage of existing attributes as a hack is better than a new syntax.
For example creating the following new syntax:
MARKDOWN
!audio(music.m4a)
It is rendered in other libraries, such as cmark:
MARKDOWN
<p> !audio(music.m4a) </p>
This means that the user would see a text instead of an audio if they used the same markdown file in another library which is worse than the previous example where a link to the file was available.
Obviously using MMark it is possible to create the audio element from a link, but is worth mentioning that cross compatibility is prefered when building the extensions.
For example, we could create an extension called audioExt:
HASKELL
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"] $ do
source_ [src_ (URI.render uri) , type_ "audio/mp4"]
(_,_) -> old l
other -> old other
That receiving the following markdown:
MARKDOWN
[audio](podcast.m4a)
Delivers the following HTML:
HTML
<audio controls="controls" preload="none"><source src="podcast.m4a" type="audio/mp4"></audio>
With the aforementioned advantage that it is a little more compatible with other libraries because its syntax falls back to an usable link.
Which syntax is preferable to use?
It will depend on the use case. However, for the solution implemented in this article we will use the principles mentioned. You may think that using the title
attribute of an image is not a good pattern. However, this attribute is very little used in reality. It is only visible on devices with a pointer (e.g desktop) and is not used as an accessibility element. In turn, its impact on SEO is negligible. Therefore, removing this attribute from the final HTML is a very reasonable trade-off. MMark allows you to transform inline elements such as <img>
in a composable way, so you don’t need to remove this attribute until at the end, being able to use it to define other attributes.
For example, we can create an extension that allows us to add the HTML attribute loading="lazy"
:
HASKELL
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
case "lazy" `elem` wo of
True -> return $ with (old (Ex.Image txt url mattr)) [loading_ "lazy"]
False -> return $ with (old (Ex.Image txt url mattr)) []
other -> old other
So then by writing:
MARKDOWN

We get:
HTML
<img src="image.png" alt="alt" loading="lazy" title="lazy">
Note that the title
attribute with lazy value is maintained. This is because with (old (Ex.Image txt url mattr))
“drags” all attributes allowing to compose the extensions. However, you can remove the title
attribute in the case of having a lazy value, keeping it only if it is another value (a true image title value, for example) by modifying that line:
HASKELL
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
let src' = URI.render url
let alt' = Ex.asPlainText txt
case "lazy" `elem` wo of
-- modified line:
True -> return $ img_ [alt_ alt', src_ src', loading_ "lazy"]
False -> return $ with (old (Ex.Image txt url mattr)) []
other -> old other
Getting HTML without title:
HTML
<img src="image.png" alt="alt" loading="lazy">
Also note that it is necessary to recreate the alt
attribute because we do not “drag” this attribute but its value (variable txt
). Ditto with original src
. An attentive reader will perceive that the above solution works, however, if this markdown is processed by another commonmark library, the title
attribute will necessarily appear with a lazy value. This is a trade-off that we consider reasonable, as it is easily correctable with Javascript by removing title
attribute from images and obviously only an issue if we change the library.
For companies like us, where we are dedicated to building websites and systems, it makes sense to create composable extensions of responsive and sustainable attributes that allows more granular control, such as:
-
loading="lazy"
that allows you to avoid requests for images that require scrolling to be seen (under the fold) -
fetchpriority="high/low"
that allows prioritizing critical file requests -
srcset
andsizes
which provides image alternatives and information on image width and how the images will be displayed to the browser, allowing you to optimize bandwidth and/or improve user experience.
However, authors and bloggers with simple sites may prefer a simpler solution, where you don’t need to think about how to optimize the images, but rather they are optimized by default.
Of the four responsive and sustainable attributes for images, both loading=lazy
and fetchprioroty
necessarily require thought to optimize the site. For example, loading="lazy"
is an anti-pattern for critical images, and should be used for images below the visible area on initial load, so it’s a bad idea to add it by default. Idem with fecthpriority
that should be used on a case-by-case basis as it makes sense. So either you accept this fact and create extensions in the spirit of those mentioned, or ignore it in the Markdown layer.
However, the attributes of srcset
and sizes
are good candidates for a simple solution 1.
For example, let’s consider a typical case of a blog where images are displayed at full width on mobile and the content of the page does not exceed a specific width on desktop, making the desktop image equal to that width (imagine content centered with a lot of margin on both sides on a wide monitor). A simple sizes
rule could be sizes = (max-width:600px) 100vw, 850px
which says that up to a screen width of 600px the image is displayed at 100% of the device’s width, and when the screen is larger, it is displayed at 850px. In turn, you could define two types of files: mobile and desktop, 400px and 850px for example. With this you could define srcset
attribute as srcset= image-small.avif 400w, image-big.avif 850w
. Finally, let’s assume that we will have an image naming convention where the width of the file will be in the name. For example, ‘image-small.avif’ would be renamed to imagen_400.avif
While this typical case example is not an ultra-optimized site, it is a big gain to display the 400px vs. 850px image every time it is viewed on screens smaller than 600px, along with allowing the browser to display the larger image if it made sense (device with high pixel density and fast internet speed).
So let’s create such an extension:
HASKELL
imgResExt :: MMark.Extension
imgResExt = Ex.inlineRender $ \old inline ->
case inline of
l@(Ex.Image txt url _) -> fromMaybe (old l) $ do
let url' = clear_str $ show $ URI.render url
let file = FP.takeBaseName url'
let ext = FP.takeExtension url'
let path = FP.takeDirectory url'
let src' = URI.render url
return $ img_ [alt_ (Ex.asPlainText txt),src_ src', srcset_ (imgSet file ext path), sizes_ defSizes]
other -> old other
--defining sizes value
defSizes :: Te.Text
defSizes = Te.pack $ "(max-width:600px) 100vw, 850px"
--example of srcset
imgSet :: String -> String -> String -> Te.Text
imgSet filebase ext path = Te.pack $ (path ++ "/" ++ filebase ++ "_400" ++ ext ++ " 400w,"
++ path ++ "/" ++ filebase ++ "_850" ++ ext ++ " 850w")
-- The @srcset@ attribute
-- Lucid provide makeAttribute that allow us to create a new attribute
srcset_ :: Te.Text -> Attribute
srcset_ val = makeAttribute "srcset" val
--clear "" from show
clear_str :: String -> String
clear_str xs = filter (not . (`elem` ("\""::String))) xs
Then the following markdown:
MARKDOWN

Produces the HTML:
HTML
<img src="image.avif" alt="alt" srcset="image_400.avif 400w, image_850.avif 850w" sizes="(max-width:600px) 100vw, 850px">
It is important to emphasize that this is only an example and that it can be improved. In fact, for production use, the values of sizes and srcset could be in a configuration file and/or in yaml within the markdown along with parameterizing these functions. At the same time, to have defined a process of transformation of the images and their naming convention. On the other hand, it might be interesting to add a query string with a random value to the ‘src’ attribute to allow caching busting 2. In addition, it is advisable to add the width
and height
attributes of <img>
element, because they are used to define the initial load of the site. This could be done via an extension similar to those mentioned for lazy
that allow you to explicitly define the dimensions using the title
attribute like 
. Also it could be added automatically, for example using the JucyPixels library, or it could be added from the pathfile or file name if any naming convention is respected.
HASKELL
import Codec.Picture --remember to add JuicyPixels >= 3.3.9 to the cabal file
-- read the image from path
readImage :: FilePath -> IO (Either String DynamicImage)
-- get image's width
dynWidth :: DynamicImage -> Int
dynWidth img = dynamicMap imageWidth img
It is up to the reader to improve the examples provided and adjust them to the specific requirements of the organization that will create and maintain the markdown and subsequent HTML. Or you can simply write to us to discuss a solution for your business.
As example we added a config file that amkes easy to edit the values of sizes
and srcset
.
Sourcecode
Main.hs
{-# 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
Use
- Create a directory & cd to the directory
- Run ‘cabal init’ command in the terminal within the directory
- Create a markdown file, example.md or any name and add some images
- 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
-
Run
cabal update && cabal build
-
Run
cabal run exes -- yourfile.md
-
See the
yourfile.html
file with the resulting HTML
Conclusion
While MarkDown seems limited when it comes to creating responsive and sustainable images, extensible and strict libraries such as MMark allow you to transform the final HTML by being able to add attributes to the images automatically or manually if you want more control over the publication, along with providing useful syntax errors.
At Injeniero we follow the aforementioned principles of 0 vendor lock-in and we align with Markdown’s spirit of ease of reading and writing by default. However, we can also develop the syntax that makes the most sense for your organization.