{-# LANGUAGE OverloadedStrings, LambdaCase #-}
module Hledger.Utils (
module Hledger.Utils,
module Hledger.Utils.Debug,
module Hledger.Utils.Parse,
module Hledger.Utils.Regex,
module Hledger.Utils.String,
module Hledger.Utils.Text,
module Hledger.Utils.Test,
module Hledger.Utils.Color,
module Hledger.Utils.Tree,
error',userError',usageError,
)
where
import Control.Monad (liftM, when)
import Data.Default
import Data.FileEmbed (makeRelativeToProject, embedStringFile)
import Data.List
import Data.Text (Text)
import qualified Data.Text.IO as T
import Data.Time.Clock
import Data.Time.LocalTime
import Language.Haskell.TH.Syntax (Q, Exp)
import System.Directory (getHomeDirectory)
import System.FilePath((</>), isRelative)
import System.IO
import Hledger.Utils.Debug
import Hledger.Utils.Parse
import Hledger.Utils.Regex
import Hledger.Utils.String
import Hledger.Utils.Text
import Hledger.Utils.Test
import Hledger.Utils.Color
import Hledger.Utils.Tree
import Hledger.Utils.UTF8IOCompat (error',userError',usageError)
first3 (x,_,_) = x
second3 (_,x,_) = x
third3 (_,_,x) = x
first4 (x,_,_,_) = x
second4 (_,x,_,_) = x
third4 (_,_,x,_) = x
fourth4 (_,_,_,x) = x
first5 (x,_,_,_,_) = x
second5 (_,x,_,_,_) = x
third5 (_,_,x,_,_) = x
fourth5 (_,_,_,x,_) = x
fifth5 (_,_,_,_,x) = x
first6 (x,_,_,_,_,_) = x
second6 (_,x,_,_,_,_) = x
third6 (_,_,x,_,_,_) = x
fourth6 (_,_,_,x,_,_) = x
fifth6 (_,_,_,_,x,_) = x
sixth6 (_,_,_,_,_,x) = x
curry2 :: ((a, b) -> c) -> a -> b -> c
curry2 f x y = f (x, y)
uncurry2 :: (a -> b -> c) -> (a, b) -> c
uncurry2 f (x, y) = f x y
curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d
curry3 f x y z = f (x, y, z)
uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 f (x, y, z) = f x y z
curry4 :: ((a, b, c, d) -> e) -> a -> b -> c -> d -> e
curry4 f w x y z = f (w, x, y, z)
uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
uncurry4 f (w, x, y, z) = f w x y z
splitAtElement :: Eq a => a -> [a] -> [[a]]
splitAtElement x l =
case l of
[] -> []
e:es | e==x -> split es
es -> split es
where
split es = let (first,rest) = break (x==) es
in first : splitAtElement x rest
getCurrentLocalTime :: IO LocalTime
getCurrentLocalTime = do
t <- getCurrentTime
tz <- getCurrentTimeZone
return $ utcToLocalTime tz t
getCurrentZonedTime :: IO ZonedTime
getCurrentZonedTime = do
t <- getCurrentTime
tz <- getCurrentTimeZone
return $ utcToZonedTime tz t
instance Default Bool where def = False
isLeft :: Either a b -> Bool
isLeft (Left _) = True
isLeft _ = False
isRight :: Either a b -> Bool
isRight = not . isLeft
applyN :: Int -> (a -> a) -> a -> a
applyN n f | n < 1 = id
| otherwise = (!! n) . iterate f
expandPath :: FilePath -> FilePath -> IO FilePath
expandPath _ "-" = return "-"
expandPath curdir p = (if isRelative p then (curdir </>) else id) `liftM` expandHomePath p
expandHomePath :: FilePath -> IO FilePath
expandHomePath = \case
('~':'/':p) -> (</> p) <$> getHomeDirectory
('~':'\\':p) -> (</> p) <$> getHomeDirectory
('~':_) -> ioError $ userError "~USERNAME in paths is not supported"
p -> return p
firstJust ms = case dropWhile (==Nothing) ms of
[] -> Nothing
(md:_) -> md
readFilePortably :: FilePath -> IO Text
readFilePortably f = openFile f ReadMode >>= readHandlePortably
readFileOrStdinPortably :: String -> IO Text
readFileOrStdinPortably f = openFileOrStdin f ReadMode >>= readHandlePortably
where
openFileOrStdin :: String -> IOMode -> IO Handle
openFileOrStdin "-" _ = return stdin
openFileOrStdin f m = openFile f m
readHandlePortably :: Handle -> IO Text
readHandlePortably h = do
hSetNewlineMode h universalNewlineMode
menc <- hGetEncoding h
when (fmap show menc == Just "UTF-8") $
hSetEncoding h utf8_bom
T.hGetContents h
maximum' :: Integral a => [a] -> a
maximum' [] = 0
maximum' xs = maximumStrict xs
{-# INLINABLE sumStrict #-}
sumStrict :: Num a => [a] -> a
sumStrict = foldl' (+) 0
{-# INLINABLE maximumStrict #-}
maximumStrict :: Ord a => [a] -> a
maximumStrict = foldl1' max
{-# INLINABLE minimumStrict #-}
minimumStrict :: Ord a => [a] -> a
minimumStrict = foldl1' min
{-# INLINABLE sequence' #-}
sequence' :: Monad f => [f a] -> f [a]
sequence' ms = do
h <- go id ms
return (h [])
where
go h [] = return h
go h (m:ms) = do
x <- m
go (h . (x :)) ms
{-# INLINABLE mapM' #-}
mapM' :: Monad f => (a -> f b) -> [a] -> f [b]
mapM' f = sequence' . map f
embedFileRelative :: FilePath -> Q Exp
embedFileRelative f = makeRelativeToProject f >>= embedStringFile
tests_Utils = tests "Utils" [
tests_Text
]