derive NFData (and Generic) for all types

so we can benchmark things more easily with criterion.

As well as NFData, the Generic instance and a bunch more GHC extensions
seemed necessary. This is a little scary, impact unknown.
This commit is contained in:
Simon Michael 2015-06-28 16:16:20 -07:00
parent 42d452f99c
commit 790d42bfa4

View File

@ -1,4 +1,4 @@
{-# LANGUAGE CPP, DeriveDataTypeable, StandaloneDeriving, TypeSynonymInstances, FlexibleInstances #-}
{-# LANGUAGE CPP, DeriveDataTypeable, StandaloneDeriving, DeriveAnyClass, DeriveGeneric, TypeSynonymInstances, FlexibleInstances #-}
{-|
Most data types are defined here to avoid import cycles.
@ -19,6 +19,8 @@ For more detailed documentation on each type, see the corresponding modules.
module Hledger.Data.Types
where
import GHC.Generics (Generic)
import Control.DeepSeq (NFData)
import Control.Monad.Except (ExceptT)
import Data.Data
#ifndef DOUBLE
@ -29,7 +31,6 @@ import qualified Data.Map as M
import Data.Time.Calendar
import Data.Time.LocalTime
import System.Time (ClockTime(..))
import Text.Parsec.Pos
import Hledger.Utils.Regex
@ -38,28 +39,21 @@ type SmartDate = (String,String,String)
data WhichDate = PrimaryDate | SecondaryDate deriving (Eq,Show)
data DateSpan = DateSpan (Maybe Day) (Maybe Day) deriving (Eq,Ord,Data,Typeable)
data DateSpan = DateSpan (Maybe Day) (Maybe Day) deriving (Eq,Ord,Data,NFData,Generic,Typeable)
data Interval = NoInterval
| Days Int | Weeks Int | Months Int | Quarters Int | Years Int
| DayOfMonth Int | DayOfWeek Int
-- WeekOfYear Int | MonthOfYear Int | QuarterOfYear Int
deriving (Eq,Show,Ord,Data,Typeable)
deriving (Eq,Show,Ord,Data,NFData,Generic,Typeable)
type AccountName = String
data AccountAlias = BasicAlias AccountName AccountName
| RegexAlias Regexp Replacement
deriving (
Eq
,Read
,Show
,Ord
,Data
,Typeable
)
deriving (Eq, Read, Show, Ord, Data, NFData,Generic, Typeable)
data Side = L | R deriving (Eq,Show,Read,Ord,Typeable,Data)
data Side = L | R deriving (Eq,Show,Read,Ord,Typeable,Data,NFData,Generic)
type Commodity = String
@ -82,7 +76,7 @@ numberRepresentation = "Decimal"
-- | An amount's price (none, per unit, or total) in another commodity.
-- Note the price should be a positive number, although this is not enforced.
data Price = NoPrice | UnitPrice Amount | TotalPrice Amount deriving (Eq,Ord,Typeable,Data)
data Price = NoPrice | UnitPrice Amount | TotalPrice Amount deriving (Eq,Ord,Typeable,Data,NFData,Generic)
-- | Display style for an amount.
data AmountStyle = AmountStyle {
@ -91,7 +85,7 @@ data AmountStyle = AmountStyle {
asprecision :: Int, -- ^ 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,Show,Typeable,Data)
} deriving (Eq,Ord,Read,Show,Typeable,Data,NFData,Generic)
-- | A style for displaying digit groups in the integer part of a
-- floating point number. It consists of the character used to
@ -100,24 +94,24 @@ data AmountStyle = AmountStyle {
-- the decimal point. The last group size is assumed to repeat. Eg,
-- comma between thousands is DigitGroups ',' [3].
data DigitGroupStyle = DigitGroups Char [Int]
deriving (Eq,Ord,Read,Show,Typeable,Data)
deriving (Eq,Ord,Read,Show,Typeable,Data,NFData,Generic)
data Amount = Amount {
acommodity :: Commodity,
aquantity :: Quantity,
aprice :: Price, -- ^ the (fixed) price for this amount, if any
astyle :: AmountStyle
} deriving (Eq,Ord,Typeable,Data)
} deriving (Eq,Ord,Typeable,Data,NFData,Generic)
newtype MixedAmount = Mixed [Amount] deriving (Eq,Ord,Typeable,Data)
newtype MixedAmount = Mixed [Amount] deriving (Eq,Ord,Typeable,Data,NFData,Generic)
data PostingType = RegularPosting | VirtualPosting | BalancedVirtualPosting
deriving (Eq,Show,Typeable,Data)
deriving (Eq,Show,Typeable,Data,NFData,Generic)
type Tag = (String, String) -- ^ A tag name and (possibly empty) value.
data ClearedStatus = Uncleared | Pending | Cleared
deriving (Eq,Ord,Typeable,Data)
deriving (Eq,Ord,Typeable,Data,NFData,Generic)
instance Show ClearedStatus where -- custom show
show Uncleared = "" -- a bad idea
@ -136,7 +130,7 @@ data Posting = Posting {
pbalanceassertion :: Maybe MixedAmount, -- ^ optional: the expected balance in the account after this posting
ptransaction :: Maybe Transaction -- ^ this posting's parent transaction (co-recursive types).
-- Tying this knot gets tedious, Maybe makes it easier/optional.
} deriving (Typeable,Data)
} deriving (Typeable,Data,NFData,Generic)
-- The equality test for postings ignores the parent transaction's
-- identity, to avoid infinite loops.
@ -146,7 +140,7 @@ instance Eq Posting where
-- | The position of parse errors (eg), like parsec's SourcePos but generic.
-- File name, 1-based line number and 1-based column number.
data GenericSourcePos = GenericSourcePos FilePath Int Int
deriving (Eq, Read, Show, Ord, Data, Typeable)
deriving (Eq, Read, Show, Ord, Data, NFData, Generic, Typeable)
data Transaction = Transaction {
tsourcepos :: GenericSourcePos,
@ -159,19 +153,19 @@ data Transaction = Transaction {
ttags :: [Tag], -- ^ tag names and values, extracted from the comment
tpostings :: [Posting], -- ^ this transaction's postings
tpreceding_comment_lines :: String -- ^ any comment lines immediately preceding this transaction
} deriving (Eq,Typeable,Data)
} deriving (Eq,Typeable,Data,NFData,Generic)
data ModifierTransaction = ModifierTransaction {
mtvalueexpr :: String,
mtpostings :: [Posting]
} deriving (Eq,Typeable,Data)
} deriving (Eq,Typeable,Data,NFData,Generic)
data PeriodicTransaction = PeriodicTransaction {
ptperiodicexpr :: String,
ptpostings :: [Posting]
} deriving (Eq,Typeable,Data)
} deriving (Eq,Typeable,Data,NFData,Generic)
data TimeLogCode = SetBalance | SetRequiredHours | In | Out | FinalOut deriving (Eq,Ord,Typeable,Data)
data TimeLogCode = SetBalance | SetRequiredHours | In | Out | FinalOut deriving (Eq,Ord,Typeable,Data,NFData,Generic)
data TimeLogEntry = TimeLogEntry {
tlsourcepos :: GenericSourcePos,
@ -179,13 +173,13 @@ data TimeLogEntry = TimeLogEntry {
tldatetime :: LocalTime,
tlaccount :: String,
tldescription :: String
} deriving (Eq,Ord,Typeable,Data)
} deriving (Eq,Ord,Typeable,Data,NFData,Generic)
data HistoricalPrice = HistoricalPrice {
hdate :: Day,
hcommodity :: Commodity,
hamount :: Amount
} deriving (Eq,Typeable,Data) -- & Show (in Amount.hs)
} deriving (Eq,Typeable,Data, NFData,Generic) -- & Show (in Amount.hs)
type Year = Integer
@ -200,10 +194,12 @@ data JournalContext = Ctx {
-- specified with "account" directive(s). Concatenated, these
-- are the account prefix prepended to parsed account names.
, ctxAliases :: ![AccountAlias] -- ^ the current list of account name aliases in effect
} deriving (Read, Show, Eq, Data, Typeable)
} deriving (Read, Show, Eq, Data, Typeable, NFData,Generic)
deriving instance Data (ClockTime)
deriving instance Typeable (ClockTime)
deriving instance NFData (ClockTime)
deriving instance Generic (ClockTime)
data Journal = Journal {
jmodifiertxns :: [ModifierTransaction],
@ -219,7 +215,7 @@ data Journal = Journal {
-- order encountered.
filereadtime :: ClockTime, -- ^ when this journal was last read from its file(s)
jcommoditystyles :: M.Map Commodity AmountStyle -- ^ how to display amounts in each commodity
} deriving (Eq, Typeable, Data)
} deriving (Eq, Typeable, Data, NFData,Generic)
-- | A JournalUpdate is some transformation of a Journal. It can do I/O or
-- raise an error.