Skip to content

Commit

Permalink
Add block config options to yaml parser
Browse files Browse the repository at this point in the history
  • Loading branch information
volhovm committed Oct 31, 2017
1 parent ab7e7cd commit 795bd6c
Show file tree
Hide file tree
Showing 3 changed files with 16 additions and 9 deletions.
11 changes: 7 additions & 4 deletions src/OrgStat/Config.hs
Expand Up @@ -26,9 +26,9 @@ import Data.Time (LocalTime)
import Data.Time.Format (defaultTimeLocale, parseTimeM)
import Universum

import OrgStat.Outputs.Types (BlockParams (..), SummaryParams (..),
TimelineParams, tpBackground, tpColumnHeight,
tpColumnWidth, tpLegend, tpTopDay)
import OrgStat.Outputs.Types (BlockParams, SummaryParams (..), TimelineParams,
bpMaxLength, bpUnicode, tpBackground,
tpColumnHeight, tpColumnWidth, tpLegend, tpTopDay)
import OrgStat.Scope (AstPath (..), ScopeModifier (..))
import OrgStat.Util (parseColour, (??~))

Expand Down Expand Up @@ -158,7 +158,10 @@ instance FromJSON ConfOutputType where
pure $ SummaryOutput $ SummaryParams soTemplate
(String "block") -> do
boReport <- o .: "report"
let boParams = def
maxLength <- o .: "maxLength"
unicode <- o .: "unicode"
let boParams = def & bpMaxLength ??~ maxLength
& bpUnicode ??~ unicode
pure $ BlockOutput {..}
other -> fail $ "Unsupported output type: " ++ show other

Expand Down
6 changes: 3 additions & 3 deletions src/OrgStat/Outputs/Block.hs
Expand Up @@ -33,18 +33,18 @@ genBlockOutput BlockParams{..} (filterHasClock -> o0) = do
BlockOutput $ fromString $ render $
hsep 2 center1 [vsep,col1,vsep,col2,vsep]
where
BlockFrames{..} = if bpUnicode then unicodeBlockFrames else asciiBlockFrames
BlockFrames{..} = if _bpUnicode then unicodeBlockFrames else asciiBlockFrames
text' = text . toString
elems = withDepth (0::Int) o0
col1 = vcat left $ map (text' . trimTitle . fst) elems
col2 = vcat right $ map (text' . snd) elems
vsep = vcat center1 $ replicate (length elems) (text $ toString bfVertical)

trimTitle t | T.length t > bpMaxLength = T.take (bpMaxLength - 3) t <> "..."
trimTitle t | T.length t > _bpMaxLength = T.take (_bpMaxLength - 3) t <> "..."
| otherwise = t
formatter o =
let dur = orgTotalDuration o
titleRaw = T.take bpMaxLength $ o ^. orgTitle
titleRaw = T.take _bpMaxLength $ o ^. orgTitle
in (titleRaw, timeF dur)

withDepth :: Int -> Org -> [(Text,Text)]
Expand Down
8 changes: 6 additions & 2 deletions src/OrgStat/Outputs/Types.hs
Expand Up @@ -16,6 +16,8 @@ module OrgStat.Outputs.Types
, SummaryOutput (..)

, BlockParams (..)
, bpMaxLength
, bpUnicode
, BlockOutput (..)
) where

Expand Down Expand Up @@ -93,11 +95,13 @@ newtype SummaryOutput = SummaryOutput Text

-- | Parameters for block output. Stub (for now).
data BlockParams = BlockParams
{ bpMaxLength :: Int
{ _bpMaxLength :: Int
-- ^ Maximum title length (together with indentation).
, bpUnicode :: Bool
, _bpUnicode :: Bool
} deriving (Show)

makeLenses ''BlockParams

instance Default BlockParams where
def = BlockParams 80 True

Expand Down

0 comments on commit 795bd6c

Please sign in to comment.