{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Database.PostgreSQL.Simple.Newtypes (
    Aeson (..), getAeson,
) where
import Data.Typeable (Typeable)
import Database.PostgreSQL.Simple.ToField (ToField (..))
import Database.PostgreSQL.Simple.FromField (FromField (..), fromJSONField)
import qualified Data.Aeson as Aeson
newtype Aeson a = Aeson a
  deriving (Aeson a -> Aeson a -> Bool
forall a. Eq a => Aeson a -> Aeson a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Aeson a -> Aeson a -> Bool
$c/= :: forall a. Eq a => Aeson a -> Aeson a -> Bool
== :: Aeson a -> Aeson a -> Bool
$c== :: forall a. Eq a => Aeson a -> Aeson a -> Bool
Eq, Int -> Aeson a -> ShowS
forall a. Show a => Int -> Aeson a -> ShowS
forall a. Show a => [Aeson a] -> ShowS
forall a. Show a => Aeson a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Aeson a] -> ShowS
$cshowList :: forall a. Show a => [Aeson a] -> ShowS
show :: Aeson a -> String
$cshow :: forall a. Show a => Aeson a -> String
showsPrec :: Int -> Aeson a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Aeson a -> ShowS
Show, ReadPrec [Aeson a]
ReadPrec (Aeson a)
ReadS [Aeson a]
forall a. Read a => ReadPrec [Aeson a]
forall a. Read a => ReadPrec (Aeson a)
forall a. Read a => Int -> ReadS (Aeson a)
forall a. Read a => ReadS [Aeson a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Aeson a]
$creadListPrec :: forall a. Read a => ReadPrec [Aeson a]
readPrec :: ReadPrec (Aeson a)
$creadPrec :: forall a. Read a => ReadPrec (Aeson a)
readList :: ReadS [Aeson a]
$creadList :: forall a. Read a => ReadS [Aeson a]
readsPrec :: Int -> ReadS (Aeson a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Aeson a)
Read, Typeable, forall a b. a -> Aeson b -> Aeson a
forall a b. (a -> b) -> Aeson a -> Aeson b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Aeson b -> Aeson a
$c<$ :: forall a b. a -> Aeson b -> Aeson a
fmap :: forall a b. (a -> b) -> Aeson a -> Aeson b
$cfmap :: forall a b. (a -> b) -> Aeson a -> Aeson b
Functor)
getAeson :: Aeson a -> a
getAeson :: forall a. Aeson a -> a
getAeson (Aeson a
a) = a
a
instance Aeson.ToJSON a => ToField (Aeson a) where
    toField :: Aeson a -> Action
toField = forall a. ToField a => a -> Action
toField forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> ByteString
Aeson.encode forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Aeson a -> a
getAeson
instance (Aeson.FromJSON a, Typeable a) => FromField (Aeson a) where
    fromField :: FieldParser (Aeson a)
fromField Field
f Maybe ByteString
bs = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Aeson a
Aeson (forall a. (FromJSON a, Typeable a) => FieldParser a
fromJSONField Field
f Maybe ByteString
bs)