{-# LANGUAGE ParallelListComp #-} module Main where import Graphics.Rendering.Diagrams import Data.Colour.SRGB.Linear colors = [ rgb r 0 0.5 | r <- [0.2, 0.4 .. 1.0] ] circles = [ fc c $ circle r | c <- colors | r <- [5,4..1] ] alignments = [ [ (ha,va) | ha <- [left, hcenter, right] ] | va <- [top, vcenter, bottom] ] dia = vsep 2 . map (hsep 2) . map (map (\(h,v) -> unionA h v circles)) $ alignments main = do renderAs PNG "alignment.png" (Width 500) dia