dev: lib: Utils cleanups

This commit is contained in:
Simon Michael 2022-11-04 09:51:25 -10:00
parent 5bc977442a
commit 80249c3e8a
2 changed files with 16 additions and 33 deletions

View File

@ -1,34 +1,20 @@
{-| {-|
Utilities used throughout hledger, or needed low in the module hierarchy.
Standard imports and utilities which are useful everywhere, or needed low This is the bottom of hledger's module graph.
in the module hierarchy. This is the bottom of hledger's module graph.
-} -}
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
module Hledger.Utils (---- provide these frequently used modules - or not, for clearer api: module Hledger.Utils (
-- module Control.Monad, module Hledger.Utils,
-- module Data.List, module Hledger.Utils.Debug,
-- module Data.Maybe, module Hledger.Utils.Parse,
-- module Data.Time.Calendar, module Hledger.Utils.Print,
-- module Data.Time.Clock, module Hledger.Utils.Regex,
-- module Data.Time.LocalTime, module Hledger.Utils.String,
-- module Data.Tree, module Hledger.Utils.Text,
-- module Text.RegexPR, module Hledger.Utils.Test,
-- module Text.Printf, )
---- all of this one:
module Hledger.Utils,
module Hledger.Utils.Debug,
module Hledger.Utils.Parse,
module Hledger.Utils.Print,
module Hledger.Utils.Regex,
module Hledger.Utils.String,
module Hledger.Utils.Text,
module Hledger.Utils.Test,
-- Debug.Trace.trace,
-- module Data.PPrint,
-- the rest need to be done in each module I think
)
where where
import Control.Monad (when) import Control.Monad (when)
@ -42,8 +28,8 @@ import qualified Data.Text.Lazy.Builder as TB
import Data.Time.Clock (getCurrentTime) import Data.Time.Clock (getCurrentTime)
import Data.Time.LocalTime (LocalTime, ZonedTime, getCurrentTimeZone, import Data.Time.LocalTime (LocalTime, ZonedTime, getCurrentTimeZone,
utcToLocalTime, utcToZonedTime) utcToLocalTime, utcToZonedTime)
import Data.Tree (foldTree, Tree (Node, subForest))
import Language.Haskell.TH (DecsQ, Name, mkName, nameBase) import Language.Haskell.TH (DecsQ, Name, mkName, nameBase)
-- import Language.Haskell.TH.Quote (QuasiQuoter(..))
import Language.Haskell.TH.Syntax (Q, Exp) import Language.Haskell.TH.Syntax (Q, Exp)
import Lens.Micro ((&), (.~)) import Lens.Micro ((&), (.~))
import Lens.Micro.TH (DefName(TopName), lensClass, lensField, makeLensesWith, classyRules) import Lens.Micro.TH (DefName(TopName), lensClass, lensField, makeLensesWith, classyRules)
@ -61,7 +47,6 @@ import Hledger.Utils.Regex
import Hledger.Utils.String import Hledger.Utils.String
import Hledger.Utils.Text import Hledger.Utils.Text
import Hledger.Utils.Test import Hledger.Utils.Test
import Data.Tree (foldTree, Tree (Node, subForest))
-- tuples -- tuples
@ -128,8 +113,6 @@ treeLeaves :: Show a => Tree a -> [a]
treeLeaves Node{subForest=[]} = [] treeLeaves Node{subForest=[]} = []
treeLeaves t = foldTree (\a bs -> (if null bs then (a:) else id) $ concat bs) t treeLeaves t = foldTree (\a bs -> (if null bs then (a:) else id) $ concat bs) t
-- text
-- time -- time
getCurrentLocalTime :: IO LocalTime getCurrentLocalTime :: IO LocalTime

View File

@ -108,12 +108,12 @@ colorOption =
-- or ( -- or (
-- the program was not started with --color=no|never -- the program was not started with --color=no|never
-- and a NO_COLOR environment variable is not defined -- and a NO_COLOR environment variable is not defined
-- and stdout supports ANSI color and -o/--output-file was not used or is "-" -- and stdout supports ANSI color
-- and -o/--output-file was not used, or its value is "-"
-- ). -- ).
useColorOnStdout :: Bool useColorOnStdout :: Bool
useColorOnStdout = not hasOutputFile && useColorOnHandle stdout useColorOnStdout = not hasOutputFile && useColorOnHandle stdout
-- Avoid using dbg*, pshow etc. in this function (infinite loop).
-- | Like useColorOnStdout, but checks for ANSI color support on stderr, -- | Like useColorOnStdout, but checks for ANSI color support on stderr,
-- and is not affected by -o/--output-file. -- and is not affected by -o/--output-file.
useColorOnStderr :: Bool useColorOnStderr :: Bool