{-# LANGUAGE CPP                 #-}
{-# LANGUAGE DataKinds           #-}
{-# LANGUAGE KindSignatures      #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.Aeson.Extra.SymTag (
    SymTag(..),
    ) where
import Prelude ()
import Prelude.Compat
import Control.DeepSeq  (NFData (..))
import Data.Aeson
import Data.Aeson.Types hiding ((.:?))
import Data.Proxy       (Proxy (..))
import GHC.TypeLits     (KnownSymbol, Symbol, symbolVal)
import qualified Data.Text as T
data SymTag (s :: Symbol) = SymTag
  deriving (SymTag s -> SymTag s -> Bool
(SymTag s -> SymTag s -> Bool)
-> (SymTag s -> SymTag s -> Bool) -> Eq (SymTag s)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (s :: Symbol). SymTag s -> SymTag s -> Bool
/= :: SymTag s -> SymTag s -> Bool
$c/= :: forall (s :: Symbol). SymTag s -> SymTag s -> Bool
== :: SymTag s -> SymTag s -> Bool
$c== :: forall (s :: Symbol). SymTag s -> SymTag s -> Bool
Eq, Eq (SymTag s)
Eq (SymTag s)
-> (SymTag s -> SymTag s -> Ordering)
-> (SymTag s -> SymTag s -> Bool)
-> (SymTag s -> SymTag s -> Bool)
-> (SymTag s -> SymTag s -> Bool)
-> (SymTag s -> SymTag s -> Bool)
-> (SymTag s -> SymTag s -> SymTag s)
-> (SymTag s -> SymTag s -> SymTag s)
-> Ord (SymTag s)
SymTag s -> SymTag s -> Bool
SymTag s -> SymTag s -> Ordering
SymTag s -> SymTag s -> SymTag s
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 (s :: Symbol). Eq (SymTag s)
forall (s :: Symbol). SymTag s -> SymTag s -> Bool
forall (s :: Symbol). SymTag s -> SymTag s -> Ordering
forall (s :: Symbol). SymTag s -> SymTag s -> SymTag s
min :: SymTag s -> SymTag s -> SymTag s
$cmin :: forall (s :: Symbol). SymTag s -> SymTag s -> SymTag s
max :: SymTag s -> SymTag s -> SymTag s
$cmax :: forall (s :: Symbol). SymTag s -> SymTag s -> SymTag s
>= :: SymTag s -> SymTag s -> Bool
$c>= :: forall (s :: Symbol). SymTag s -> SymTag s -> Bool
> :: SymTag s -> SymTag s -> Bool
$c> :: forall (s :: Symbol). SymTag s -> SymTag s -> Bool
<= :: SymTag s -> SymTag s -> Bool
$c<= :: forall (s :: Symbol). SymTag s -> SymTag s -> Bool
< :: SymTag s -> SymTag s -> Bool
$c< :: forall (s :: Symbol). SymTag s -> SymTag s -> Bool
compare :: SymTag s -> SymTag s -> Ordering
$ccompare :: forall (s :: Symbol). SymTag s -> SymTag s -> Ordering
$cp1Ord :: forall (s :: Symbol). Eq (SymTag s)
Ord, Int -> SymTag s -> ShowS
[SymTag s] -> ShowS
SymTag s -> String
(Int -> SymTag s -> ShowS)
-> (SymTag s -> String) -> ([SymTag s] -> ShowS) -> Show (SymTag s)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (s :: Symbol). Int -> SymTag s -> ShowS
forall (s :: Symbol). [SymTag s] -> ShowS
forall (s :: Symbol). SymTag s -> String
showList :: [SymTag s] -> ShowS
$cshowList :: forall (s :: Symbol). [SymTag s] -> ShowS
show :: SymTag s -> String
$cshow :: forall (s :: Symbol). SymTag s -> String
showsPrec :: Int -> SymTag s -> ShowS
$cshowsPrec :: forall (s :: Symbol). Int -> SymTag s -> ShowS
Show, ReadPrec [SymTag s]
ReadPrec (SymTag s)
Int -> ReadS (SymTag s)
ReadS [SymTag s]
(Int -> ReadS (SymTag s))
-> ReadS [SymTag s]
-> ReadPrec (SymTag s)
-> ReadPrec [SymTag s]
-> Read (SymTag s)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall (s :: Symbol). ReadPrec [SymTag s]
forall (s :: Symbol). ReadPrec (SymTag s)
forall (s :: Symbol). Int -> ReadS (SymTag s)
forall (s :: Symbol). ReadS [SymTag s]
readListPrec :: ReadPrec [SymTag s]
$creadListPrec :: forall (s :: Symbol). ReadPrec [SymTag s]
readPrec :: ReadPrec (SymTag s)
$creadPrec :: forall (s :: Symbol). ReadPrec (SymTag s)
readList :: ReadS [SymTag s]
$creadList :: forall (s :: Symbol). ReadS [SymTag s]
readsPrec :: Int -> ReadS (SymTag s)
$creadsPrec :: forall (s :: Symbol). Int -> ReadS (SymTag s)
Read, Int -> SymTag s
SymTag s -> Int
SymTag s -> [SymTag s]
SymTag s -> SymTag s
SymTag s -> SymTag s -> [SymTag s]
SymTag s -> SymTag s -> SymTag s -> [SymTag s]
(SymTag s -> SymTag s)
-> (SymTag s -> SymTag s)
-> (Int -> SymTag s)
-> (SymTag s -> Int)
-> (SymTag s -> [SymTag s])
-> (SymTag s -> SymTag s -> [SymTag s])
-> (SymTag s -> SymTag s -> [SymTag s])
-> (SymTag s -> SymTag s -> SymTag s -> [SymTag s])
-> Enum (SymTag s)
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
forall (s :: Symbol). Int -> SymTag s
forall (s :: Symbol). SymTag s -> Int
forall (s :: Symbol). SymTag s -> [SymTag s]
forall (s :: Symbol). SymTag s -> SymTag s
forall (s :: Symbol). SymTag s -> SymTag s -> [SymTag s]
forall (s :: Symbol).
SymTag s -> SymTag s -> SymTag s -> [SymTag s]
enumFromThenTo :: SymTag s -> SymTag s -> SymTag s -> [SymTag s]
$cenumFromThenTo :: forall (s :: Symbol).
SymTag s -> SymTag s -> SymTag s -> [SymTag s]
enumFromTo :: SymTag s -> SymTag s -> [SymTag s]
$cenumFromTo :: forall (s :: Symbol). SymTag s -> SymTag s -> [SymTag s]
enumFromThen :: SymTag s -> SymTag s -> [SymTag s]
$cenumFromThen :: forall (s :: Symbol). SymTag s -> SymTag s -> [SymTag s]
enumFrom :: SymTag s -> [SymTag s]
$cenumFrom :: forall (s :: Symbol). SymTag s -> [SymTag s]
fromEnum :: SymTag s -> Int
$cfromEnum :: forall (s :: Symbol). SymTag s -> Int
toEnum :: Int -> SymTag s
$ctoEnum :: forall (s :: Symbol). Int -> SymTag s
pred :: SymTag s -> SymTag s
$cpred :: forall (s :: Symbol). SymTag s -> SymTag s
succ :: SymTag s -> SymTag s
$csucc :: forall (s :: Symbol). SymTag s -> SymTag s
Enum, SymTag s
SymTag s -> SymTag s -> Bounded (SymTag s)
forall a. a -> a -> Bounded a
forall (s :: Symbol). SymTag s
maxBound :: SymTag s
$cmaxBound :: forall (s :: Symbol). SymTag s
minBound :: SymTag s
$cminBound :: forall (s :: Symbol). SymTag s
Bounded)
instance KnownSymbol s => FromJSON (SymTag s) where
  parseJSON :: Value -> Parser (SymTag s)
parseJSON (String Text
t)
    | Text -> String
T.unpack Text
t String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== Proxy s -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy s
forall k (t :: k). Proxy t
Proxy :: Proxy s) = SymTag s -> Parser (SymTag s)
forall (f :: * -> *) a. Applicative f => a -> f a
pure SymTag s
forall (s :: Symbol). SymTag s
SymTag
  parseJSON Value
v = String -> Value -> Parser (SymTag s)
forall a. String -> Value -> Parser a
typeMismatch (String
"SymTag " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show (Proxy s -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy s
forall k (t :: k). Proxy t
Proxy :: Proxy s))) Value
v
instance KnownSymbol s => ToJSON (SymTag s) where
#if MIN_VERSION_aeson (0,10,0)
  toEncoding :: SymTag s -> Encoding
toEncoding SymTag s
_ = String -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding (Proxy s -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy s
forall k (t :: k). Proxy t
Proxy :: Proxy s))
#endif
  toJSON :: SymTag s -> Value
toJSON SymTag s
_ = String -> Value
forall a. ToJSON a => a -> Value
toJSON (Proxy s -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy s
forall k (t :: k). Proxy t
Proxy :: Proxy s))
instance NFData (SymTag s) where
    rnf :: SymTag s -> ()
rnf SymTag s
SymTag = ()