-- This file is part of the Wire Server implementation.
--
-- Copyright (C) 2022 Wire Swiss GmbH <opensource@wire.com>
--
-- This program is free software: you can redistribute it and/or modify it under
-- the terms of the GNU Affero General Public License as published by the Free
-- Software Foundation, either version 3 of the License, or (at your option) any
-- later version.
--
-- This program is distributed in the hope that it will be useful, but WITHOUT
-- ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
-- FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more
-- details.
--
-- You should have received a copy of the GNU Affero General Public License along
-- with this program. If not, see <https://www.gnu.org/licenses/>.

module Wire.API.Util.Aeson
  ( customEncodingOptions,
    customEncodingOptionsDropChar,
    defaultOptsDropChar,
    CustomEncoded (..),
    CustomEncodedLensable (..),
  )
where

import Data.Aeson
import Data.Json.Util (toJSONFieldName)
import GHC.Generics (Rep)
import Imports hiding (All)

-- | Drops record field name prefixes (anything until the first upper-case char)
-- and turns the rest into snake_case.
--
-- For example, it converts @_recordFieldLabel@ into @field_label@.
customEncodingOptions :: Options
customEncodingOptions :: Options
customEncodingOptions = Options
toJSONFieldName

-- This is useful for structures that are also creating lenses.
-- If the field name doesn't have a leading underscore then the
-- default `makeLenses` call won't make any lenses.
customEncodingOptionsDropChar :: Char -> Options
customEncodingOptionsDropChar :: Char -> Options
customEncodingOptionsDropChar Char
c =
  Options
toJSONFieldName
    { fieldLabelModifier = fieldLabelModifier toJSONFieldName . dropWhile (c ==)
    }

-- Similar to customEncodingOptionsDropChar, but not doing snake_case
defaultOptsDropChar :: Char -> Options
defaultOptsDropChar :: Char -> Options
defaultOptsDropChar Char
c =
  Options
defaultOptions
    { fieldLabelModifier = fieldLabelModifier defaultOptions . dropWhile (c ==)
    }

newtype CustomEncoded a = CustomEncoded {forall a. CustomEncoded a -> a
unCustomEncoded :: a}

instance (Generic a, GToJSON Zero (Rep a)) => ToJSON (CustomEncoded a) where
  toJSON :: CustomEncoded a -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON @a Options
customEncodingOptions (a -> Value) -> (CustomEncoded a -> a) -> CustomEncoded a -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CustomEncoded a -> a
forall a. CustomEncoded a -> a
unCustomEncoded

instance (Generic a, GFromJSON Zero (Rep a)) => FromJSON (CustomEncoded a) where
  parseJSON :: Value -> Parser (CustomEncoded a)
parseJSON = (a -> CustomEncoded a) -> Parser a -> Parser (CustomEncoded a)
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> CustomEncoded a
forall a. a -> CustomEncoded a
CustomEncoded (Parser a -> Parser (CustomEncoded a))
-> (Value -> Parser a) -> Value -> Parser (CustomEncoded a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON @a Options
customEncodingOptions

-- Similar to CustomEncoded except that it will first strip off leading '_' characters.
-- This is important for records with field names that would otherwise be keywords, like type or data
-- It is also useful if the record has lenses being generated.
newtype CustomEncodedLensable a = CustomEncodedLensable {forall a. CustomEncodedLensable a -> a
unCustomEncodedLensable :: a}

instance (Generic a, GToJSON Zero (Rep a)) => ToJSON (CustomEncodedLensable a) where
  toJSON :: CustomEncodedLensable a -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON @a (Char -> Options
customEncodingOptionsDropChar Char
'_') (a -> Value)
-> (CustomEncodedLensable a -> a)
-> CustomEncodedLensable a
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CustomEncodedLensable a -> a
forall a. CustomEncodedLensable a -> a
unCustomEncodedLensable

instance (Generic a, GFromJSON Zero (Rep a)) => FromJSON (CustomEncodedLensable a) where
  parseJSON :: Value -> Parser (CustomEncodedLensable a)
parseJSON = (a -> CustomEncodedLensable a)
-> Parser a -> Parser (CustomEncodedLensable a)
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> CustomEncodedLensable a
forall a. a -> CustomEncodedLensable a
CustomEncodedLensable (Parser a -> Parser (CustomEncodedLensable a))
-> (Value -> Parser a) -> Value -> Parser (CustomEncodedLensable a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON @a (Char -> Options
customEncodingOptionsDropChar Char
'_')