List and format
This commit is contained in:
@ -8,6 +8,7 @@ module Data.Buuka
|
||||
, Buuka
|
||||
|
||||
, insert
|
||||
, elements
|
||||
)
|
||||
where
|
||||
|
||||
@ -41,6 +42,9 @@ newtype Buuka = Buuka [BuukaEntry]
|
||||
insert :: BuukaEntry -> Buuka -> Buuka
|
||||
insert e (Buuka b) = Buuka (e : b)
|
||||
|
||||
elements :: Buuka -> [BuukaEntry]
|
||||
elements (Buuka b) = b
|
||||
|
||||
instance SafeJSON Buuka where
|
||||
type Version Buuka = 0
|
||||
|
||||
|
@ -1,6 +1,10 @@
|
||||
module Operations
|
||||
( module Operations.Insert )
|
||||
( module Operations.Insert
|
||||
, module Operations.List
|
||||
)
|
||||
where
|
||||
|
||||
import Operations.Insert
|
||||
(insert)
|
||||
import Operations.List
|
||||
(list)
|
||||
|
29
src/Operations/List.hs
Normal file
29
src/Operations/List.hs
Normal 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)
|
Reference in New Issue
Block a user