lib,cli,ui: Remove redundant Typeable and Data instances.

Also add some explicit import lists.
This commit is contained in:
Stephen Morgan 2020-08-31 14:56:38 +10:00
parent 01f5a92761
commit af31d6e140
15 changed files with 72 additions and 95 deletions

View File

@ -1,5 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-|
hledger's cmdargs modes parse command-line arguments to an
@ -28,17 +26,16 @@ module Hledger.Data.RawOptions (
)
where
import Data.Maybe
import Data.Data
import Data.Default
import Safe
import Data.Maybe (fromMaybe, isJust, mapMaybe)
import Data.Default (Default(..))
import Safe (headMay, lastMay, readDef)
import Hledger.Utils
-- | The result of running cmdargs: an association list of option names to string values.
newtype RawOpts = RawOpts { unRawOpts :: [(String,String)] }
deriving (Show, Data, Typeable)
deriving (Show)
instance Default RawOpts where def = RawOpts []
@ -61,6 +58,7 @@ boolopt = inRawOpts
-- for which the given predicate returns a Just value.
-- Useful for exclusive choice flags like --daily|--weekly|--quarterly...
--
-- >>> import Safe (readMay)
-- >>> choiceopt Just (RawOpts [("a",""), ("b",""), ("c","")])
-- Just "c"
-- >>> choiceopt (const Nothing) (RawOpts [("a","")])

View File

@ -17,7 +17,6 @@ For more detailed documentation on each type, see the corresponding modules.
-}
-- {-# LANGUAGE DeriveAnyClass #-} -- https://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html#v:rnf
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
@ -30,7 +29,6 @@ where
import GHC.Generics (Generic)
import Control.DeepSeq (NFData)
import Data.Data
import Data.Decimal
import Data.Default
import Data.Functor (($>))
@ -77,7 +75,7 @@ data SmartInterval = Day | Week | Month | Quarter | Year deriving (Show)
data WhichDate = PrimaryDate | SecondaryDate deriving (Eq,Show)
data DateSpan = DateSpan (Maybe Day) (Maybe Day) deriving (Eq,Ord,Data,Generic,Typeable)
data DateSpan = DateSpan (Maybe Day) (Maybe Day) deriving (Eq,Ord,Generic)
instance Default DateSpan where def = DateSpan Nothing Nothing
@ -105,7 +103,7 @@ data Period =
| PeriodFrom Day
| PeriodTo Day
| PeriodAll
deriving (Eq,Ord,Show,Data,Generic,Typeable)
deriving (Eq,Ord,Show,Generic)
instance Default Period where def = PeriodAll
@ -116,7 +114,7 @@ instance Default Period where def = PeriodAll
-- MonthLong
-- QuarterLong
-- YearLong
-- deriving (Eq,Ord,Show,Data,Generic,Typeable)
-- deriving (Eq,Ord,Show,Generic)
-- Ways in which a period can be divided into subperiods.
data Interval =
@ -133,7 +131,7 @@ data Interval =
-- WeekOfYear Int
-- MonthOfYear Int
-- QuarterOfYear Int
deriving (Eq,Show,Ord,Data,Generic,Typeable)
deriving (Eq,Show,Ord,Generic)
instance Default Interval where def = NoInterval
@ -148,7 +146,7 @@ data AccountType =
| Revenue
| Expense
| Cash -- ^ a subtype of Asset - liquid assets to show in cashflow report
deriving (Show,Eq,Ord,Data,Generic)
deriving (Show,Eq,Ord,Generic)
instance NFData AccountType
@ -164,17 +162,16 @@ instance NFData AccountType
data AccountAlias = BasicAlias AccountName AccountName
| RegexAlias Regexp Replacement
deriving (Eq, Read, Show, Ord, Data, Generic, Typeable)
deriving (Eq, Read, Show, Ord, Generic)
-- instance NFData AccountAlias
data Side = L | R deriving (Eq,Show,Read,Ord,Typeable,Data,Generic)
data Side = L | R deriving (Eq,Show,Read,Ord,Generic)
instance NFData Side
-- | The basic numeric type used in amounts.
type Quantity = Decimal
deriving instance Data Quantity
-- The following is for hledger-web, and requires blaze-markup.
-- Doing it here avoids needing a matching flag on the hledger-web package.
instance ToMarkup Quantity
@ -185,7 +182,7 @@ instance ToMarkup Quantity
-- commodity, as recorded in the journal entry eg with @ or @@.
-- Docs call this "transaction price". The amount is always positive.
data AmountPrice = UnitPrice Amount | TotalPrice Amount
deriving (Eq,Ord,Typeable,Data,Generic,Show)
deriving (Eq,Ord,Generic,Show)
instance NFData AmountPrice
@ -196,7 +193,7 @@ data AmountStyle = AmountStyle {
asprecision :: !AmountPrecision, -- ^ number of digits displayed after the decimal point
asdecimalpoint :: Maybe Char, -- ^ character used as decimal point: period or comma. Nothing means "unspecified, use default"
asdigitgroups :: Maybe DigitGroupStyle -- ^ style for displaying digit groups, if any
} deriving (Eq,Ord,Read,Typeable,Data,Generic)
} deriving (Eq,Ord,Read,Generic)
instance NFData AmountStyle
@ -209,7 +206,7 @@ instance Show AmountStyle where
(show asdecimalpoint)
(show asdigitgroups)
data AmountPrecision = Precision !Word8 | NaturalPrecision deriving (Eq,Ord,Read,Show,Typeable,Data,Generic)
data AmountPrecision = Precision !Word8 | NaturalPrecision deriving (Eq,Ord,Read,Show,Generic)
instance NFData AmountPrecision
@ -220,7 +217,7 @@ instance NFData AmountPrecision
-- the decimal point. The last group size is assumed to repeat. Eg,
-- comma between thousands is DigitGroups ',' [3].
data DigitGroupStyle = DigitGroups Char [Word8]
deriving (Eq,Ord,Read,Show,Typeable,Data,Generic)
deriving (Eq,Ord,Read,Show,Generic)
instance NFData DigitGroupStyle
@ -229,7 +226,7 @@ type CommoditySymbol = Text
data Commodity = Commodity {
csymbol :: CommoditySymbol,
cformat :: Maybe AmountStyle
} deriving (Show,Eq,Data,Generic) --,Ord,Typeable,Data,Generic)
} deriving (Show,Eq,Generic) --,Ord)
instance NFData Commodity
@ -240,16 +237,16 @@ data Amount = Amount {
-- in a TMPostingRule. In a regular Posting, should always be false.
astyle :: AmountStyle,
aprice :: Maybe AmountPrice -- ^ the (fixed, transaction-specific) price for this amount, if any
} deriving (Eq,Ord,Typeable,Data,Generic,Show)
} deriving (Eq,Ord,Generic,Show)
instance NFData Amount
newtype MixedAmount = Mixed [Amount] deriving (Eq,Ord,Typeable,Data,Generic,Show)
newtype MixedAmount = Mixed [Amount] deriving (Eq,Ord,Generic,Show)
instance NFData MixedAmount
data PostingType = RegularPosting | VirtualPosting | BalancedVirtualPosting
deriving (Eq,Show,Typeable,Data,Generic)
deriving (Eq,Show,Generic)
instance NFData PostingType
@ -261,7 +258,7 @@ type DateTag = (TagName, Day)
-- | The status of a transaction or posting, recorded with a status mark
-- (nothing, !, or *). What these mean is ultimately user defined.
data Status = Unmarked | Pending | Cleared
deriving (Eq,Ord,Bounded,Enum,Typeable,Data,Generic)
deriving (Eq,Ord,Bounded,Enum,Generic)
instance NFData Status
@ -312,7 +309,7 @@ data BalanceAssertion = BalanceAssertion {
batotal :: Bool, -- ^ disallow additional non-asserted commodities ?
bainclusive :: Bool, -- ^ include subaccounts when calculating the actual balance ?
baposition :: GenericSourcePos -- ^ the assertion's file position, for error reporting
} deriving (Eq,Typeable,Data,Generic,Show)
} deriving (Eq,Generic,Show)
instance NFData BalanceAssertion
@ -333,7 +330,7 @@ data Posting = Posting {
-- (eg its amount or price was inferred, or the account name was
-- changed by a pivot or budget report), this references the original
-- untransformed posting (which will have Nothing in this field).
} deriving (Typeable,Data,Generic)
} deriving (Generic)
instance NFData Posting
@ -363,7 +360,7 @@ instance Show Posting where
-- | The position of parse errors (eg), like parsec's SourcePos but generic.
data GenericSourcePos = GenericSourcePos FilePath Int Int -- ^ file path, 1-based line number and 1-based column number.
| JournalSourcePos FilePath (Int, Int) -- ^ file path, inclusive range of 1-based line numbers (first, last).
deriving (Eq, Read, Show, Ord, Data, Generic, Typeable)
deriving (Eq, Read, Show, Ord, Generic)
instance NFData GenericSourcePos
@ -383,7 +380,7 @@ data Transaction = Transaction {
tcomment :: Text, -- ^ this transaction's comment lines, as a single non-indented multi-line string
ttags :: [Tag], -- ^ tag names and values, extracted from the comment
tpostings :: [Posting] -- ^ this transaction's postings
} deriving (Eq,Typeable,Data,Generic,Show)
} deriving (Eq,Generic,Show)
instance NFData Transaction
@ -395,7 +392,7 @@ instance NFData Transaction
data TransactionModifier = TransactionModifier {
tmquerytxt :: Text,
tmpostingrules :: [TMPostingRule]
} deriving (Eq,Typeable,Data,Generic,Show)
} deriving (Eq,Generic,Show)
instance NFData TransactionModifier
@ -422,7 +419,7 @@ data PeriodicTransaction = PeriodicTransaction {
ptcomment :: Text,
pttags :: [Tag],
ptpostings :: [Posting]
} deriving (Eq,Typeable,Data,Generic) -- , Show in PeriodicTransaction.hs
} deriving (Eq,Generic) -- , Show in PeriodicTransaction.hs
nullperiodictransaction = PeriodicTransaction{
ptperiodexpr = ""
@ -438,7 +435,7 @@ nullperiodictransaction = PeriodicTransaction{
instance NFData PeriodicTransaction
data TimeclockCode = SetBalance | SetRequiredHours | In | Out | FinalOut deriving (Eq,Ord,Typeable,Data,Generic)
data TimeclockCode = SetBalance | SetRequiredHours | In | Out | FinalOut deriving (Eq,Ord,Generic)
instance NFData TimeclockCode
@ -448,7 +445,7 @@ data TimeclockEntry = TimeclockEntry {
tldatetime :: LocalTime,
tlaccount :: AccountName,
tldescription :: Text
} deriving (Eq,Ord,Typeable,Data,Generic)
} deriving (Eq,Ord,Generic)
instance NFData TimeclockEntry
@ -459,7 +456,7 @@ data PriceDirective = PriceDirective {
pddate :: Day
,pdcommodity :: CommoditySymbol
,pdamount :: Amount
} deriving (Eq,Ord,Typeable,Data,Generic,Show)
} deriving (Eq,Ord,Generic,Show)
-- Show instance derived in Amount.hs (XXX why ?)
instance NFData PriceDirective
@ -471,7 +468,7 @@ data MarketPrice = MarketPrice {
,mpfrom :: CommoditySymbol -- ^ The commodity being converted from.
,mpto :: CommoditySymbol -- ^ The commodity being converted to.
,mprate :: Quantity -- ^ One unit of the "from" commodity is worth this quantity of the "to" commodity.
} deriving (Eq,Ord,Typeable,Data,Generic)
} deriving (Eq,Ord,Generic)
-- Show instance derived in Amount.hs (XXX why ?)
instance NFData MarketPrice
@ -514,8 +511,6 @@ data Journal = Journal {
,jlastreadtime :: ClockTime -- ^ when this journal was last read from its file(s)
} deriving (Eq, Generic)
deriving instance Data ClockTime
deriving instance Typeable ClockTime
deriving instance Generic ClockTime
instance NFData ClockTime
-- instance NFData Journal
@ -535,7 +530,7 @@ data AccountDeclarationInfo = AccountDeclarationInfo {
,aditags :: [Tag] -- ^ tags extracted from the account comment, if any
,adideclarationorder :: Int -- ^ the order in which this account was declared,
-- relative to other account declarations, during parsing (1..)
} deriving (Eq,Show,Data,Generic)
} deriving (Eq,Show,Generic)
instance NFData AccountDeclarationInfo
@ -558,14 +553,14 @@ data Account = Account {
,anumpostings :: Int -- ^ the number of postings to this account
,aebalance :: MixedAmount -- ^ this account's balance, excluding subaccounts
,aibalance :: MixedAmount -- ^ this account's balance, including subaccounts
} deriving (Typeable, Data, Generic)
} deriving (Generic)
-- | Whether an account's balance is normally a positive number (in
-- accounting terms, a debit balance) or a negative number (credit balance).
-- Assets and expenses are normally positive (debit), while liabilities, equity
-- and income are normally negative (credit).
-- https://en.wikipedia.org/wiki/Normal_balance
data NormalSign = NormallyPositive | NormallyNegative deriving (Show, Data, Eq)
data NormalSign = NormallyPositive | NormallyNegative deriving (Show, Eq)
-- | A Ledger has the journal it derives from, and the accounts
-- derived from that. Accounts are accessible both list-wise and

View File

@ -9,7 +9,7 @@ looking up historical market prices (exchange rates) between commodities.
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
{-# LANGUAGE DeriveGeneric #-}
module Hledger.Data.Valuation (
ValuationType(..)
@ -29,7 +29,6 @@ where
import Control.Applicative ((<|>))
import Control.DeepSeq (NFData)
import Data.Data
import Data.Decimal (roundTo)
import Data.Function ((&), on)
import Data.Graph.Inductive (Gr, Node, NodeMap, mkMapGraph, mkNode, lab, out, sp)
@ -60,7 +59,7 @@ data ValuationType =
| AtNow (Maybe CommoditySymbol) -- ^ convert to default or given valuation commodity, using current market prices
| AtDate Day (Maybe CommoditySymbol) -- ^ convert to default or given valuation commodity, using market prices on some date
| AtDefault (Maybe CommoditySymbol) -- ^ works like AtNow in single period reports, like AtEnd in multiperiod reports
deriving (Show,Data,Eq) -- Typeable
deriving (Show,Eq)
-- | A snapshot of the known exchange rates between commodity pairs at a given date,
-- as a graph allowing fast lookup and path finding, along with some helper data.

View File

@ -10,7 +10,6 @@ transactions..) by various criteria, and a SimpleTextParser for query expressio
{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
@ -60,18 +59,17 @@ module Hledger.Query (
where
import Control.Applicative ((<|>), liftA2, many, optional)
import Data.Data
import Data.Either
import Data.List
import Data.Maybe
import Data.Either (partitionEithers)
import Data.List (partition)
import Data.Maybe (fromMaybe, isJust, mapMaybe)
#if !(MIN_VERSION_base(4,11,0))
import Data.Monoid ((<>))
#endif
import qualified Data.Text as T
import Data.Time.Calendar
import Data.Time.Calendar (Day, fromGregorian )
import Safe (readDef, readMay, maximumByMay, maximumMay, minimumMay)
import Text.Megaparsec (between, noneOf, sepBy)
import Text.Megaparsec.Char
import Text.Megaparsec.Char (char, string)
import Hledger.Utils hiding (words')
import Hledger.Data.Types
@ -105,7 +103,7 @@ data Query = Any -- ^ always match
-- and sometimes like a query option (for controlling display)
| Tag Regexp (Maybe Regexp) -- ^ match if a tag's name, and optionally its value, is matched by these respective regexps
-- matching the regexp if provided, exists
deriving (Eq,Show,Data,Typeable)
deriving (Eq,Show)
-- | Construct a payee tag
payeeTag :: Maybe String -> Either RegexError Query
@ -118,14 +116,14 @@ noteTag = liftA2 Tag (toRegexCI_ "note") . maybe (pure Nothing) (fmap Just . toR
-- | A more expressive Ord, used for amt: queries. The Abs* variants
-- compare with the absolute value of a number, ignoring sign.
data OrdPlus = Lt | LtEq | Gt | GtEq | Eq | AbsLt | AbsLtEq | AbsGt | AbsGtEq | AbsEq
deriving (Show,Eq,Data,Typeable)
deriving (Show,Eq)
-- | A query option changes a query's/report's behaviour and output in some way.
data QueryOpt = QueryOptInAcctOnly AccountName -- ^ show an account register focussed on this account
| QueryOptInAcct AccountName -- ^ as above but include sub-accounts in the account register
-- | QueryOptCostBasis -- ^ show amounts converted to cost where possible
-- | QueryOptDate2 -- ^ show secondary dates instead of primary dates
deriving (Show, Eq, Data, Typeable)
deriving (Show, Eq)
-- parsing

View File

@ -14,7 +14,6 @@ Some of these might belong in Hledger.Read.JournalReader or Hledger.Read.
--- ** language
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
@ -116,32 +115,33 @@ where
--- ** imports
import Prelude ()
import "base-compat-batteries" Prelude.Compat hiding (fail, readFile)
import Control.Applicative.Permutations (runPermutation, toPermutationWithDefault)
import qualified "base-compat-batteries" Control.Monad.Fail.Compat as Fail (fail)
import Control.Monad.Except (ExceptT(..), runExceptT, throwError)
import Control.Monad.State.Strict hiding (fail)
import Data.Bifunctor (bimap, second)
import Data.Char
import Data.Data
import Data.Char (digitToInt, isDigit, isSpace)
import Data.Decimal (DecimalRaw (Decimal), Decimal)
import Data.Default
import Data.Default (Default(..))
import Data.Function ((&))
import Data.Functor.Identity
import Data.Functor.Identity (Identity)
import "base-compat-batteries" Data.List.Compat
import Data.List.NonEmpty (NonEmpty(..))
import Data.Maybe
import Data.Maybe (catMaybes, fromMaybe, isJust, listToMaybe)
import qualified Data.Map as M
import qualified Data.Semigroup as Sem
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time.Calendar
import Data.Time.LocalTime
import Data.Time.Calendar (Day, fromGregorianValid, toGregorian)
import Data.Time.LocalTime (LocalTime(..), TimeOfDay(..))
import Data.Word (Word8)
import System.Time (getClockTime)
import Text.Megaparsec
import Text.Megaparsec.Char
import Text.Megaparsec.Char (char, char', digitChar, newline, string)
import Text.Megaparsec.Char.Lexer (decimal)
import Text.Megaparsec.Custom
import Control.Applicative.Permutations
(FinalParseError, attachSource, customErrorBundlePretty,
finalErrorBundlePretty, parseErrorAt, parseErrorAtRegion)
import Hledger.Data
import Hledger.Utils hiding (match)
@ -194,7 +194,7 @@ data InputOpts = InputOpts {
,new_save_ :: Bool -- ^ save latest new transactions state for next time
,pivot_ :: String -- ^ use the given field's value as the account name
,auto_ :: Bool -- ^ generate automatic postings when journal is parsed
} deriving (Show, Data) --, Typeable)
} deriving (Show)
instance Default InputOpts where def = definputopts

View File

@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, RecordWildCards, DeriveDataTypeable, FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings, RecordWildCards, FlexibleInstances #-}
{-|
Generate several common kinds of report from a journal, as \"*Report\" -

View File

@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, RecordWildCards, DeriveDataTypeable, FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings, RecordWildCards, FlexibleInstances #-}
{-|
An account-centric transactions report.

View File

@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, RecordWildCards, DeriveDataTypeable, FlexibleInstances, ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings, RecordWildCards, FlexibleInstances, ScopedTypeVariables #-}
{-|
Journal entries report, used by the print command.

View File

@ -4,7 +4,6 @@ Postings report, used by the register command.
-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

View File

@ -4,7 +4,6 @@ Options common to most hledger reports.
-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
@ -49,14 +48,12 @@ module Hledger.Reports.ReportOptions (
where
import Control.Applicative ((<|>))
import Data.Data (Data)
import Data.List.Extra (nubSort)
import Data.Maybe
import Data.Maybe (fromMaybe, isJust)
import qualified Data.Text as T
import Data.Typeable (Typeable)
import Data.Time.Calendar
import Data.Default
import Safe
import Data.Time.Calendar (Day, addDays, fromGregorian)
import Data.Default (Default(..))
import Safe (lastDef, lastMay)
import System.Console.ANSI (hSupportsANSIColor)
import System.Environment (lookupEnv)
@ -76,12 +73,12 @@ data BalanceType = PeriodChange -- ^ The change of balance in each period.
| HistoricalBalance -- ^ The historical ending balance, including the effect of
-- all postings before the report period. Unless altered by,
-- a query, this is what you would see on a bank statement.
deriving (Eq,Show,Data,Typeable)
deriving (Eq,Show)
instance Default BalanceType where def = PeriodChange
-- | Should accounts be displayed: in the command's default style, hierarchically, or as a flat list ?
data AccountListMode = ALFlat | ALTree deriving (Eq, Show, Data, Typeable)
data AccountListMode = ALFlat | ALTree deriving (Eq, Show)
instance Default AccountListMode where def = ALFlat
@ -140,7 +137,7 @@ data ReportOpts = ReportOpts {
-- TERM and existence of NO_COLOR environment variables.
,forecast_ :: Maybe DateSpan
,transpose_ :: Bool
} deriving (Show, Data, Typeable)
} deriving (Show)
instance Default ReportOpts where def = defreportopts

View File

@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, RecordWildCards, DeriveDataTypeable, FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings, RecordWildCards, FlexibleInstances #-}
{-|
A transactions report. Like an EntriesReport, but with more

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
@ -80,7 +79,6 @@ import Control.Monad (foldM)
import Data.Aeson (ToJSON(..), Value(String))
import Data.Array ((!), elems, indices)
import Data.Char (isDigit)
import Data.Data (Data(..), mkNoRepType)
import Data.List (foldl')
import Data.MemoUgly (memo)
import qualified Data.Text as T
@ -124,11 +122,6 @@ instance Read Regexp where
(m,t) <- readsPrec (app_prec+1) s]) r
where app_prec = 10
instance Data Regexp where
toConstr _ = error' "No toConstr for Regex"
gunfold _ _ = error' "No gunfold for Regex"
dataTypeOf _ = mkNoRepType "Hledger.Utils.Regex"
instance ToJSON Regexp where
toJSON (Regexp s _) = String . T.pack $ "Regexp " ++ s
toJSON (RegexpCI s _) = String . T.pack $ "RegexpCI " ++ s

View File

@ -1,5 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE LambdaCase #-}
{-|

View File

@ -5,7 +5,7 @@ related utilities used by hledger commands.
-}
{-# LANGUAGE CPP, ScopedTypeVariables, DeriveDataTypeable, FlexibleContexts, TypeFamilies, OverloadedStrings, PackageImports #-}
{-# LANGUAGE CPP, ScopedTypeVariables, FlexibleContexts, TypeFamilies, OverloadedStrings, PackageImports #-}
module Hledger.Cli.CliOptions (
@ -413,7 +413,7 @@ data CliOpts = CliOpts {
-- 1. the COLUMNS env var, if set
-- 2. the width reported by the terminal, if supported
-- 3. the default (80)
} deriving (Show, Data, Typeable)
} deriving (Show)
instance Default CliOpts where def = defcliopts

View File

@ -3,7 +3,7 @@ A history-aware add command to help with data entry.
|-}
{-# OPTIONS_GHC -fno-warn-missing-signatures -fno-warn-unused-do-bind #-}
{-# LANGUAGE ScopedTypeVariables, DeriveDataTypeable, RecordWildCards, TypeOperators, FlexibleContexts, OverloadedStrings, PackageImports, LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables, RecordWildCards, TypeOperators, FlexibleContexts, OverloadedStrings, PackageImports, LambdaCase #-}
{-# LANGUAGE TemplateHaskell #-}
module Hledger.Cli.Commands.Add (
@ -32,7 +32,6 @@ import Data.Text (Text)
import qualified Data.Text as T
import Data.Time.Calendar (Day)
import Data.Time.Format (formatTime, defaultTimeLocale, iso8601DateFormat)
import Data.Typeable (Typeable)
import Safe (headDef, headMay, atMay)
import System.Console.CmdArgs.Explicit
import System.Console.Haskeline (runInputT, defaultSettings, setComplete)
@ -65,7 +64,7 @@ data EntryState = EntryState {
,esJournal :: Journal -- ^ the journal we are adding to
,esSimilarTransaction :: Maybe Transaction -- ^ the most similar historical txn
,esPostings :: [Posting] -- ^ postings entered so far in the current txn
} deriving (Show,Typeable)
} deriving (Show)
defEntryState = EntryState {
esOpts = defcliopts
@ -77,10 +76,10 @@ defEntryState = EntryState {
,esPostings = []
}
data RestartTransactionException = RestartTransactionException deriving (Typeable,Show)
data RestartTransactionException = RestartTransactionException deriving (Show)
instance Exception RestartTransactionException
-- data ShowHelpException = ShowHelpException deriving (Typeable,Show)
-- data ShowHelpException = ShowHelpException deriving (Show)
-- instance Exception ShowHelpException
-- | Read multiple transactions from the console, prompting for each