2019-02-21 04:33:35 +03:00
{- # OPTIONS_GHC - fno - warn - orphans # -}
--{-# LANGUAGE CPP #-}
--{-# 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-07-15 13:28:52 +03:00
module Hledger.Web.Json (
2019-02-21 04:33:35 +03:00
-- * Instances
-- * Utilities
readJsonFile
, writeJsonFile
) where
import Data.Aeson
--import Data.Aeson.TH
import qualified Data.ByteString.Lazy as BL
import Data.Decimal
import Data.Maybe
import GHC.Generics ( Generic )
import Hledger.Data
2019-09-12 00:49:22 +03:00
-- JSON instances. Should they be in hledger-lib Types.hs ?
2019-02-21 04:33:35 +03:00
-- To JSON
instance ToJSON Status
instance ToJSON GenericSourcePos
instance ToJSON Decimal
instance ToJSON Amount
instance ToJSON AmountStyle
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
[ " pdate " .= toJSON pdate
, " pdate2 " .= toJSON pdate2
, " pstatus " .= toJSON pstatus
, " paccount " .= toJSON paccount
, " pamount " .= toJSON pamount
, " pcomment " .= toJSON pcomment
, " ptype " .= toJSON ptype
, " ptags " .= toJSON ptags
, " pbalanceassertion " .= toJSON 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.
, " ptransaction_ " .= toJSON ( maybe " " ( show . tindex ) ptransaction )
-- This is probably not wanted in json, we discard it.
2019-07-15 13:28:52 +03:00
, " poriginal " .= toJSON ( 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-03-10 02:28:30 +03:00
2019-02-21 04:33:35 +03:00
instance ToJSON Account where
toJSON a = object
[ " aname " .= toJSON ( aname a )
, " aebalance " .= toJSON ( aebalance a )
, " aibalance " .= toJSON ( aibalance a )
, " anumpostings " .= toJSON ( anumpostings a )
, " aboring " .= toJSON ( 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.
, " aparent_ " .= toJSON ( 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-02-21 04:33:35 +03:00
, " asubs_ " .= toJSON ( map aname $ asubs a )
2019-03-10 02:28:30 +03:00
-- The actual subaccounts (and their subs..), making a (probably highly redundant) tree
-- ,"asubs" .= toJSON (asubs a)
-- Omit the actual subaccounts
, " asubs " .= toJSON ( [] :: [ Account ] )
2019-02-21 04:33:35 +03:00
]
-- From JSON
instance FromJSON Status
instance FromJSON GenericSourcePos
instance FromJSON Amount
instance FromJSON AmountStyle
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`.
2019-02-21 04:33:35 +03:00
-- Utilities
-- | Read a json from a file and decode/parse it as the target type, if we can.
-- Example:
-- >>> readJsonFile "in.json" :: IO MixedAmount
readJsonFile :: FromJSON a => FilePath -> IO a
readJsonFile f = do
bs <- BL . readFile f
2019-07-15 13:28:52 +03:00
let v = fromMaybe ( error " could not decode bytestring as json value " ) ( decode bs :: 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
-- | Write some to-JSON-convertible haskell value to a json file, if we can.
-- Example:
-- >>> writeJsonFile "out.json" nullmixedamt
writeJsonFile :: ToJSON a => FilePath -> a -> IO ()
writeJsonFile f v = BL . writeFile f ( encode $ toJSON v )