Skip to content

Commit

Permalink
[#66] Print list of found templates in nicer way
Browse files Browse the repository at this point in the history
  • Loading branch information
vaclavsvejcar committed Apr 15, 2021
1 parent 9c83ad6 commit 89bee01
Show file tree
Hide file tree
Showing 6 changed files with 74 additions and 28 deletions.
4 changes: 3 additions & 1 deletion headroom.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ cabal-version: 2.2
--
-- see: https://github.com/sol/hpack
--
-- hash: f870c819024dab0465f52c54b12f1cbaa2bbe15340fdbad90db4d3c64b3da3fb
-- hash: 72415323085ba06bc3915586a518274dfacd0cc40094ff2cb15a4fda96cce90b

name: headroom
version: 0.4.2.0
Expand Down Expand Up @@ -189,6 +189,7 @@ library
Headroom.Types
Headroom.UI
Headroom.UI.Progress
Headroom.UI.Table
Headroom.Variables
Headroom.Variables.Types
other-modules:
Expand Down Expand Up @@ -291,6 +292,7 @@ test-suite spec
Headroom.Template.TemplateRefSpec
Headroom.TypesSpec
Headroom.UI.ProgressSpec
Headroom.UI.TableSpec
Headroom.VariablesSpec
Paths_headroom
hs-source-dirs:
Expand Down
25 changes: 4 additions & 21 deletions src/Headroom/Command/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,6 @@ responsible for license header management.

module Headroom.Command.Run
( commandRun
, loadBuiltInTemplates
, loadTemplateRefs
, typeOfTemplate
-- * License Header Post-processing
Expand All @@ -55,7 +54,6 @@ import Headroom.Configuration.Types ( Configuration(..)
, CtHeaderFnConfigs
, HeaderConfig(..)
, HeaderSyntax(..)
, LicenseType(..)
, PtConfiguration
, RunMode(..)
)
Expand Down Expand Up @@ -108,6 +106,7 @@ import Headroom.Types ( CurrentYear(..) )
import Headroom.UI ( Progress(..)
, zipWithProgress
)
import Headroom.UI.Table ( Table2(..) )
import Headroom.Variables ( compileVariables
, dynamicVariables
, parseVariables
Expand Down Expand Up @@ -388,22 +387,6 @@ loadTemplateRefs refs = do
mapMaybe (L.headMaybe . L.sort) . L.groupBy (\x y -> fst x == fst y) $ rs


-- | Loads built-in templates, stored in "Headroom.Embedded", for the given
-- 'LicenseType'.
loadBuiltInTemplates :: (HasLogFunc env)
=> LicenseType -- ^ selected license type
-> RIO env (Map FileType TemplateType) -- ^ map of file types and templates
loadBuiltInTemplates licenseType = do
logInfo $ "Using built-in templates for license: " <> displayShow licenseType
parsed <- mapM
(\(t, r) -> (t, ) <$> parseTemplate (BuiltInRef licenseType t) r)
rawTemplates
pure $ M.fromList parsed
where
rawTemplates = fmap (\ft -> (ft, template ft)) (allValues @FileType)
template = licenseTemplate licenseType


loadTemplates :: ( Has CtConfiguration env
, Has (FileSystem (RIO env)) env
, Has (Network (RIO env)) env
Expand All @@ -414,11 +397,11 @@ loadTemplates = do
Configuration {..} <- viewL @CtConfiguration
let allRefs = builtInRefs cBuiltInTemplates <> cTemplateRefs
templates <- loadTemplateRefs @TemplateType allRefs
logInfo . display . T.intercalate "\n" . stats . M.toList $ templates
logInfo . display . stats . M.toList $ templates
pure $ M.mapWithKey (extractHeaderTemplate cLicenseHeaders) templates
where
stats =
fmap (\(ft, t) -> [i|Using #{ft} template: #{renderRef . templateRef $ t}|])
stats = Table2 . fmap
(\(ft, t) -> ([i|Using #{ft} template:|], renderRef . templateRef $ t))
builtInRefs = \case
Just lt -> fmap (BuiltInRef lt) $ allValues @FileType
_ -> []
Expand Down
34 changes: 34 additions & 0 deletions src/Headroom/UI/Table.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,34 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE StrictData #-}

{-|
Module : Headroom.UI.Table
Description : UI components for rendering tables
Copyright : (c) 2019-2021 Vaclav Svejcar
License : BSD-3-Clause
Maintainer : [email protected]
Stability : experimental
Portability : POSIX
Module providing UI components for tables.
-}

module Headroom.UI.Table where

import qualified Headroom.Data.Text as T
import RIO
import qualified RIO.List.Partial as LP
import qualified RIO.Text as T


-- | Represents two columns wide table.
newtype Table2 = Table2 [(Text, Text)] deriving (Eq, Show)

instance Display Table2 where
textDisplay (Table2 rows) =
let maxWidth = (+ 1) . maximum' . fmap (T.length . fst) $ rows
aligned = fmap (\(c1, c2) -> T.justifyLeft maxWidth ' ' c1 <> c2) rows
in T.fromLines aligned
where
maximum' [] = 0
maximum' xs = LP.maximum xs
5 changes: 0 additions & 5 deletions test/Headroom/Command/RunSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,6 @@ import Headroom.Configuration.Types ( CtHeaderFnConfigs
, HeaderFnConfig(..)
, HeaderFnConfigs(..)
, HeaderSyntax(..)
, LicenseType(..)
, UpdateCopyrightConfig(..)
)
import Headroom.Data.EnumExtra ( EnumExtra(..) )
Expand Down Expand Up @@ -82,10 +81,6 @@ instance Has (Network (RIO TestEnv)) TestEnv where

spec :: Spec
spec = do
describe "loadBuiltInTemplates" $ do
it "should load correct number of built-in templates" $ do
M.size <$> runRIO env (loadBuiltInTemplates BSD3) `shouldReturn` 12


describe "loadTemplateRefs" $ do
it "should load templates from given references" $ do
Expand Down
5 changes: 4 additions & 1 deletion test/Headroom/UI/ProgressSpec.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}

module Headroom.UI.ProgressSpec
( spec
)
Expand All @@ -11,13 +12,15 @@ import Test.Hspec

spec :: Spec
spec = do

describe "zipWithProgress" $ do
it "zips progress for given collection" $ do
let col = ["a", "b"] :: [Text]
expected = [(Progress 1 2, "a"), (Progress 2 2, "b")]
zipWithProgress col `shouldBe` expected

describe "show" $ do

describe "Display instance" $ do
it "displays correct output for Progress data type" $ do
textDisplay (Progress 1 1) `shouldBe` "[1 of 1]"
textDisplay (Progress 10 250) `shouldBe` "[ 10 of 250]"
29 changes: 29 additions & 0 deletions test/Headroom/UI/TableSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}

module Headroom.UI.TableSpec
( spec
)
where

import qualified Headroom.Data.Text as T
import Headroom.UI.Table
import RIO
import Test.Hspec


spec :: Spec
spec = do
describe "Display instance for Table2" $ do
it "prints columns correctly aligned" $ do
let sample = Table2
[ ("hello" , "world")
, ("super super long first column", "foo")
, ("bar" , "baz")
]
expected = T.fromLines
[ "hello world"
, "super super long first column foo"
, "bar baz"
]
textDisplay sample `shouldBe` expected

0 comments on commit 89bee01

Please sign in to comment.