cln: Derive more instances in Hledger.Data.Types to reduce orphans.

Also clean up some outdated or inaccurate comments.
This commit is contained in:
Stephen Morgan 2021-08-12 13:29:31 +10:00 committed by Simon Michael
parent 993d0b5c54
commit 912b5e6c23
4 changed files with 11 additions and 48 deletions

View File

@ -43,7 +43,6 @@ exchange rates.
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
module Hledger.Data.Amount ( module Hledger.Data.Amount (
-- * Amount -- * Amount
@ -166,8 +165,6 @@ import Hledger.Data.Types
import Hledger.Data.Commodity import Hledger.Data.Commodity
import Hledger.Utils import Hledger.Utils
deriving instance Show MarketPrice
-- | Options for the display of Amount and MixedAmount. -- | Options for the display of Amount and MixedAmount.
data AmountDisplayOpts = AmountDisplayOpts data AmountDisplayOpts = AmountDisplayOpts

View File

@ -107,7 +107,7 @@ import Data.Foldable (toList)
import Data.Function ((&)) import Data.Function ((&))
import qualified Data.HashTable.Class as H (toList) import qualified Data.HashTable.Class as H (toList)
import qualified Data.HashTable.ST.Cuckoo as H import qualified Data.HashTable.ST.Cuckoo as H
import Data.List ((\\), find, foldl', sortOn) import Data.List ((\\), find, foldl', sortBy, sortOn)
import Data.List.Extra (nubSort) import Data.List.Extra (nubSort)
import qualified Data.Map.Strict as M import qualified Data.Map.Strict as M
import Data.Maybe (catMaybes, fromJust, fromMaybe, isJust, mapMaybe, maybeToList) import Data.Maybe (catMaybes, fromJust, fromMaybe, isJust, mapMaybe, maybeToList)
@ -129,14 +129,9 @@ import Hledger.Data.Transaction
import Hledger.Data.TransactionModifier import Hledger.Data.TransactionModifier
import Hledger.Data.Posting import Hledger.Data.Posting
import Hledger.Query import Hledger.Query
import Data.List (sortBy)
-- try to make Journal ppShow-compatible
-- instance Show ClockTime where
-- show t = "<ClockTime>"
-- deriving instance Show Journal -- deriving instance Show Journal
instance Show Journal where instance Show Journal where
show j show j
| debugLevel < 3 = printf "Journal %s with %d transactions, %d accounts" | debugLevel < 3 = printf "Journal %s with %d transactions, %d accounts"

View File

@ -2,28 +2,10 @@
JSON instances. Should they be in Types.hs ? JSON instances. Should they be in Types.hs ?
-} -}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
--{-# LANGUAGE DataKinds #-}
--{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
--{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
--{-# LANGUAGE NamedFieldPuns #-}
--{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
--{-# LANGUAGE PolyKinds #-} {-# LANGUAGE RecordWildCards #-}
--{-# LANGUAGE QuasiQuotes #-}
--{-# LANGUAGE QuasiQuotes #-}
--{-# LANGUAGE Rank2Types #-}
--{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
--{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
--{-# LANGUAGE TemplateHaskell #-}
--{-# LANGUAGE TypeFamilies #-}
--{-# LANGUAGE TypeOperators #-}
module Hledger.Data.Json ( module Hledger.Data.Json (
-- * Instances -- * Instances
@ -42,7 +24,6 @@ import Data.Decimal (DecimalRaw(..), roundTo)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TB import qualified Data.Text.Lazy.Builder as TB
import GHC.Generics (Generic)
import Hledger.Data.Types import Hledger.Data.Types
import Hledger.Data.Amount (amountsRaw, mixed) import Hledger.Data.Amount (amountsRaw, mixed)
@ -172,7 +153,6 @@ accountKV a =
, "asubs" .= ([]::[Account]) , "asubs" .= ([]::[Account])
] ]
deriving instance Generic (Ledger)
instance ToJSON Ledger instance ToJSON Ledger
-- From JSON -- From JSON
@ -216,9 +196,6 @@ instance FromJSON Account
-- $(deriveFromJSON defaultOptions ''DecimalRaw) -- works; requires TH, but gives better parse error messages -- $(deriveFromJSON defaultOptions ''DecimalRaw) -- works; requires TH, but gives better parse error messages
-- --
-- https://github.com/PaulJohnson/Haskell-Decimal/issues/6 -- https://github.com/PaulJohnson/Haskell-Decimal/issues/6
--deriving instance Generic Decimal
--instance FromJSON Decimal
deriving instance Generic (DecimalRaw a)
instance FromJSON (DecimalRaw Integer) instance FromJSON (DecimalRaw Integer)
-- --
-- @simonmichael, I think the code in your first comment should work if it compiles—though “work” doesnt mean you can parse a JSON number directly into a `Decimal` using the generic instance, as youve discovered. -- @simonmichael, I think the code in your first comment should work if it compiles—though “work” doesnt mean you can parse a JSON number directly into a `Decimal` using the generic instance, as youve discovered.

View File

@ -27,7 +27,7 @@ module Hledger.Data.Types
where where
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Data.Decimal (Decimal) import Data.Decimal (Decimal, DecimalRaw(..))
import Data.Default (Default(..)) import Data.Default (Default(..))
import Data.Functor (($>)) import Data.Functor (($>))
import Data.List (intercalate) import Data.List (intercalate)
@ -172,6 +172,7 @@ type Quantity = Decimal
instance ToMarkup Quantity instance ToMarkup Quantity
where where
toMarkup = toMarkup . show toMarkup = toMarkup . show
deriving instance Generic (DecimalRaw a)
-- | An amount's per-unit or total cost/selling price in another -- | An amount's per-unit or total cost/selling price in another
-- commodity, as recorded in the journal entry eg with @ or @@. -- commodity, as recorded in the journal entry eg with @ or @@.
@ -390,10 +391,6 @@ data GenericSourcePos = GenericSourcePos FilePath Int Int -- ^ file path, 1-b
| JournalSourcePos FilePath (Int, Int) -- ^ file path, inclusive range of 1-based line numbers (first, last). | JournalSourcePos FilePath (Int, Int) -- ^ file path, inclusive range of 1-based line numbers (first, last).
deriving (Eq, Read, Show, Ord, Generic) deriving (Eq, Read, Show, Ord, Generic)
--{-# ANN Transaction "HLint: ignore" #-}
-- Ambiguous type variable p0 arising from an annotation
-- prevents the constraint (Data p0) from being solved.
-- Probable fix: use a type annotation to specify what p0 should be.
data Transaction = Transaction { data Transaction = Transaction {
tindex :: Integer, -- ^ this transaction's 1-based position in the transaction stream, or 0 when not available tindex :: Integer, -- ^ this transaction's 1-based position in the transaction stream, or 0 when not available
tprecedingcomment :: Text, -- ^ any comment lines immediately preceding this transaction tprecedingcomment :: Text, -- ^ any comment lines immediately preceding this transaction
@ -425,7 +422,7 @@ nulltransactionmodifier = TransactionModifier{
-- | A transaction modifier transformation, which adds an extra posting -- | A transaction modifier transformation, which adds an extra posting
-- to the matched posting's transaction. -- to the matched posting's transaction.
-- Can be like a regular posting, or the amount can have the aismultiplier flag set, -- Can be like a regular posting, or can have the tmprIsMultiplier flag set,
-- indicating that it's a multiplier for the matched posting's amount. -- indicating that it's a multiplier for the matched posting's amount.
data TMPostingRule = TMPostingRule data TMPostingRule = TMPostingRule
{ tmprPosting :: Posting { tmprPosting :: Posting
@ -476,7 +473,6 @@ data PriceDirective = PriceDirective {
,pdcommodity :: CommoditySymbol ,pdcommodity :: CommoditySymbol
,pdamount :: Amount ,pdamount :: Amount
} deriving (Eq,Ord,Generic,Show) } deriving (Eq,Ord,Generic,Show)
-- Show instance derived in Amount.hs (XXX why ?)
-- | A historical market price (exchange rate) from one commodity to another. -- | A historical market price (exchange rate) from one commodity to another.
-- A more concise form of a PriceDirective, without the amount display info. -- A more concise form of a PriceDirective, without the amount display info.
@ -485,8 +481,7 @@ data MarketPrice = MarketPrice {
,mpfrom :: CommoditySymbol -- ^ The commodity being converted from. ,mpfrom :: CommoditySymbol -- ^ The commodity being converted from.
,mpto :: CommoditySymbol -- ^ The commodity being converted to. ,mpto :: CommoditySymbol -- ^ The commodity being converted to.
,mprate :: Quantity -- ^ One unit of the "from" commodity is worth this quantity of the "to" commodity. ,mprate :: Quantity -- ^ One unit of the "from" commodity is worth this quantity of the "to" commodity.
} deriving (Eq,Ord,Generic) } deriving (Eq,Ord,Generic, Show)
-- Show instance derived in Amount.hs (XXX why ?)
-- additional valuation-related types in Valuation.hs -- additional valuation-related types in Valuation.hs
@ -592,7 +587,6 @@ data NormalSign = NormallyPositive | NormallyNegative deriving (Show, Eq)
-- tree-wise, since each one knows its parent and subs; the first -- tree-wise, since each one knows its parent and subs; the first
-- account is the root of the tree and always exists. -- account is the root of the tree and always exists.
data Ledger = Ledger { data Ledger = Ledger {
ljournal :: Journal, ljournal :: Journal
laccounts :: [Account] ,laccounts :: [Account]
} } deriving (Generic)