{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}

module Database.Bolt.Extras.Internal.Persisted
  (
    BoltId
  , Persisted (..)
  , GetBoltId (..)
  , fromInt
  ) where

import           Data.Aeson        (FromJSON (..), ToJSON (..),
                                    genericParseJSON, genericToJSON)
import           Data.Aeson.Casing (aesonPrefix, snakeCase)
import           Database.Bolt     (Node (..), Relationship (..),
                                    URelationship (..))
import           GHC.Generics      (Generic (..))

-- | 'BoltId' is alias for Bolt 'Node', 'Relationship' and 'URelationship' identities.
--
type BoltId = Int

-- | 'Persisted' is wrapper for some object that can be identified with 'BoltId'.
--
data Persisted a = Persisted { forall a. Persisted a -> Int
objectId    :: BoltId
                             , forall a. Persisted a -> a
objectValue :: a
                             } deriving (Int -> Persisted a -> ShowS
forall a. Show a => Int -> Persisted a -> ShowS
forall a. Show a => [Persisted a] -> ShowS
forall a. Show a => Persisted a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Persisted a] -> ShowS
$cshowList :: forall a. Show a => [Persisted a] -> ShowS
show :: Persisted a -> String
$cshow :: forall a. Show a => Persisted a -> String
showsPrec :: Int -> Persisted a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Persisted a -> ShowS
Show, forall a b. a -> Persisted b -> Persisted a
forall a b. (a -> b) -> Persisted a -> Persisted 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 -> Persisted b -> Persisted a
$c<$ :: forall a b. a -> Persisted b -> Persisted a
fmap :: forall a b. (a -> b) -> Persisted a -> Persisted b
$cfmap :: forall a b. (a -> b) -> Persisted a -> Persisted b
Functor, Persisted a -> Persisted a -> Bool
forall a. Eq a => Persisted a -> Persisted a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Persisted a -> Persisted a -> Bool
$c/= :: forall a. Eq a => Persisted a -> Persisted a -> Bool
== :: Persisted a -> Persisted a -> Bool
$c== :: forall a. Eq a => Persisted a -> Persisted a -> Bool
Eq, Persisted a -> Persisted a -> Bool
Persisted a -> Persisted a -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (Persisted a)
forall a. Ord a => Persisted a -> Persisted a -> Bool
forall a. Ord a => Persisted a -> Persisted a -> Ordering
forall a. Ord a => Persisted a -> Persisted a -> Persisted a
min :: Persisted a -> Persisted a -> Persisted a
$cmin :: forall a. Ord a => Persisted a -> Persisted a -> Persisted a
max :: Persisted a -> Persisted a -> Persisted a
$cmax :: forall a. Ord a => Persisted a -> Persisted a -> Persisted a
>= :: Persisted a -> Persisted a -> Bool
$c>= :: forall a. Ord a => Persisted a -> Persisted a -> Bool
> :: Persisted a -> Persisted a -> Bool
$c> :: forall a. Ord a => Persisted a -> Persisted a -> Bool
<= :: Persisted a -> Persisted a -> Bool
$c<= :: forall a. Ord a => Persisted a -> Persisted a -> Bool
< :: Persisted a -> Persisted a -> Bool
$c< :: forall a. Ord a => Persisted a -> Persisted a -> Bool
compare :: Persisted a -> Persisted a -> Ordering
$ccompare :: forall a. Ord a => Persisted a -> Persisted a -> Ordering
Ord, ReadPrec [Persisted a]
ReadPrec (Persisted a)
ReadS [Persisted a]
forall a. Read a => ReadPrec [Persisted a]
forall a. Read a => ReadPrec (Persisted a)
forall a. Read a => Int -> ReadS (Persisted a)
forall a. Read a => ReadS [Persisted a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Persisted a]
$creadListPrec :: forall a. Read a => ReadPrec [Persisted a]
readPrec :: ReadPrec (Persisted a)
$creadPrec :: forall a. Read a => ReadPrec (Persisted a)
readList :: ReadS [Persisted a]
$creadList :: forall a. Read a => ReadS [Persisted a]
readsPrec :: Int -> ReadS (Persisted a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Persisted a)
Read, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Persisted a) x -> Persisted a
forall a x. Persisted a -> Rep (Persisted a) x
$cto :: forall a x. Rep (Persisted a) x -> Persisted a
$cfrom :: forall a x. Persisted a -> Rep (Persisted a) x
Generic)

-- | This is just check that your 'BoltId' is valid.
--
fromInt :: Int -> BoltId
fromInt :: Int -> Int
fromInt Int
i | Int
i forall a. Ord a => a -> a -> Bool
>= Int
0    = Int
i
          | Bool
otherwise = forall a. HasCallStack => String -> a
error String
"Database.Bolt.Extras.Internal.Persisted: could not create BoltId with identity less then zero."

-- | Common class to get 'BoltId' from the object.
--
class GetBoltId a where
  getBoltId :: a -> BoltId

instance GetBoltId Node where
  getBoltId :: Node -> Int
getBoltId = Int -> Int
fromInt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> Int
nodeIdentity

instance GetBoltId Relationship where
  getBoltId :: Relationship -> Int
getBoltId = Int -> Int
fromInt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Relationship -> Int
relIdentity

instance GetBoltId URelationship where
  getBoltId :: URelationship -> Int
getBoltId = Int -> Int
fromInt forall b c a. (b -> c) -> (a -> b) -> a -> c
. URelationship -> Int
urelIdentity

instance GetBoltId (Persisted a) where
  getBoltId :: Persisted a -> Int
getBoltId = Int -> Int
fromInt forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Persisted a -> Int
objectId

instance ToJSON a => ToJSON (Persisted a) where
  toJSON :: Persisted a -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON forall a b. (a -> b) -> a -> b
$ ShowS -> Options
aesonPrefix ShowS
snakeCase

instance FromJSON a => FromJSON (Persisted a) where
  parseJSON :: Value -> Parser (Persisted a)
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON forall a b. (a -> b) -> a -> b
$ ShowS -> Options
aesonPrefix ShowS
snakeCase