2019-12-17 04:15:24 +03:00
{-
JSON instances . Should they be in Types . hs ?
- }
2019-02-21 04:33:35 +03:00
{- # OPTIONS_GHC - fno - warn - orphans # -}
2020-06-07 00:53:09 +03:00
{- # LANGUAGE CPP # -}
2019-02-21 04:33:35 +03:00
--{-# LANGUAGE DataKinds #-}
--{-# LANGUAGE DeriveAnyClass #-}
{- # LANGUAGE DeriveGeneric # -}
--{-# LANGUAGE FlexibleContexts #-}
{- # LANGUAGE FlexibleInstances # -}
--{-# LANGUAGE NamedFieldPuns #-}
--{-# LANGUAGE OverloadedStrings #-}
{- # LANGUAGE OverloadedStrings # -}
--{-# LANGUAGE PolyKinds #-}
--{-# LANGUAGE QuasiQuotes #-}
--{-# LANGUAGE QuasiQuotes #-}
--{-# LANGUAGE Rank2Types #-}
--{-# LANGUAGE RankNTypes #-}
{- # LANGUAGE RecordWildCards # -}
--{-# LANGUAGE ScopedTypeVariables #-}
{- # LANGUAGE StandaloneDeriving # -}
--{-# LANGUAGE TemplateHaskell #-}
--{-# LANGUAGE TypeFamilies #-}
--{-# LANGUAGE TypeOperators #-}
2019-12-17 04:15:24 +03:00
module Hledger.Data.Json (
2019-02-21 04:33:35 +03:00
-- * Instances
-- * Utilities
2020-06-06 22:33:06 +03:00
toJsonText
2019-02-21 04:33:35 +03:00
, writeJsonFile
2020-06-06 22:33:06 +03:00
, readJsonFile
2019-02-21 04:33:35 +03:00
) where
2020-06-07 00:53:09 +03:00
# if ! ( MIN_VERSION_base ( 4 , 13 , 0 ) )
import Data.Semigroup ( ( <> ) )
# endif
2019-02-21 04:33:35 +03:00
import Data.Aeson
2020-06-06 22:33:06 +03:00
import Data.Aeson.Encode.Pretty ( encodePrettyToTextBuilder )
2019-02-21 04:33:35 +03:00
--import Data.Aeson.TH
import qualified Data.ByteString.Lazy as BL
import Data.Decimal
import Data.Maybe
2020-06-06 22:33:06 +03:00
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.IO as TL
2020-10-27 05:04:00 +03:00
import qualified Data.Text.Lazy.Builder as TB
2019-02-21 04:33:35 +03:00
import GHC.Generics ( Generic )
2019-12-17 04:16:04 +03:00
import System.Time ( ClockTime )
2019-02-21 04:33:35 +03:00
2019-12-17 04:15:24 +03:00
import Hledger.Data.Types
2019-02-21 04:33:35 +03:00
-- To JSON
instance ToJSON Status
instance ToJSON GenericSourcePos
2020-02-25 20:26:36 +03:00
-- https://github.com/simonmichael/hledger/issues/1195
2020-03-02 03:44:28 +03:00
-- The default JSON output for Decimal can contain 255-digit integers
-- (for repeating decimals caused by implicit transaction prices).
2020-02-25 20:26:36 +03:00
-- JSON output is intended to be consumed by diverse apps and
2020-03-02 03:44:28 +03:00
-- programming languages, which can't handle numbers like that.
-- From #1195:
2020-02-25 20:26:36 +03:00
--
-- > - JavaScript uses 64-bit IEEE754 numbers which can only accurately
-- > represent integers up to 9007199254740991 (i.e. a maximum of 15 digits).
-- > - Java’ s largest integers are limited to 18 digits.
-- > - Python 3 integers are unbounded.
-- > - Python 2 integers are limited to 18 digits like Java.
-- > - C and C++ number limits depend on platform — most platforms should
-- > be able to represent unsigned integers up to 64 bits, i.e. 19 digits.
--
2020-03-02 03:44:28 +03:00
-- What is the best compromise for both accuracy and practicality ?
-- For now, we provide both the maximum precision representation
-- (decimalPlaces & decimalMantissa), and a floating point representation
-- with up to 10 decimal places (and an unbounded number of integer digits).
-- We hope the mere presence of the large number in JSON won't break things,
-- and that the overall number of significant digits in the floating point
-- remains manageable in practice. (I'm not sure how to limit the number
-- of significant digits in a Decimal right now.)
instance ToJSON Decimal where
toJSON d = object
[ " decimalPlaces " .= toJSON decimalPlaces
, " decimalMantissa " .= toJSON decimalMantissa
, " floatingPoint " .= toJSON ( fromRational $ toRational d' :: Double )
]
where d' @ Decimal { .. } = roundTo 10 d
2020-02-25 20:26:36 +03:00
2019-02-21 04:33:35 +03:00
instance ToJSON Amount
instance ToJSON AmountStyle
2020-08-13 14:15:41 +03:00
instance ToJSON AmountPrecision
2019-02-21 04:33:35 +03:00
instance ToJSON Side
instance ToJSON DigitGroupStyle
instance ToJSON MixedAmount
instance ToJSON BalanceAssertion
2019-06-04 03:26:27 +03:00
instance ToJSON AmountPrice
2019-02-21 04:33:35 +03:00
instance ToJSON MarketPrice
instance ToJSON PostingType
2019-03-10 02:28:30 +03:00
2019-02-21 04:33:35 +03:00
instance ToJSON Posting where
toJSON Posting { .. } = object
2019-12-28 02:49:42 +03:00
[ " pdate " .= pdate
, " pdate2 " .= pdate2
, " pstatus " .= pstatus
, " paccount " .= paccount
, " pamount " .= pamount
, " pcomment " .= pcomment
, " ptype " .= ptype
, " ptags " .= ptags
, " pbalanceassertion " .= pbalanceassertion
2019-07-15 13:28:52 +03:00
-- To avoid a cycle, show just the parent transaction's index number
2019-02-21 04:33:35 +03:00
-- in a dummy field. When re-parsed, there will be no parent.
2019-12-28 02:49:42 +03:00
, " ptransaction_ " .= maybe " " ( show . tindex ) ptransaction
2019-02-21 04:33:35 +03:00
-- This is probably not wanted in json, we discard it.
2019-12-28 02:49:42 +03:00
, " poriginal " .= ( Nothing :: Maybe Posting )
2019-02-21 04:33:35 +03:00
]
2019-03-10 02:28:30 +03:00
2019-02-21 04:33:35 +03:00
instance ToJSON Transaction
2019-12-17 04:16:04 +03:00
instance ToJSON TransactionModifier
instance ToJSON PeriodicTransaction
instance ToJSON PriceDirective
instance ToJSON DateSpan
instance ToJSON Interval
instance ToJSON AccountAlias
instance ToJSON AccountType
instance ToJSONKey AccountType
instance ToJSON AccountDeclarationInfo
2020-12-30 22:38:13 +03:00
instance ToJSON PayeeDeclarationInfo
2019-12-17 04:16:04 +03:00
instance ToJSON Commodity
instance ToJSON TimeclockCode
instance ToJSON TimeclockEntry
instance ToJSON ClockTime
instance ToJSON Journal
2019-03-10 02:28:30 +03:00
2019-02-21 04:33:35 +03:00
instance ToJSON Account where
toJSON a = object
2019-12-28 02:49:42 +03:00
[ " aname " .= aname a
, " aebalance " .= aebalance a
, " aibalance " .= aibalance a
, " anumpostings " .= anumpostings a
, " aboring " .= aboring a
2019-07-15 13:28:52 +03:00
-- To avoid a cycle, show just the parent account's name
2019-02-21 04:33:35 +03:00
-- in a dummy field. When re-parsed, there will be no parent.
2019-12-28 02:49:42 +03:00
, " aparent_ " .= maybe " " aname ( aparent a )
2019-03-10 02:28:30 +03:00
-- Just the names of subaccounts, as a dummy field, ignored when parsed.
2019-12-28 02:49:42 +03:00
, " asubs_ " .= map aname ( asubs a )
2019-03-10 02:28:30 +03:00
-- The actual subaccounts (and their subs..), making a (probably highly redundant) tree
2019-12-28 02:49:42 +03:00
-- ,"asubs" .= asubs a
2019-03-10 02:28:30 +03:00
-- Omit the actual subaccounts
2019-12-28 02:49:42 +03:00
, " asubs " .= ( [] :: [ Account ] )
2019-02-21 04:33:35 +03:00
]
2019-12-17 04:16:04 +03:00
deriving instance Generic ( Ledger )
instance ToJSON Ledger
2019-02-21 04:33:35 +03:00
-- From JSON
instance FromJSON Status
instance FromJSON GenericSourcePos
instance FromJSON Amount
instance FromJSON AmountStyle
2020-08-13 14:15:41 +03:00
instance FromJSON AmountPrecision
2019-02-21 04:33:35 +03:00
instance FromJSON Side
instance FromJSON DigitGroupStyle
instance FromJSON MixedAmount
instance FromJSON BalanceAssertion
2019-06-04 03:26:27 +03:00
instance FromJSON AmountPrice
2019-02-21 04:33:35 +03:00
instance FromJSON MarketPrice
instance FromJSON PostingType
instance FromJSON Posting
instance FromJSON Transaction
instance FromJSON AccountDeclarationInfo
2019-03-10 02:28:30 +03:00
-- XXX The ToJSON instance replaces subaccounts with just names.
2019-07-15 13:28:52 +03:00
-- Here we should try to make use of those to reconstruct the
2019-03-10 02:28:30 +03:00
-- parent-child relationships.
2019-02-21 04:33:35 +03:00
instance FromJSON Account
2019-02-22 04:13:47 +03:00
-- Decimal, various attempts
--
-- https://stackoverflow.com/questions/40331851/haskell-data-decimal-as-aeson-type
2019-07-15 13:28:52 +03:00
----instance FromJSON Decimal where parseJSON =
2019-02-22 04:13:47 +03:00
---- A.withScientific "Decimal" (return . right . eitherFromRational . toRational)
--
-- https://github.com/bos/aeson/issues/474
-- http://hackage.haskell.org/package/aeson-1.4.2.0/docs/Data-Aeson-TH.html
-- $(deriveFromJSON defaultOptions ''Decimal) -- doesn't work
-- $(deriveFromJSON defaultOptions ''DecimalRaw) -- works; requires TH, but gives better parse error messages
--
-- https://github.com/PaulJohnson/Haskell-Decimal/issues/6
--deriving instance Generic Decimal
--instance FromJSON Decimal
2019-03-02 02:07:17 +03:00
deriving instance Generic ( DecimalRaw a )
2019-02-22 04:13:47 +03:00
instance FromJSON ( DecimalRaw Integer )
--
-- @simonmichael, I think the code in your first comment should work if it compiles—though “work” doesn’ t mean you can parse a JSON number directly into a `Decimal` using the generic instance, as you’ ve discovered.
--
--Error messages with these extensions are always rather cryptic, but I’ d prefer them to Template Haskell. Typically you’ ll want to start by getting a generic `ToJSON` instance working, then use that to figure out what the `FromJSON` instance expects to parse: for a correct instance, `encode` and `decode` should give you an isomorphism between your type and a subset of `Bytestring` (up to the `Maybe` wrapper that `decode` returns).
--
--I don’ t have time to test it right now, but I think it will also work without `DeriveAnyClass`, just using `DeriveGeneric` and `StandAloneDeriving`. It should also work to use the [`genericParseJSON`](http://hackage.haskell.org/package/aeson/docs/Data-Aeson.html#v:genericParseJSON) function to implement the class explicitly, something like this:
--
--{-# LANGUAGE DeriveGeneric #-}
--{-# LANGUAGE StandAloneDeriving #-}
--import GHC.Generics
--import Data.Aeson
--deriving instance Generic Decimal
--instance FromJSON Decimal where
-- parseJSON = genericParseJSON defaultOptions
--
--And of course you can avoid `StandAloneDeriving` entirely if you’ re willing to wrap `Decimal` in your own `newtype`.
2020-06-06 22:38:06 +03:00
-- XXX these will allow reading a Journal, but currently the
-- jdeclaredaccounttypes Map gets serialised as a JSON list, which
-- can't be read back.
--
-- instance FromJSON AccountAlias
-- instance FromJSONKey AccountType where fromJSONKey = genericFromJSONKey defaultJSONKeyOptions
-- instance FromJSON AccountType
-- instance FromJSON ClockTime
-- instance FromJSON Commodity
-- instance FromJSON DateSpan
-- instance FromJSON Interval
-- instance FromJSON PeriodicTransaction
-- instance FromJSON PriceDirective
-- instance FromJSON TimeclockCode
-- instance FromJSON TimeclockEntry
-- instance FromJSON TransactionModifier
-- instance FromJSON Journal
2019-02-21 04:33:35 +03:00
-- Utilities
2020-06-06 22:33:06 +03:00
-- | Show a JSON-convertible haskell value as pretty-printed JSON text.
toJsonText :: ToJSON a => a -> TL . Text
2020-10-27 05:04:00 +03:00
toJsonText = TB . toLazyText . ( <> TB . fromText " \ n " ) . encodePrettyToTextBuilder
2020-06-06 22:33:06 +03:00
-- | Write a JSON-convertible haskell value to a pretty-printed JSON file.
-- Eg: writeJsonFile "a.json" nulltransaction
writeJsonFile :: ToJSON a => FilePath -> a -> IO ()
writeJsonFile f = TL . writeFile f . toJsonText
-- we write with Text and read with ByteString, is that fine ?
-- | Read a JSON file and decode it to the target type, or raise an error if we can't.
-- Eg: readJsonFile "a.json" :: IO Transaction
2019-02-21 04:33:35 +03:00
readJsonFile :: FromJSON a => FilePath -> IO a
readJsonFile f = do
2020-06-06 22:33:06 +03:00
bl <- BL . readFile f
2020-08-06 02:05:56 +03:00
-- PARTIAL:
2020-06-06 22:33:06 +03:00
let v = fromMaybe ( error $ " could not decode JSON in " ++ show f ++ " to target value " )
( decode bl :: Maybe Value )
2019-02-21 04:33:35 +03:00
case fromJSON v :: FromJSON a => Result a of
Error e -> error e
Success t -> return t