lib,cli,ui: Remove old CPP directives made redundant by version bounds.
This commit is contained in:
parent
dc426266a4
commit
2fd678e415
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE NoMonoLocalBinds #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
@ -93,12 +92,7 @@ import Data.Maybe
|
||||
import qualified Data.Set as Set
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
#if MIN_VERSION_time(1,5,0)
|
||||
import Data.Time.Format hiding (months)
|
||||
#else
|
||||
import Data.Time.Format
|
||||
import System.Locale (TimeLocale, defaultTimeLocale)
|
||||
#endif
|
||||
import Data.Time.Calendar
|
||||
import Data.Time.Calendar.OrdinalDate
|
||||
import Data.Time.Clock
|
||||
@ -669,23 +663,20 @@ advancetonthweekday n wd s =
|
||||
-- parseTime defaultTimeLocale "%Y-%m-%d %H:%M:%S" s
|
||||
-- ]
|
||||
|
||||
parsetime :: ParseTime t => TimeLocale -> String -> String -> Maybe t
|
||||
parsetime =
|
||||
#if MIN_VERSION_time(1,5,0)
|
||||
parseTimeM True
|
||||
#else
|
||||
parseTime
|
||||
#endif
|
||||
|
||||
|
||||
-- | Try to parse a couple of date string formats:
|
||||
-- `YYYY-MM-DD`, `YYYY/MM/DD` or `YYYY.MM.DD`, with leading zeros required.
|
||||
-- For internal use, not quite the same as the journal's "simple dates".
|
||||
-- >>> parsedateM "2008/02/03"
|
||||
-- Just 2008-02-03
|
||||
-- >>> parsedateM "2008/02/03/"
|
||||
-- Nothing
|
||||
-- >>> parsedateM "2008/02/30"
|
||||
-- Nothing
|
||||
parsedateM :: String -> Maybe Day
|
||||
parsedateM s = asum [
|
||||
parsetime defaultTimeLocale "%Y-%m-%d" s,
|
||||
parsetime defaultTimeLocale "%Y/%m/%d" s,
|
||||
parsetime defaultTimeLocale "%Y.%m.%d" s
|
||||
parseTimeM True defaultTimeLocale "%Y-%m-%d" s,
|
||||
parseTimeM True defaultTimeLocale "%Y/%m/%d" s,
|
||||
parseTimeM True defaultTimeLocale "%Y.%m.%d" s
|
||||
]
|
||||
|
||||
|
||||
@ -695,28 +686,9 @@ parsedateM s = asum [
|
||||
-- (parsedatetimeM s)
|
||||
|
||||
-- | Like parsedateM, raising an error on parse failure.
|
||||
--
|
||||
-- >>> parsedate "2008/02/03"
|
||||
-- 2008-02-03
|
||||
parsedate :: String -> Day
|
||||
parsedate s = fromMaybe (error' $ "could not parse date \"" ++ s ++ "\"") -- PARTIAL:
|
||||
(parsedateM s)
|
||||
-- doctests I haven't been able to make compatible with both GHC 7 and 8
|
||||
-- -- >>> parsedate "2008/02/03/"
|
||||
-- -- *** Exception: could not parse date "2008/02/03/"
|
||||
-- #if MIN_VERSION_base(4,9,0)
|
||||
-- -- ...
|
||||
-- #endif
|
||||
-- #if MIN_VERSION_time(1,6,0)
|
||||
-- -- >>> parsedate "2008/02/30" -- with time >= 1.6, invalid dates are rejected
|
||||
-- -- *** Exception: could not parse date "2008/02/30"
|
||||
-- #if MIN_VERSION_base(4,9,0)
|
||||
-- -- ...
|
||||
-- #endif
|
||||
-- #else
|
||||
-- -- >>> parsedate "2008/02/30" -- with time < 1.6, they are silently adjusted
|
||||
-- -- 2008-02-29
|
||||
-- #endif
|
||||
parsedate s = fromMaybe (error' $ "could not parse date \"" ++ s ++ "\"") -- PARTIAL:
|
||||
$ parsedateM s
|
||||
|
||||
{-|
|
||||
Parse a date in any of the formats allowed in Ledger's period expressions, and some others.
|
||||
|
||||
@ -6,7 +6,7 @@ converted to 'Transactions' and queried like a ledger.
|
||||
|
||||
-}
|
||||
|
||||
{-# LANGUAGE CPP, OverloadedStrings #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Hledger.Data.Timeclock (
|
||||
timeclockEntriesToTransactions
|
||||
@ -21,9 +21,6 @@ import Data.Time.Calendar
|
||||
import Data.Time.Clock
|
||||
import Data.Time.Format
|
||||
import Data.Time.LocalTime
|
||||
#if !(MIN_VERSION_time(1,5,0))
|
||||
import System.Locale (defaultTimeLocale)
|
||||
#endif
|
||||
import Text.Printf
|
||||
|
||||
import Hledger.Utils
|
||||
@ -136,11 +133,7 @@ tests_Timeclock = tests "Timeclock" [
|
||||
yesterday = prevday today
|
||||
clockin = TimeclockEntry nullsourcepos In
|
||||
mktime d = LocalTime d . fromMaybe midnight .
|
||||
#if MIN_VERSION_time(1,5,0)
|
||||
parseTimeM True defaultTimeLocale "%H:%M:%S"
|
||||
#else
|
||||
parseTime defaultTimeLocale "%H:%M:%S"
|
||||
#endif
|
||||
showtime = formatTime defaultTimeLocale "%H:%M"
|
||||
txndescs = map (T.unpack . tdescription) . timeclockEntriesToTransactions now
|
||||
future = utcToLocalTime tz $ addUTCTime 100 now'
|
||||
|
||||
@ -11,7 +11,6 @@ A reader for CSV data, using an extra rules file to help interpret the data.
|
||||
-- stack haddock hledger-lib --fast --no-haddock-deps --haddock-arguments='--ignore-all-exports' --open
|
||||
|
||||
--- ** language
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE MultiWayIf #-}
|
||||
@ -61,12 +60,7 @@ import qualified Data.Text as T
|
||||
import qualified Data.Text.Encoding as T
|
||||
import qualified Data.Text.IO as T
|
||||
import Data.Time.Calendar (Day)
|
||||
#if MIN_VERSION_time(1,5,0)
|
||||
import Data.Time.Format (parseTimeM, defaultTimeLocale)
|
||||
#else
|
||||
import Data.Time.Format (parseTime)
|
||||
import System.Locale (defaultTimeLocale)
|
||||
#endif
|
||||
import Safe
|
||||
import System.Directory (doesFileExist)
|
||||
import System.FilePath
|
||||
@ -1229,13 +1223,7 @@ csvFieldValue rules record fieldname = do
|
||||
parseDateWithCustomOrDefaultFormats :: Maybe DateFormat -> String -> Maybe Day
|
||||
parseDateWithCustomOrDefaultFormats mformat s = asum $ map parsewith formats
|
||||
where
|
||||
parsetime =
|
||||
#if MIN_VERSION_time(1,5,0)
|
||||
parseTimeM True
|
||||
#else
|
||||
parseTime
|
||||
#endif
|
||||
parsewith = flip (parsetime defaultTimeLocale) s
|
||||
parsewith = flip (parseTimeM True defaultTimeLocale) s
|
||||
formats = maybe
|
||||
["%Y/%-m/%-d"
|
||||
,"%Y-%-m-%-d"
|
||||
|
||||
@ -33,11 +33,7 @@ import System.FilePath
|
||||
import System.FSNotify
|
||||
import Brick
|
||||
|
||||
#if MIN_VERSION_brick(0,16,0)
|
||||
import qualified Brick.BChan as BC
|
||||
#else
|
||||
import Control.Concurrent.Chan (newChan, writeChan)
|
||||
#endif
|
||||
|
||||
import Hledger
|
||||
import Hledger.Cli hiding (progname,prognameandversion)
|
||||
@ -50,13 +46,11 @@ import Hledger.UI.RegisterScreen
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
||||
#if MIN_VERSION_brick(0,16,0)
|
||||
newChan :: IO (BC.BChan a)
|
||||
newChan = BC.newBChan 10
|
||||
|
||||
writeChan :: BC.BChan a -> a -> IO ()
|
||||
writeChan = BC.writeBChan
|
||||
#endif
|
||||
|
||||
|
||||
main :: IO ()
|
||||
|
||||
@ -1,6 +1,5 @@
|
||||
{- | UIState operations. -}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
@ -8,9 +7,6 @@
|
||||
module Hledger.UI.UIState
|
||||
where
|
||||
|
||||
#if !MIN_VERSION_brick(0,19,0)
|
||||
import Brick
|
||||
#endif
|
||||
import Brick.Widgets.Edit
|
||||
import Data.List
|
||||
import Data.Text.Zipper (gotoEOL)
|
||||
@ -308,11 +304,7 @@ getDepth UIState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=ropts}}} = depth_ rop
|
||||
showMinibuffer :: UIState -> UIState
|
||||
showMinibuffer ui = setMode (Minibuffer e) ui
|
||||
where
|
||||
#if MIN_VERSION_brick(0,19,0)
|
||||
e = applyEdit gotoEOL $ editor MinibufferEditor (Just 1) oldq
|
||||
#else
|
||||
e = applyEdit gotoEOL $ editor MinibufferEditor (str . unlines) (Just 1) oldq
|
||||
#endif
|
||||
oldq = query_ $ reportopts_ $ cliopts_ $ aopts ui
|
||||
|
||||
-- | Close the minibuffer, discarding any edit in progress.
|
||||
|
||||
@ -180,12 +180,7 @@ helpHandle ui ev = do
|
||||
minibuffer :: Editor String Name -> Widget Name
|
||||
minibuffer ed =
|
||||
forceAttr ("border" <> "minibuffer") $
|
||||
hBox $
|
||||
#if MIN_VERSION_brick(0,19,0)
|
||||
[txt "filter: ", renderEditor (str . unlines) True ed]
|
||||
#else
|
||||
[txt "filter: ", renderEditor True ed]
|
||||
#endif
|
||||
hBox [txt "filter: ", renderEditor (str . unlines) True ed]
|
||||
|
||||
borderQueryStr :: String -> Widget Name
|
||||
borderQueryStr "" = str ""
|
||||
|
||||
@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE ParallelListComp, CPP #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE ParallelListComp #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-|
|
||||
|
||||
The @roi@ command prints internal rate of return and time-weighted rate of return for and investment.
|
||||
@ -205,15 +205,10 @@ internalRateOfReturn showCashFlow prettyTables (OneSpan spanBegin spanEnd valueB
|
||||
-- 0% is always a solution, so require at least something here
|
||||
case totalCF of
|
||||
[] -> return 0
|
||||
_ ->
|
||||
case ridders
|
||||
#if MIN_VERSION_math_functions(0,3,0)
|
||||
(RiddersParam 100 (AbsTol 0.00001))
|
||||
#else
|
||||
0.00001
|
||||
#endif
|
||||
(0.000000000001,10000) (interestSum spanEnd totalCF) of
|
||||
Root rate -> return ((rate-1)*100)
|
||||
_ -> case ridders (RiddersParam 100 (AbsTol 0.00001))
|
||||
(0.000000000001,10000)
|
||||
(interestSum spanEnd totalCF) of
|
||||
Root rate -> return ((rate-1)*100)
|
||||
NotBracketed -> error' "Error: No solution -- not bracketed." -- PARTIAL:
|
||||
SearchFailed -> error' "Error: Failed to find solution."
|
||||
|
||||
|
||||
Loading…
Reference in New Issue
Block a user