Skip to content

Instantly share code, notes, and snippets.

@oisdk
Last active April 28, 2019 22:32
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save oisdk/67e5231e477cf1e1ba680e48a7b5da88 to your computer and use it in GitHub Desktop.
Save oisdk/67e5231e477cf1e1ba680e48a7b5da88 to your computer and use it in GitHub Desktop.
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
import Data.Semigroup
import Control.Arrow
import Data.Align
import Data.Coerce
import Data.Tuple
newtype Stream a = Stream [a]
instance Monoid a => Monoid (Stream a) where
mempty = Stream []
mappend = coerce (malign @[] @a)
zipLeft f = foldr (\x k ~(y:ys) -> f x y : k ys) (const [])
pad = foldr (\x k n -> x : k (n-1)) (flip replicate ' ')
tabular :: [[String]] -> String
tabular = unlines . map unwords . loop (swap . uncurry f)
where
f xs (Stream ys) = traverse (first Stream . unzip . flip (zipLeft g) ys) xs
g x (Max n) = (Max (length x), pad x n)
ex1 :: String
ex1 = tabular
[ [ "foo", "bar" ]
, [ "x", "xyzzy", "foo" ]
, [ "sik", "kik", "tik" ]
]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment