module Hledger.Utils (
module Hledger.Utils,
Debug.Trace.trace,
SystemString,fromSystemString,toSystemString,error',userError',
#if __GLASGOW_HASKELL__ >= 704
ppShow
#endif
)
where
import Control.Monad (liftM, when)
import Control.Monad.Error (MonadIO)
import Control.Monad.IO.Class (liftIO)
import Data.Char
import Data.List
import qualified Data.Map as M
import Data.Maybe
import Data.Time.Clock
import Data.Time.LocalTime
import Data.Tree
import Debug.Trace
import Safe (readDef)
import System.Directory (getHomeDirectory)
import System.Environment (getArgs)
import System.Exit
import System.FilePath((</>), isRelative)
import System.IO
import System.IO.Unsafe (unsafePerformIO)
import Test.HUnit
import Text.ParserCombinators.Parsec
import Text.Printf
import Text.Regex.TDFA
import Text.RegexPR
import Hledger.Utils.UTF8IOCompat (SystemString,fromSystemString,toSystemString,error',userError')
#if __GLASGOW_HASKELL__ >= 704
import Text.Show.Pretty (ppShow)
#else
ppShow :: Show a => a -> String
ppShow = show
#endif
lowercase = map toLower
uppercase = map toUpper
strip = lstrip . rstrip
lstrip = dropWhile (`elem` " \t") :: String -> String
rstrip = reverse . lstrip . reverse
stripbrackets = dropWhile (`elem` "([") . reverse . dropWhile (`elem` "])") . reverse :: String -> String
elideLeft width s =
if length s > width then ".." ++ reverse (take (width 2) $ reverse s) else s
elideRight width s =
if length s > width then take (width 2) s ++ ".." else s
underline :: String -> String
underline s = s' ++ replicate (length s) '-' ++ "\n"
where s'
| last s == '\n' = s
| otherwise = s ++ "\n"
quoteIfSpaced :: String -> String
quoteIfSpaced s | isSingleQuoted s || isDoubleQuoted s = s
| not $ any (`elem` s) whitespacechars = s
| otherwise = "'"++escapeSingleQuotes s++"'"
quoteIfNeeded s | any (`elem` s) (quotechars++whitespacechars) = "\"" ++ escapeDoubleQuotes s ++ "\""
| otherwise = s
singleQuoteIfNeeded s | any (`elem` s) whitespacechars = "'"++s++"'"
| otherwise = s
quotechars = "'\""
whitespacechars = " \t\n\r"
escapeDoubleQuotes :: String -> String
escapeDoubleQuotes = regexReplace "\"" "\""
escapeSingleQuotes :: String -> String
escapeSingleQuotes = regexReplace "'" "\'"
escapeQuotes :: String -> String
escapeQuotes = regexReplace "([\"'])" "\\1"
words' :: String -> [String]
words' "" = []
words' s = map stripquotes $ fromparse $ parsewith p s
where
p = do ss <- (singleQuotedPattern <|> doubleQuotedPattern <|> pattern) `sepBy` many1 spacenonewline
return ss
pattern = many (noneOf whitespacechars)
singleQuotedPattern = between (char '\'') (char '\'') (many $ noneOf "'")
doubleQuotedPattern = between (char '"') (char '"') (many $ noneOf "\"")
unwords' :: [String] -> String
unwords' = unwords . map quoteIfNeeded
stripquotes :: String -> String
stripquotes s = if isSingleQuoted s || isDoubleQuoted s then init $ tail s else s
isSingleQuoted s@(_:_:_) = head s == '\'' && last s == '\''
isSingleQuoted _ = False
isDoubleQuoted s@(_:_:_) = head s == '"' && last s == '"'
isDoubleQuoted _ = False
unbracket :: String -> String
unbracket s
| (head s == '[' && last s == ']') || (head s == '(' && last s == ')') = init $ tail s
| otherwise = s
concatTopPadded :: [String] -> String
concatTopPadded strs = intercalate "\n" $ map concat $ transpose padded
where
lss = map lines strs
h = maximum $ map length lss
ypad ls = replicate (difforzero h (length ls)) "" ++ ls
xpad ls = map (padleft w) ls where w | null ls = 0
| otherwise = maximum $ map length ls
padded = map (xpad . ypad) lss
concatBottomPadded :: [String] -> String
concatBottomPadded strs = intercalate "\n" $ map concat $ transpose padded
where
lss = map lines strs
h = maximum $ map length lss
ypad ls = ls ++ replicate (difforzero h (length ls)) ""
xpad ls = map (padright w) ls where w | null ls = 0
| otherwise = maximum $ map length ls
padded = map (xpad . ypad) lss
vConcatRightAligned :: [String] -> String
vConcatRightAligned ss = intercalate "\n" $ map showfixedwidth ss
where
showfixedwidth = printf (printf "%%%ds" width)
width = maximum $ map length ss
padtop :: Int -> String -> String
padtop h s = intercalate "\n" xpadded
where
ls = lines s
sh = length ls
sw | null ls = 0
| otherwise = maximum $ map length ls
ypadded = replicate (difforzero h sh) "" ++ ls
xpadded = map (padleft sw) ypadded
padbottom :: Int -> String -> String
padbottom h s = intercalate "\n" xpadded
where
ls = lines s
sh = length ls
sw | null ls = 0
| otherwise = maximum $ map length ls
ypadded = ls ++ replicate (difforzero h sh) ""
xpadded = map (padleft sw) ypadded
padleft :: Int -> String -> String
padleft w "" = concat $ replicate w " "
padleft w s = intercalate "\n" $ map (printf (printf "%%%ds" w)) $ lines s
padright :: Int -> String -> String
padright w "" = concat $ replicate w " "
padright w s = intercalate "\n" $ map (printf (printf "%%-%ds" w)) $ lines s
cliptopleft :: Int -> Int -> String -> String
cliptopleft w h = intercalate "\n" . take h . map (take w) . lines
fitto :: Int -> Int -> String -> String
fitto w h s = intercalate "\n" $ take h $ rows ++ repeat blankline
where
rows = map (fit w) $ lines s
fit w = take w . (++ repeat ' ')
blankline = replicate w ' '
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
difforzero :: (Num a, Ord a) => a -> a -> a
difforzero a b = maximum [(a b), 0]
regexMatch r s = matchRegexPR r s
regexMatchCI r s = regexMatch (regexToCaseInsensitive r) s
regexMatches :: String -> String -> Bool
regexMatches r s = isJust $ matchRegexPR r s
regexMatchesCI :: String -> String -> Bool
regexMatchesCI r s = regexMatches (regexToCaseInsensitive r) s
containsRegex = regexMatchesCI
regexReplace :: String -> String -> String -> String
regexReplace r repl s = gsubRegexPR r repl s
regexReplaceCI :: String -> String -> String -> String
regexReplaceCI r s = regexReplace (regexToCaseInsensitive r) s
regexReplaceBy :: String -> (String -> String) -> String -> String
regexReplaceBy r replfn s = gsubRegexPRBy r replfn s
regexToCaseInsensitive :: String -> String
regexToCaseInsensitive r = "(?i)"++ r
regexSplit :: String -> String -> [String]
regexSplit = splitRegexPR
regexMatchesRegexCompat :: String -> String -> Bool
regexMatchesRegexCompat = flip (=~)
regexMatchesCIRegexCompat :: String -> String -> Bool
regexMatchesCIRegexCompat r = match (makeRegexOpts defaultCompOpt { multiline = True, caseSensitive = False, newSyntax = True } defaultExecOpt r)
splitAtElement :: Eq a => a -> [a] -> [[a]]
splitAtElement e l =
case dropWhile (e==) l of
[] -> []
l' -> first : splitAtElement e rest
where
(first,rest) = break (e==) l'
root = rootLabel
subs = subForest
branches = subForest
leaves :: Tree a -> [a]
leaves (Node v []) = [v]
leaves (Node _ branches) = concatMap leaves branches
subtreeat :: Eq a => a -> Tree a -> Maybe (Tree a)
subtreeat v t
| root t == v = Just t
| otherwise = subtreeinforest v $ subs t
subtreeinforest :: Eq a => a -> [Tree a] -> Maybe (Tree a)
subtreeinforest _ [] = Nothing
subtreeinforest v (t:ts) = case (subtreeat v t) of
Just t' -> Just t'
Nothing -> subtreeinforest v ts
treeprune :: Int -> Tree a -> Tree a
treeprune 0 t = Node (root t) []
treeprune d t = Node (root t) (map (treeprune $ d1) $ branches t)
treemap :: (a -> b) -> Tree a -> Tree b
treemap f t = Node (f $ root t) (map (treemap f) $ branches t)
treefilter :: (a -> Bool) -> Tree a -> Tree a
treefilter f t = Node
(root t)
(map (treefilter f) $ filter (treeany f) $ branches t)
treeany :: (a -> Bool) -> Tree a -> Bool
treeany f t = f (root t) || any (treeany f) (branches t)
showtree :: Show a => Tree a -> String
showtree = unlines . filter (regexMatches "[^ \\|]") . lines . drawTree . treemap show
showforest :: Show a => Forest a -> String
showforest = concatMap showtree
newtype FastTree a = T (M.Map a (FastTree a))
deriving (Show, Eq, Ord)
emptyTree = T M.empty
mergeTrees :: (Ord a) => FastTree a -> FastTree a -> FastTree a
mergeTrees (T m) (T m') = T (M.unionWith mergeTrees m m')
treeFromPath :: [a] -> FastTree a
treeFromPath [] = T M.empty
treeFromPath (x:xs) = T (M.singleton x (treeFromPath xs))
treeFromPaths :: (Ord a) => [[a]] -> FastTree a
treeFromPaths = foldl' mergeTrees emptyTree . map treeFromPath
strace :: Show a => a -> a
strace a = trace (show a) a
ltrace :: Show a => String -> a -> a
ltrace l a = trace (l ++ ": " ++ show a) a
mtrace :: (Monad m, Show a) => a -> m a
mtrace a = strace a `seq` return a
traceWith :: (a -> String) -> a -> a
traceWith f e = trace (f e) e
ptrace :: String -> GenParser Char st ()
ptrace msg = do
pos <- getPosition
next <- take peeklength `fmap` getInput
let (l,c) = (sourceLine pos, sourceColumn pos)
s = printf "at line %2d col %2d: %s" l c (show next) :: String
s' = printf ("%-"++show (peeklength+30)++"s") s ++ " " ++ msg
trace s' $ return ()
where
peeklength = 30
debugLevel :: Int
debugLevel = case snd $ break (=="--debug") args of
"--debug":[] -> 1
"--debug":n:_ -> readDef 1 n
_ ->
case take 1 $ filter ("--debug" `isPrefixOf`) args of
['-':'-':'d':'e':'b':'u':'g':'=':v] -> readDef 1 v
_ -> 0
where
args = unsafePerformIO getArgs
dbg :: Show a => String -> a -> a
dbg = dbg1
dbg0 :: Show a => String -> a -> a
dbg0 = dbgAt 0
dbg1 :: Show a => String -> a -> a
dbg1 = dbgAt 1
dbg2 :: Show a => String -> a -> a
dbg2 = dbgAt 2
dbgAt :: Show a => Int -> String -> a -> a
dbgAt lvl = dbgppshow lvl
dbgAtM :: Show a => Int -> String -> a -> IO ()
dbgAtM lvl lbl x = dbgAt lvl lbl x `seq` return ()
dbgshow :: Show a => Int -> String -> a -> a
dbgshow level
| debugLevel >= level = ltrace
| otherwise = flip const
dbgppshow :: Show a => Int -> String -> a -> a
dbgppshow level
| debugLevel < level = flip const
| otherwise = \s a -> let p = ppShow a
ls = lines p
nlorspace | length ls > 1 = "\n"
| otherwise = " " ++ take (10 length s) (repeat ' ')
ls' | length ls > 1 = map (" "++) ls
| otherwise = ls
in trace (s++":"++nlorspace++intercalate "\n" ls') a
dbgExit :: Show a => String -> a -> a
dbgExit msg = const (unsafePerformIO exitFailure) . dbg msg
pdbg level msg = when (level <= debugLevel) $ ptrace msg
choice' :: [GenParser tok st a] -> GenParser tok st a
choice' = choice . map Text.ParserCombinators.Parsec.try
parsewith :: Parser a -> String -> Either ParseError a
parsewith p = parse p ""
parseWithCtx :: b -> GenParser Char b a -> String -> Either ParseError a
parseWithCtx ctx p = runParser p ctx ""
fromparse :: Either ParseError a -> a
fromparse = either parseerror id
parseerror :: ParseError -> a
parseerror e = error' $ showParseError e
showParseError :: ParseError -> String
showParseError e = "parse error at " ++ show e
showDateParseError :: ParseError -> String
showDateParseError e = printf "date parse error (%s)" (intercalate ", " $ tail $ lines $ show e)
nonspace :: GenParser Char st Char
nonspace = satisfy (not . isSpace)
spacenonewline :: GenParser Char st Char
spacenonewline = satisfy (`elem` " \v\f\t")
restofline :: GenParser Char st String
restofline = anyChar `manyTill` newline
eolof :: GenParser Char st ()
eolof = (newline >> return ()) <|> eof
getCurrentLocalTime :: IO LocalTime
getCurrentLocalTime = do
t <- getCurrentTime
tz <- getCurrentTimeZone
return $ utcToLocalTime tz t
testName :: Test -> String
testName (TestLabel n _) = n
testName _ = ""
flattenTests :: Test -> [Test]
flattenTests (TestLabel _ t@(TestList _)) = flattenTests t
flattenTests (TestList ts) = concatMap flattenTests ts
flattenTests t = [t]
filterTests :: (Test -> Bool) -> Test -> Test
filterTests p (TestLabel l ts) = TestLabel l (filterTests p ts)
filterTests p (TestList ts) = TestList $ filter (any p . flattenTests) $ map (filterTests p) ts
filterTests _ t = t
is :: (Eq a, Show a) => a -> a -> Assertion
a `is` e = assertEqual "" e a
assertParse :: (Either ParseError a) -> Assertion
assertParse parse = either (assertFailure.show) (const (return ())) parse
assertParseFailure :: (Either ParseError a) -> Assertion
assertParseFailure parse = either (const $ return ()) (const $ assertFailure "parse should not have succeeded") parse
assertParseEqual :: (Show a, Eq a) => (Either ParseError a) -> a -> Assertion
assertParseEqual parse expected = either (assertFailure.show) (`is` expected) parse
printParseError :: (Show a) => a -> IO ()
printParseError e = do putStr "parse error at "; print e
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) . iterate f
expandPath :: MonadIO m => FilePath -> FilePath -> m FilePath
expandPath _ "-" = return "-"
expandPath curdir p = (if isRelative p then (curdir </>) else id) `liftM` expandPath' p
where
expandPath' ('~':'/':p) = liftIO $ (</> p) `fmap` getHomeDirectory
expandPath' ('~':'\\':p) = liftIO $ (</> p) `fmap` getHomeDirectory
expandPath' ('~':_) = error' "~USERNAME in paths is not supported"
expandPath' p = return p
firstJust ms = case dropWhile (==Nothing) ms of
[] -> Nothing
(md:_) -> md
readFile' :: FilePath -> IO String
readFile' name = do
h <- openFile name ReadMode
hSetNewlineMode h universalNewlineMode
hGetContents h