layoutz: Simple, beautiful CLI output for Haskell

[ apache, library, text ] [ Propose Tags ] [ Report a vulnerability ]

Build declarative and composable sections, trees, tables, dashboards, and interactive Elm-style TUI's. . Zero dependencies, rich text formatting with alignment, underlines, padding, margins. Features lists, trees, tables, charts, spinners, ANSI colors, and a built-in TUI runtime.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.1.1.0, 0.2.0.0
Dependencies base (>=4.7 && <5) [details]
License Apache-2.0
Copyright 2025 Matthieu Court
Author Matthieu Court
Maintainer matthieu.court@protonmail.com
Category Text
Home page https://github.com/mattlianje/layoutz
Bug tracker https://github.com/mattlianje/layoutz/issues
Source repo head: git clone https://github.com/mattlianje/layoutz(hs)
Uploaded by mattlianje at 2025-11-26T22:20:12Z
Distributions NixOS:0.1.0.0
Downloads 11 total (7 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2025-11-26 [all 1 reports]

Readme for layoutz-0.2.0.0

[back to package description]

layoutz

Simple, beautiful CLI output for Haskell ๐Ÿชถ

Build declarative and composable sections, trees, tables, dashboards, and interactive Elm-style TUI's.

Part of d4 โ€ข Also in: JavaScript, Scala

Features

  • Zero dependencies, use Layoutz.hs like a header file
  • Rich text formatting: alignment, underlines, padding, margins
  • Lists, trees, tables, charts, spinners...
  • ANSI colors and wide character support
  • Easily create new primitives (no component-library limitations)
  • LayoutzApp for Elm-style TUI's


TaskListDemo.hs โ€ข SimpleGame.hs

Table of Contents

Installation

Add Layoutz on Hackage to your project's .cabal file:

build-depends: layoutz

All you need:

import Layoutz

Quickstart

(1/2) Static rendering - Beautiful, compositional strings:

import Layoutz

demo = layout
  [ center $ row 
      [ withStyle StyleBold $ text "Layoutz"
      , withColor ColorCyan $ underline' "ห†" $ text "DEMO"
      ]
  , br
  , row
    [ statusCard "Users" "1.2K"
    , withBorder BorderDouble $ statusCard "API" "UP"
    , withColor ColorRed $ withBorder BorderThick $ statusCard "CPU" "23%"
    , withStyle StyleReverse $ withBorder BorderRound $ table ["Name", "Role", "Skills"] 
	[ ["Gegard", "Pugilist", ul ["Armenian", ul ["bad", ul["man"]]]]
        , ["Eve", "QA", "Testing"]
        ]
    ]
  ]

putStrLn $ render demo

(2/2) Interactive apps - Build Elm-style TUI's:

import Layoutz

data Msg = Inc | Dec

counterApp :: LayoutzApp Int Msg
counterApp = LayoutzApp
  { appInit = (0, None)
  , appUpdate = \msg count -> case msg of
      Inc -> (count + 1, None)
      Dec -> (count - 1, None)
  , appSubscriptions = \_ -> onKeyPress $ \key -> case key of
      CharKey '+' -> Just Inc
      CharKey '-' -> Just Dec
      _           -> Nothing
  , appView = \count -> layout
      [ section "Counter" [text $ "Count: " <> show count]
      , ul ["Press '+' or '-'", "ESC to quit"]
      ]
  }

main = runApp counterApp

Why layoutz?

  • We have printf and full-blown TUI libraries - but there's a gap in-between
  • layoutz is a tiny, declarative DSL for structured CLI output
  • On the side, it has a little Elm-style runtime + keyhandling DSL to animate your elements, much like a flipbook...
    • But you can just use Layoutz without any of the TUI stuff

Core concepts

  • Every piece of content is an Element
  • Elements are immutable and composable - build complex layouts by combining simple elements
  • A layout arranges elements vertically:
layout [elem1, elem2, elem3]  -- Joins with "\n"

Call render on any element to get a string

The power comes from uniform composition - since everything has the Element typeclass, everything can be combined.

String Literals

With OverloadedStrings enabled, you can use string literals directly:

layout ["Hello", "World"]  -- Instead of layout [text "Hello", text "World"]

Note: When passing to functions that take polymorphic Element a parameters (like underline', center', pad), use text explicitly:

underline' "=" $ text "Title"  -- Correct
underline' "=" "Title"         -- Ambiguous type error

Elements

Text

text "Simple text"
-- Or with OverloadedStrings:
"Simple text"
Simple text

Line Break

Add line breaks with br:

layout ["Line 1", br, "Line 2"]
Line 1

Line 2

Section: section

section "Config" [kv [("env", "prod")]]
section' "-" "Status" [kv [("health", "ok")]]
section'' "#" "Report" 5 [kv [("items", "42")]]
=== Config ===
env: prod

--- Status ---
health: ok

##### Report #####
items: 42

Layout (vertical): layout

layout ["First", "Second", "Third"]
First
Second
Third

Row (horizontal): row

Arrange elements side-by-side horizontally:

row ["Left", "Middle", "Right"]
Left Middle Right

Multi-line elements are aligned at the top:

row 
  [ layout ["Left", "Column"]
  , layout ["Middle", "Column"]
  , layout ["Right", "Column"]
  ]

Tight Row: tightRow

Like row, but with no spacing between elements (useful for gradients and progress bars):

tightRow [withColor ColorRed $ text "โ–ˆ", withColor ColorGreen $ text "โ–ˆ", withColor ColorBlue $ text "โ–ˆ"]
โ–ˆโ–ˆโ–ˆ

Text alignment: alignLeft, alignRight, alignCenter, justify

Align text within a specified width:

layout
  [ alignLeft 40 "Left aligned"
  , alignCenter 40 "Centered"
  , alignRight 40 "Right aligned"
  , justify 40 "This text is justified evenly"
  ]
Left aligned                            
               Centered                 
                           Right aligned
This  text  is  justified         evenly

Horizontal rule: hr

hr
hr' "~"
hr'' "-" 10
โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
----------

Vertical rule: vr

row [vr, vr' "โ•‘", vr'' "x" 5]
โ”‚ โ•‘ x
โ”‚ โ•‘ x
โ”‚ โ•‘ x
โ”‚ โ•‘ x
โ”‚ โ•‘ x
โ”‚ โ•‘
โ”‚ โ•‘
โ”‚ โ•‘
โ”‚ โ•‘
โ”‚ โ•‘

Key-value pairs: kv

kv [("name", "Alice"), ("role", "admin")]
name: Alice
role: admin

Table: table

Tables automatically handle alignment and borders:

table ["Name", "Age", "City"] 
  [ ["Alice", "30", "New York"]
  , ["Bob", "25", ""]
  , ["Charlie", "35", "London"]
  ]
โ”Œโ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”ฌโ”€โ”€โ”€โ”€โ”€โ”ฌโ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”
โ”‚ Name    โ”‚ Age โ”‚ City    โ”‚
โ”œโ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”ผโ”€โ”€โ”€โ”€โ”€โ”ผโ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”ค
โ”‚ Alice   โ”‚ 30  โ”‚ New Yorkโ”‚
โ”‚ Bob     โ”‚ 25  โ”‚         โ”‚
โ”‚ Charlie โ”‚ 35  โ”‚ London  โ”‚
โ””โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”ดโ”€โ”€โ”€โ”€โ”€โ”ดโ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”˜

Unordered Lists: ul

Clean unordered lists with automatic nesting:

ul ["Feature A", "Feature B", "Feature C"]
โ€ข Feature A
โ€ข Feature B
โ€ข Feature C

Nested lists with auto-styling:

ul [ "Backend"
   , ul ["API", "Database"]
   , "Frontend"
   , ul ["Components", ul ["Header", ul ["Footer"]]]
   ]
โ€ข Backend
  โ—ฆ API
  โ—ฆ Database
โ€ข Frontend
  โ—ฆ Components
    โ–ช Header
      โ€ข Footer

Ordered Lists: ol

Numbered lists with automatic nesting:

ol ["First step", "Second step", "Third step"]
1. First step
2. Second step
3. Third step

Nested ordered lists with automatic style cycling (numbers โ†’ letters โ†’ roman numerals):

ol [ "Setup"
   , ol ["Install dependencies", "Configure", ol ["Check version"]]
   , "Build"
   , "Deploy"
   ]
1. Setup
  a. Install dependencies
  b. Configure
    i. Check version
2. Build
3. Deploy

Underline: underline

Add underlines to any element:

underline "Important Title"
underline' "=" $ text "Custom"  -- Use text for custom underline char
Important Title
โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€

Custom
โ•โ•โ•โ•โ•โ•

Box: box

With title:

box "Summary" [kv [("total", "42")]]
โ”Œโ”€โ”€Summaryโ”€โ”€โ”€โ”
โ”‚ total: 42  โ”‚
โ””โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”˜

Without title:

box "" [kv [("total", "42")]]
โ”Œโ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”
โ”‚ total: 42  โ”‚
โ””โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”˜

Status card: statusCard

statusCard "CPU" "45%"
โ”Œโ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”
โ”‚ CPU   โ”‚
โ”‚ 45%   โ”‚
โ””โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”˜

Progress bar: inlineBar

inlineBar "Download" 0.75
Download [โ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ”€โ”€โ”€โ”€โ”€] 75%

Tree: tree

tree "Project" 
  [ branch "src" 
      [ leaf "main.hs"
      , leaf "test.hs"
      ]
  , branch "docs"
      [ leaf "README.md"
      ]
  ]
Project
โ”œโ”€โ”€ src
โ”‚   โ”œโ”€โ”€ main.hs
โ”‚   โ””โ”€โ”€ test.hs
โ””โ”€โ”€ docs
    โ””โ”€โ”€ README.md

Chart: chart

chart [("Web", 10), ("Mobile", 20), ("API", 15)]
Web    โ”‚โ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆ 10
Mobile โ”‚โ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆ 20
API    โ”‚โ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆโ–ˆ 15

Padding: pad

Add uniform padding around any element:

pad 2 $ text "content"
        
        
  content  
        
        

Spinners: spinner

Animated loading spinners for TUI apps:

spinner "Loading..." frameNum SpinnerDots
spinner "Processing" frameNum SpinnerLine
spinner "Working" frameNum SpinnerClock
spinner "Thinking" frameNum SpinnerBounce

Styles:

  • SpinnerDots - Braille dot spinner: โ ‹ โ ™ โ น โ ธ โ ผ โ ด โ ฆ โ ง โ ‡ โ 
  • SpinnerLine - Classic line spinner: | / - \
  • SpinnerClock - Clock face spinner: ๐Ÿ• ๐Ÿ•‘ ๐Ÿ•’ ...
  • SpinnerBounce - Bouncing dots: โ  โ ‚ โ „ โ ‚

Increment the frame number on each render to animate:

-- In your app state, track a frame counter
data AppState = AppState { spinnerFrame :: Int, ... }

-- In your view function
spinner "Loading" (spinnerFrame state) SpinnerDots

-- In your update function (triggered by a tick or key press)
state { spinnerFrame = spinnerFrame state + 1 }

With colors:

withColor ColorGreen $ spinner "Success!" frame SpinnerDots
withColor ColorYellow $ spinner "Warning" frame SpinnerLine

Centering: center

Smart auto-centering and manual width:

center "Auto-centered"     -- Uses layout context
center' 20 "Manual width"  -- Fixed width
        Auto-centered        

    Manual width    

Margin: margin

Add prefix margins to elements for compiler-style error messages:

margin "[error]"
  [ text "Ooops"
  , text ""
  , row [ text "result :: Int = "
        , underline' "^" $ text "getString"
        ]
  , text "Expected Int, found String"
  ]
[error] Ooops
[error]
[error] result :: Int =  getString
[error]                  ^^^^^^^^^
[error] Expected Int, found String

Border Styles

Elements like box, table, and statusCard support different border styles:

BorderNormal (default):

box "Title" ["content"]
โ”Œโ”€โ”€Titleโ”€โ”€โ”
โ”‚ content โ”‚
โ””โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”˜

BorderDouble:

withBorder BorderDouble $ statusCard "API" "UP"
โ•”โ•โ•โ•โ•โ•โ•โ•โ•—
โ•‘ API   โ•‘
โ•‘ UP    โ•‘
โ•šโ•โ•โ•โ•โ•โ•โ•โ•

BorderThick:

withBorder BorderThick $ table ["Name"] [["Alice"]]
โ”โ”โ”โ”โ”โ”โ”โ”โ”“
โ”ƒ Name  โ”ƒ
โ”ฃโ”โ”โ”โ”โ”โ”โ”โ”ซ
โ”ƒ Alice โ”ƒ
โ”—โ”โ”โ”โ”โ”โ”โ”โ”›

BorderRound:

withBorder BorderRound $ box "Info" ["content"]
โ•ญโ”€โ”€Infoโ”€โ”€โ”€โ•ฎ
โ”‚ content โ”‚
โ•ฐโ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ•ฏ

BorderNone (invisible borders):

withBorder BorderNone $ box "Info" ["content"]
  Info   
 content 
         

Colors (ANSI Support)

Add ANSI colors to any element:

layout[
  withColor ColorRed $ text "The quick brown fox...",
  withColor ColorBrightCyan $ text "The quick brown fox...",
  underlineColored "~" ColorRed $ text "The quick brown fox...",
  margin "[INFO]" [withColor ColorCyan $ text "The quick brown fox..."]
]

Standard Colors:

  • ColorBlack ColorRed ColorGreen ColorYellow ColorBlue ColorMagenta ColorCyan ColorWhite
  • ColorBrightBlack ColorBrightRed ColorBrightGreen ColorBrightYellow ColorBrightBlue ColorBrightMagenta ColorBrightCyan ColorBrightWhite
  • ColorNoColor (for conditional formatting)

Extended Colors:

  • ColorFull n - 256-color palette (0-255)
  • ColorTrue r g b - 24-bit RGB true color

Color Gradients

Create beautiful gradients with extended colors:

let palette   = tightRow $ map (\i -> withColor (ColorFull i) $ text "โ–ˆ") [16, 19..205]
    redToBlue = tightRow $ map (\i -> withColor (ColorTrue i 100 (255 - i)) $ text "โ–ˆ") [0, 4..255]
    greenFade = tightRow $ map (\i -> withColor (ColorTrue 0 (255 - i) i) $ text "โ–ˆ") [0, 4..255]
    rainbow   = tightRow $ map colorBlock [0, 4..255]
      where
        colorBlock i =
          let r = if i < 128 then i * 2 else 255
              g = if i < 128 then 255 else (255 - i) * 2
              b = if i > 128 then (i - 128) * 2 else 0
          in withColor (ColorTrue r g b) $ text "โ–ˆ"

putStrLn $ render $ layout [palette, redToBlue, greenFade, rainbow]

Styles (ANSI Support)

Add ANSI styles to any element:

layout[
  withStyle StyleBold $ text "The quick brown fox...",
  withColor ColorRed $ withStyle StyleBold $ text "The quick brown fox...",
  withStyle StyleReverse $ withStyle StyleItalic $ text "The quick brown fox..."
]

Styles:

  • StyleBold StyleDim StyleItalic StyleUnderline
  • StyleBlink StyleReverse StyleHidden StyleStrikethrough
  • StyleNoStyle (for conditional formatting)

Combining Styles:

Use <> to combine multiple styles at once:

layout[
  withStyle (StyleBold <> StyleItalic <> StyleUnderline) $ text "The quick brown fox...",
  withStyle (StyleBold <> StyleReverse) $ text "The quick brown fox..."
]

You can also combine colors and styles:

withColor ColorBrightYellow $ withStyle (StyleBold <> StyleItalic) $ text "The quick brown fox..."

Custom Components

Create your own components by implementing the Element typeclass

data Square = Square Int

instance Element Square where
  renderElement (Square size) 
    | size < 2 = ""
    | otherwise = intercalate "\n" (top : middle ++ [bottom])
    where
      w = size * 2 - 2
      top = "โ”Œ" ++ replicate w 'โ”€' ++ "โ”"
      middle = replicate (size - 2) ("โ”‚" ++ replicate w ' ' ++ "โ”‚")
      bottom = "โ””" ++ replicate w 'โ”€' ++ "โ”˜"

-- Helper to avoid wrapping with L
square :: Int -> L
square n = L (Square n)

-- Use it like any other element
putStrLn $ render $ row
  [ square 3
  , square 5
  , square 7
  ]
โ”Œโ”€โ”€โ”€โ”€โ” โ”Œโ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ” โ”Œโ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”
โ”‚    โ”‚ โ”‚        โ”‚ โ”‚            โ”‚
โ””โ”€โ”€โ”€โ”€โ”˜ โ”‚        โ”‚ โ”‚            โ”‚
       โ”‚        โ”‚ โ”‚            โ”‚
       โ””โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”˜ โ”‚            โ”‚
                  โ”‚            โ”‚
                  โ””โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”˜

REPL

Drop into GHCi to experiment:

cabal repl
ฮป> :set -XOverloadedStrings
ฮป> import Layoutz
ฮป> putStrLn $ render $ center $ box "Hello" ["World!"]
โ”Œโ”€โ”€Helloโ”€โ”€โ”
โ”‚ World!  โ”‚
โ””โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”€โ”˜
ฮป> putStrLn $ render $ table ["A", "B"] [["1", "2"]]
โ”Œโ”€โ”€โ”€โ”ฌโ”€โ”€โ”€โ”
โ”‚ A โ”‚ B โ”‚
โ”œโ”€โ”€โ”€โ”ผโ”€โ”€โ”€โ”ค
โ”‚ 1 โ”‚ 2 โ”‚
โ””โ”€โ”€โ”€โ”ดโ”€โ”€โ”€โ”˜

Interactive Apps

Build Elm-style terminal applications with the built-in TUI runtime.

import Layoutz

data Msg = Inc | Dec

counterApp :: LayoutzApp Int Msg
counterApp = LayoutzApp
  { appInit = (0, None)
  , appUpdate = \msg count -> case msg of
      Inc -> (count + 1, None)
      Dec -> (count - 1, None)
  , appSubscriptions = \_ -> onKeyPress $ \key -> case key of
      CharKey '+' -> Just Inc
      CharKey '-' -> Just Dec
      _           -> Nothing
  , appView = \count -> layout
      [ section "Counter" [text $ "Count: " <> show count]
      , ul ["Press '+' or '-'", "ESC to quit"]
      ]
  }

main = runApp counterApp

How the Runtime Works

The runApp function spawns three daemon threads:

  • Render thread - Continuously renders appView state to terminal (~30fps)
  • Input thread - Reads keys, maps via appSubscriptions, calls appUpdate
  • Command thread - Executes Cmd side effects async, feeds results back

As per the above, commands run without blocking the UI.

Press ESC to exit.

LayoutzApp state msg

data LayoutzApp state msg = LayoutzApp
  { appInit          :: (state, Cmd msg)                 -- Initial state + startup command
  , appUpdate        :: msg -> state -> (state, Cmd msg) -- Pure state transitions
  , appSubscriptions :: state -> Sub msg                 -- Event sources
  , appView          :: state -> L                       -- Render to UI
  }

Subscriptions

Subscription Description
onKeyPress (Key -> Maybe msg) Keyboard input
onTick msg Periodic ticks (~100ms) for animations
batch [sub1, sub2, ...] Combine subscriptions

Commands

Command Description
None No effect
Cmd (IO (Maybe msg)) Run IO, optionally produce message
Batch [cmd1, cmd2, ...] Multiple commands
cmd :: IO () -> Cmd msg Fire and forget
cmdMsg :: IO msg -> Cmd msg IO that returns a message

Example: Logger with file I/O

import Layoutz

data Msg = Log | Saved
data State = State { count :: Int, status :: String }

loggerApp :: LayoutzApp State Msg
loggerApp = LayoutzApp
  { appInit = (State 0 "Ready", None)
  , appUpdate = \msg s -> case msg of
      Log   -> (s { count = count s + 1 }, 
                cmd $ appendFile "log.txt" ("Entry " <> show (count s) <> "\n"))
      Saved -> (s { status = "Saved!" }, None)
  , appSubscriptions = \_ -> onKeyPress $ \key -> case key of
      CharKey 'l' -> Just Log
      _           -> Nothing
  , appView = \s -> layout
      [ section "Logger" [text $ "Entries: " <> show (count s)]
      , text (status s)
      , ul ["'l' to log", "ESC to quit"]
      ]
  }

main = runApp loggerApp

Key Types

CharKey Char       -- 'a', '1', ' '
EnterKey, BackspaceKey, TabKey, EscapeKey, DeleteKey
ArrowUpKey, ArrowDownKey, ArrowLeftKey, ArrowRightKey
SpecialKey String  -- "Ctrl+C", etc.

Inspiration