{-# LANGUAGE
    AllowAmbiguousTypes
  , DeriveAnyClass
  , DeriveFoldable
  , DeriveFunctor
  , DeriveGeneric
  , DeriveTraversable
  , DerivingStrategies
  , DefaultSignatures
  , FlexibleContexts
  , FlexibleInstances
  , FunctionalDependencies
  , GADTs
  , LambdaCase
  , MultiParamTypeClasses
  , OverloadedStrings
  , ScopedTypeVariables
  , TypeApplications
  , TypeFamilies
  , TypeInType
  , TypeOperators
  , UndecidableInstances
  , UndecidableSuperClasses
#-}
module Squeal.PostgreSQL.Type
  ( Money (..)
  , Json (..)
  , Jsonb (..)
  , Composite (..)
  , Enumerated (..)
  , VarArray (..)
  , FixArray (..)
  , VarChar, varChar, getVarChar
  , FixChar, fixChar, getFixChar
  , Only (..)
  ) where
import Data.Proxy
import Data.Int (Int64)
import GHC.TypeLits
import qualified Data.Text as Strict (Text)
import qualified Data.Text as Strict.Text
import qualified GHC.Generics as GHC
import qualified Generics.SOP as SOP
newtype Money = Money { cents :: Int64 }
  deriving stock (Eq, Ord, Show, Read, GHC.Generic)
  deriving anyclass (SOP.HasDatatypeInfo, SOP.Generic)
newtype Json hask = Json {getJson :: hask}
  deriving stock (Eq, Ord, Show, Read, GHC.Generic)
  deriving anyclass (SOP.HasDatatypeInfo, SOP.Generic)
newtype Jsonb hask = Jsonb {getJsonb :: hask}
  deriving stock (Eq, Ord, Show, Read, GHC.Generic)
  deriving anyclass (SOP.HasDatatypeInfo, SOP.Generic)
newtype Composite record = Composite {getComposite :: record}
  deriving stock (Eq, Ord, Show, Read, GHC.Generic)
  deriving anyclass (SOP.HasDatatypeInfo, SOP.Generic)
newtype Enumerated enum = Enumerated {getEnumerated :: enum}
  deriving stock (Eq, Ord, Show, Read, GHC.Generic)
  deriving anyclass (SOP.HasDatatypeInfo, SOP.Generic)
newtype VarArray arr
  = VarArray {getVarArray :: arr}
  deriving stock (Eq, Ord, Show, Read, GHC.Generic)
  deriving anyclass (SOP.HasDatatypeInfo, SOP.Generic)
newtype FixArray arr = FixArray {getFixArray :: arr}
  deriving stock (Eq, Ord, Show, Read, GHC.Generic)
  deriving anyclass (SOP.HasDatatypeInfo, SOP.Generic)
newtype Only x = Only { fromOnly :: x }
  deriving (Functor,Foldable,Traversable,Eq,Ord,Read,Show,GHC.Generic)
instance SOP.Generic (Only x)
instance SOP.HasDatatypeInfo (Only x)
newtype VarChar (n :: Nat) = VarChar Strict.Text
  deriving (Eq,Ord,Read,Show)
varChar :: forall  n . KnownNat n => Strict.Text -> Maybe (VarChar n)
varChar t =
  if Strict.Text.length t <= fromIntegral (natVal @n Proxy)
  then Just $ VarChar t
  else Nothing
getVarChar :: VarChar n -> Strict.Text
getVarChar (VarChar t) = t
newtype FixChar (n :: Nat) = FixChar Strict.Text
  deriving (Eq,Ord,Read,Show)
fixChar :: forall  n . KnownNat n => Strict.Text -> Maybe (FixChar n)
fixChar t =
  if Strict.Text.length t == fromIntegral (natVal @n Proxy)
  then Just $ FixChar t
  else Nothing
getFixChar :: FixChar n -> Strict.Text
getFixChar (FixChar t) = t