List and format

This commit is contained in:
2021-01-01 08:29:24 +02:00
parent 32afc6ba29
commit d9445823bb
6 changed files with 49 additions and 10 deletions

29
src/Operations/List.hs Normal file
View File

@ -0,0 +1,29 @@
{-# LANGUAGE LambdaCase #-}
module Operations.List where
import Control.Monad.Buuka
import Control.Monad.Reader
(liftIO, asks)
import Data.Foldable
(traverse_)
import Data.Semigroup (Max(..))
import Data.Buuka
(URL(..), BuukaEntry(..))
import qualified Data.Buuka as B
list :: BuukaM ()
list =
buukaQ (asks (format . B.elements)) >>= traverse_ (liftIO . putStrLn)
where
format :: [BuukaEntry] -> [String]
format xs =
let formatted = zipWith formatEntry [1..] xs
indexWidth = getMax . foldMap (Max . length . fst) $ formatted
in fmap (\(idx,x) -> idx <> replicate (indexWidth - length idx) ' ' <> ". " <> x) formatted
formatEntry :: Int -> BuukaEntry -> (String, String)
formatEntry n = \case
BuukaEntry{title=Just t} -> (show n, t)
BuukaEntry{url=URL u} -> (show n, u)