{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE StrictData #-}
module OpenTelemetry.Attributes (
Attributes (attributesDropped),
emptyAttributes,
addAttribute,
addAttributes,
getAttributes,
lookupAttribute,
Attribute (..),
ToAttribute (..),
PrimitiveAttribute (..),
ToPrimitiveAttribute (..),
AttributeLimits (..),
defaultAttributeLimits,
unsafeAttributesFromListIgnoringLimits,
unsafeMergeAttributesIgnoringLimits,
) where
import Data.Data (Data)
import qualified Data.HashMap.Strict as H
import Data.Hashable (Hashable)
import Data.Int (Int64)
import Data.String (IsString (..))
import Data.Text (Text)
import qualified Data.Text as T
import GHC.Generics (Generic)
import qualified Language.Haskell.TH.Syntax as TH
defaultAttributeLimits :: AttributeLimits
defaultAttributeLimits :: AttributeLimits
defaultAttributeLimits =
AttributeLimits
{ attributeCountLimit :: Maybe Int
attributeCountLimit = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
128
, attributeLengthLimit :: Maybe Int
attributeLengthLimit = Maybe Int
forall a. Maybe a
Nothing
}
data Attributes = Attributes
{ Attributes -> HashMap Text Attribute
attributes :: !(H.HashMap Text Attribute)
, Attributes -> Int
attributesCount :: {-# UNPACK #-} !Int
, Attributes -> Int
attributesDropped :: {-# UNPACK #-} !Int
}
deriving stock (Int -> Attributes -> ShowS
[Attributes] -> ShowS
Attributes -> String
(Int -> Attributes -> ShowS)
-> (Attributes -> String)
-> ([Attributes] -> ShowS)
-> Show Attributes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Attributes -> ShowS
showsPrec :: Int -> Attributes -> ShowS
$cshow :: Attributes -> String
show :: Attributes -> String
$cshowList :: [Attributes] -> ShowS
showList :: [Attributes] -> ShowS
Show, (forall x. Attributes -> Rep Attributes x)
-> (forall x. Rep Attributes x -> Attributes) -> Generic Attributes
forall x. Rep Attributes x -> Attributes
forall x. Attributes -> Rep Attributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Attributes -> Rep Attributes x
from :: forall x. Attributes -> Rep Attributes x
$cto :: forall x. Rep Attributes x -> Attributes
to :: forall x. Rep Attributes x -> Attributes
Generic, Attributes -> Attributes -> Bool
(Attributes -> Attributes -> Bool)
-> (Attributes -> Attributes -> Bool) -> Eq Attributes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Attributes -> Attributes -> Bool
== :: Attributes -> Attributes -> Bool
$c/= :: Attributes -> Attributes -> Bool
/= :: Attributes -> Attributes -> Bool
Eq, Eq Attributes
Eq Attributes =>
(Attributes -> Attributes -> Ordering)
-> (Attributes -> Attributes -> Bool)
-> (Attributes -> Attributes -> Bool)
-> (Attributes -> Attributes -> Bool)
-> (Attributes -> Attributes -> Bool)
-> (Attributes -> Attributes -> Attributes)
-> (Attributes -> Attributes -> Attributes)
-> Ord Attributes
Attributes -> Attributes -> Bool
Attributes -> Attributes -> Ordering
Attributes -> Attributes -> Attributes
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
$ccompare :: Attributes -> Attributes -> Ordering
compare :: Attributes -> Attributes -> Ordering
$c< :: Attributes -> Attributes -> Bool
< :: Attributes -> Attributes -> Bool
$c<= :: Attributes -> Attributes -> Bool
<= :: Attributes -> Attributes -> Bool
$c> :: Attributes -> Attributes -> Bool
> :: Attributes -> Attributes -> Bool
$c>= :: Attributes -> Attributes -> Bool
>= :: Attributes -> Attributes -> Bool
$cmax :: Attributes -> Attributes -> Attributes
max :: Attributes -> Attributes -> Attributes
$cmin :: Attributes -> Attributes -> Attributes
min :: Attributes -> Attributes -> Attributes
Ord, (forall (m :: * -> *). Quote m => Attributes -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
Attributes -> Code m Attributes)
-> Lift Attributes
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Attributes -> m Exp
forall (m :: * -> *). Quote m => Attributes -> Code m Attributes
$clift :: forall (m :: * -> *). Quote m => Attributes -> m Exp
lift :: forall (m :: * -> *). Quote m => Attributes -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => Attributes -> Code m Attributes
liftTyped :: forall (m :: * -> *). Quote m => Attributes -> Code m Attributes
TH.Lift)
instance Hashable Attributes
emptyAttributes :: Attributes
emptyAttributes :: Attributes
emptyAttributes = HashMap Text Attribute -> Int -> Int -> Attributes
Attributes HashMap Text Attribute
forall a. Monoid a => a
mempty Int
0 Int
0
addAttribute :: (ToAttribute a) => AttributeLimits -> Attributes -> Text -> a -> Attributes
addAttribute :: forall a.
ToAttribute a =>
AttributeLimits -> Attributes -> Text -> a -> Attributes
addAttribute AttributeLimits {Maybe Int
attributeCountLimit :: AttributeLimits -> Maybe Int
attributeLengthLimit :: AttributeLimits -> Maybe Int
attributeCountLimit :: Maybe Int
attributeLengthLimit :: Maybe Int
..} Attributes {Int
HashMap Text Attribute
attributesDropped :: Attributes -> Int
attributes :: Attributes -> HashMap Text Attribute
attributesCount :: Attributes -> Int
attributes :: HashMap Text Attribute
attributesCount :: Int
attributesDropped :: Int
..} !Text
k !a
v = case Maybe Int
attributeCountLimit of
Maybe Int
Nothing -> HashMap Text Attribute -> Int -> Int -> Attributes
Attributes HashMap Text Attribute
newAttrs Int
newCount Int
attributesDropped
Just Int
limit_ ->
if Int
newCount Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
limit_
then HashMap Text Attribute -> Int -> Int -> Attributes
Attributes HashMap Text Attribute
attributes Int
attributesCount (Int
attributesDropped Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
else HashMap Text Attribute -> Int -> Int -> Attributes
Attributes HashMap Text Attribute
newAttrs Int
newCount Int
attributesDropped
where
newAttrs :: HashMap Text Attribute
newAttrs = Text
-> Attribute -> HashMap Text Attribute -> HashMap Text Attribute
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
H.insert Text
k ((Attribute -> Attribute)
-> (Int -> Attribute -> Attribute)
-> Maybe Int
-> Attribute
-> Attribute
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Attribute -> Attribute
forall a. a -> a
id Int -> Attribute -> Attribute
limitLengths Maybe Int
attributeLengthLimit (Attribute -> Attribute) -> Attribute -> Attribute
forall a b. (a -> b) -> a -> b
$ a -> Attribute
forall a. ToAttribute a => a -> Attribute
toAttribute a
v) HashMap Text Attribute
attributes
newCount :: Int
newCount = HashMap Text Attribute -> Int
forall k v. HashMap k v -> Int
H.size HashMap Text Attribute
newAttrs
{-# INLINE addAttribute #-}
addAttributes :: (ToAttribute a) => AttributeLimits -> Attributes -> H.HashMap Text a -> Attributes
addAttributes :: forall a.
ToAttribute a =>
AttributeLimits -> Attributes -> HashMap Text a -> Attributes
addAttributes AttributeLimits {Maybe Int
attributeCountLimit :: AttributeLimits -> Maybe Int
attributeLengthLimit :: AttributeLimits -> Maybe Int
attributeCountLimit :: Maybe Int
attributeLengthLimit :: Maybe Int
..} Attributes {Int
HashMap Text Attribute
attributesDropped :: Attributes -> Int
attributes :: Attributes -> HashMap Text Attribute
attributesCount :: Attributes -> Int
attributes :: HashMap Text Attribute
attributesCount :: Int
attributesDropped :: Int
..} HashMap Text a
attrs = case Maybe Int
attributeCountLimit of
Maybe Int
Nothing -> HashMap Text Attribute -> Int -> Int -> Attributes
Attributes HashMap Text Attribute
newAttrs Int
newCount Int
attributesDropped
Just Int
limit_ ->
if Int
newCount Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
limit_
then HashMap Text Attribute -> Int -> Int -> Attributes
Attributes HashMap Text Attribute
attributes Int
attributesCount (Int
attributesDropped Int -> Int -> Int
forall a. Num a => a -> a -> a
+ HashMap Text a -> Int
forall k v. HashMap k v -> Int
H.size HashMap Text a
attrs)
else HashMap Text Attribute -> Int -> Int -> Attributes
Attributes HashMap Text Attribute
newAttrs Int
newCount Int
attributesDropped
where
newAttrs :: HashMap Text Attribute
newAttrs = HashMap Text Attribute
-> HashMap Text Attribute -> HashMap Text Attribute
forall k v. Eq k => HashMap k v -> HashMap k v -> HashMap k v
H.union HashMap Text Attribute
attributes (HashMap Text Attribute -> HashMap Text Attribute)
-> HashMap Text Attribute -> HashMap Text Attribute
forall a b. (a -> b) -> a -> b
$ (a -> Attribute) -> HashMap Text a -> HashMap Text Attribute
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
H.map ((Attribute -> Attribute)
-> (Int -> Attribute -> Attribute)
-> Maybe Int
-> Attribute
-> Attribute
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Attribute -> Attribute
forall a. a -> a
id Int -> Attribute -> Attribute
limitLengths Maybe Int
attributeLengthLimit (Attribute -> Attribute) -> (a -> Attribute) -> a -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Attribute
forall a. ToAttribute a => a -> Attribute
toAttribute) HashMap Text a
attrs
newCount :: Int
newCount = HashMap Text Attribute -> Int
forall k v. HashMap k v -> Int
H.size HashMap Text Attribute
newAttrs
{-# INLINE addAttributes #-}
limitPrimAttr :: Int -> PrimitiveAttribute -> PrimitiveAttribute
limitPrimAttr :: Int -> PrimitiveAttribute -> PrimitiveAttribute
limitPrimAttr Int
limit (TextAttribute Text
t) = Text -> PrimitiveAttribute
TextAttribute (Int -> Text -> Text
T.take Int
limit Text
t)
limitPrimAttr Int
_ PrimitiveAttribute
attr = PrimitiveAttribute
attr
limitLengths :: Int -> Attribute -> Attribute
limitLengths :: Int -> Attribute -> Attribute
limitLengths Int
limit (AttributeValue PrimitiveAttribute
val) = PrimitiveAttribute -> Attribute
AttributeValue (PrimitiveAttribute -> Attribute)
-> PrimitiveAttribute -> Attribute
forall a b. (a -> b) -> a -> b
$ Int -> PrimitiveAttribute -> PrimitiveAttribute
limitPrimAttr Int
limit PrimitiveAttribute
val
limitLengths Int
limit (AttributeArray [PrimitiveAttribute]
arr) = [PrimitiveAttribute] -> Attribute
AttributeArray ([PrimitiveAttribute] -> Attribute)
-> [PrimitiveAttribute] -> Attribute
forall a b. (a -> b) -> a -> b
$ (PrimitiveAttribute -> PrimitiveAttribute)
-> [PrimitiveAttribute] -> [PrimitiveAttribute]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> PrimitiveAttribute -> PrimitiveAttribute
limitPrimAttr Int
limit) [PrimitiveAttribute]
arr
getAttributes :: Attributes -> (Int, H.HashMap Text Attribute)
getAttributes :: Attributes -> (Int, HashMap Text Attribute)
getAttributes Attributes {Int
HashMap Text Attribute
attributesDropped :: Attributes -> Int
attributes :: Attributes -> HashMap Text Attribute
attributesCount :: Attributes -> Int
attributes :: HashMap Text Attribute
attributesCount :: Int
attributesDropped :: Int
..} = (Int
attributesCount, HashMap Text Attribute
attributes)
lookupAttribute :: Attributes -> Text -> Maybe Attribute
lookupAttribute :: Attributes -> Text -> Maybe Attribute
lookupAttribute Attributes {Int
HashMap Text Attribute
attributesDropped :: Attributes -> Int
attributes :: Attributes -> HashMap Text Attribute
attributesCount :: Attributes -> Int
attributes :: HashMap Text Attribute
attributesCount :: Int
attributesDropped :: Int
..} Text
k = Text -> HashMap Text Attribute -> Maybe Attribute
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
H.lookup Text
k HashMap Text Attribute
attributes
data AttributeLimits = AttributeLimits
{ AttributeLimits -> Maybe Int
attributeCountLimit :: Maybe Int
, AttributeLimits -> Maybe Int
attributeLengthLimit :: Maybe Int
}
deriving stock (ReadPrec [AttributeLimits]
ReadPrec AttributeLimits
Int -> ReadS AttributeLimits
ReadS [AttributeLimits]
(Int -> ReadS AttributeLimits)
-> ReadS [AttributeLimits]
-> ReadPrec AttributeLimits
-> ReadPrec [AttributeLimits]
-> Read AttributeLimits
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AttributeLimits
readsPrec :: Int -> ReadS AttributeLimits
$creadList :: ReadS [AttributeLimits]
readList :: ReadS [AttributeLimits]
$creadPrec :: ReadPrec AttributeLimits
readPrec :: ReadPrec AttributeLimits
$creadListPrec :: ReadPrec [AttributeLimits]
readListPrec :: ReadPrec [AttributeLimits]
Read, Int -> AttributeLimits -> ShowS
[AttributeLimits] -> ShowS
AttributeLimits -> String
(Int -> AttributeLimits -> ShowS)
-> (AttributeLimits -> String)
-> ([AttributeLimits] -> ShowS)
-> Show AttributeLimits
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AttributeLimits -> ShowS
showsPrec :: Int -> AttributeLimits -> ShowS
$cshow :: AttributeLimits -> String
show :: AttributeLimits -> String
$cshowList :: [AttributeLimits] -> ShowS
showList :: [AttributeLimits] -> ShowS
Show, AttributeLimits -> AttributeLimits -> Bool
(AttributeLimits -> AttributeLimits -> Bool)
-> (AttributeLimits -> AttributeLimits -> Bool)
-> Eq AttributeLimits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AttributeLimits -> AttributeLimits -> Bool
== :: AttributeLimits -> AttributeLimits -> Bool
$c/= :: AttributeLimits -> AttributeLimits -> Bool
/= :: AttributeLimits -> AttributeLimits -> Bool
Eq, Eq AttributeLimits
Eq AttributeLimits =>
(AttributeLimits -> AttributeLimits -> Ordering)
-> (AttributeLimits -> AttributeLimits -> Bool)
-> (AttributeLimits -> AttributeLimits -> Bool)
-> (AttributeLimits -> AttributeLimits -> Bool)
-> (AttributeLimits -> AttributeLimits -> Bool)
-> (AttributeLimits -> AttributeLimits -> AttributeLimits)
-> (AttributeLimits -> AttributeLimits -> AttributeLimits)
-> Ord AttributeLimits
AttributeLimits -> AttributeLimits -> Bool
AttributeLimits -> AttributeLimits -> Ordering
AttributeLimits -> AttributeLimits -> AttributeLimits
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
$ccompare :: AttributeLimits -> AttributeLimits -> Ordering
compare :: AttributeLimits -> AttributeLimits -> Ordering
$c< :: AttributeLimits -> AttributeLimits -> Bool
< :: AttributeLimits -> AttributeLimits -> Bool
$c<= :: AttributeLimits -> AttributeLimits -> Bool
<= :: AttributeLimits -> AttributeLimits -> Bool
$c> :: AttributeLimits -> AttributeLimits -> Bool
> :: AttributeLimits -> AttributeLimits -> Bool
$c>= :: AttributeLimits -> AttributeLimits -> Bool
>= :: AttributeLimits -> AttributeLimits -> Bool
$cmax :: AttributeLimits -> AttributeLimits -> AttributeLimits
max :: AttributeLimits -> AttributeLimits -> AttributeLimits
$cmin :: AttributeLimits -> AttributeLimits -> AttributeLimits
min :: AttributeLimits -> AttributeLimits -> AttributeLimits
Ord, Typeable AttributeLimits
Typeable AttributeLimits =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AttributeLimits -> c AttributeLimits)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AttributeLimits)
-> (AttributeLimits -> Constr)
-> (AttributeLimits -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AttributeLimits))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AttributeLimits))
-> ((forall b. Data b => b -> b)
-> AttributeLimits -> AttributeLimits)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AttributeLimits -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AttributeLimits -> r)
-> (forall u.
(forall d. Data d => d -> u) -> AttributeLimits -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> AttributeLimits -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> AttributeLimits -> m AttributeLimits)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AttributeLimits -> m AttributeLimits)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AttributeLimits -> m AttributeLimits)
-> Data AttributeLimits
AttributeLimits -> Constr
AttributeLimits -> DataType
(forall b. Data b => b -> b) -> AttributeLimits -> AttributeLimits
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> AttributeLimits -> u
forall u. (forall d. Data d => d -> u) -> AttributeLimits -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AttributeLimits -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AttributeLimits -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> AttributeLimits -> m AttributeLimits
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AttributeLimits -> m AttributeLimits
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AttributeLimits
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AttributeLimits -> c AttributeLimits
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AttributeLimits)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AttributeLimits)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AttributeLimits -> c AttributeLimits
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AttributeLimits -> c AttributeLimits
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AttributeLimits
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AttributeLimits
$ctoConstr :: AttributeLimits -> Constr
toConstr :: AttributeLimits -> Constr
$cdataTypeOf :: AttributeLimits -> DataType
dataTypeOf :: AttributeLimits -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AttributeLimits)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AttributeLimits)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AttributeLimits)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AttributeLimits)
$cgmapT :: (forall b. Data b => b -> b) -> AttributeLimits -> AttributeLimits
gmapT :: (forall b. Data b => b -> b) -> AttributeLimits -> AttributeLimits
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AttributeLimits -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AttributeLimits -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AttributeLimits -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AttributeLimits -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> AttributeLimits -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> AttributeLimits -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> AttributeLimits -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> AttributeLimits -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> AttributeLimits -> m AttributeLimits
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> AttributeLimits -> m AttributeLimits
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AttributeLimits -> m AttributeLimits
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AttributeLimits -> m AttributeLimits
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AttributeLimits -> m AttributeLimits
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> AttributeLimits -> m AttributeLimits
Data, (forall x. AttributeLimits -> Rep AttributeLimits x)
-> (forall x. Rep AttributeLimits x -> AttributeLimits)
-> Generic AttributeLimits
forall x. Rep AttributeLimits x -> AttributeLimits
forall x. AttributeLimits -> Rep AttributeLimits x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AttributeLimits -> Rep AttributeLimits x
from :: forall x. AttributeLimits -> Rep AttributeLimits x
$cto :: forall x. Rep AttributeLimits x -> AttributeLimits
to :: forall x. Rep AttributeLimits x -> AttributeLimits
Generic)
deriving anyclass (Eq AttributeLimits
Eq AttributeLimits =>
(Int -> AttributeLimits -> Int)
-> (AttributeLimits -> Int) -> Hashable AttributeLimits
Int -> AttributeLimits -> Int
AttributeLimits -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> AttributeLimits -> Int
hashWithSalt :: Int -> AttributeLimits -> Int
$chash :: AttributeLimits -> Int
hash :: AttributeLimits -> Int
Hashable)
class ToPrimitiveAttribute a where
toPrimitiveAttribute :: a -> PrimitiveAttribute
data Attribute
=
AttributeValue PrimitiveAttribute
|
AttributeArray [PrimitiveAttribute]
deriving stock (ReadPrec [Attribute]
ReadPrec Attribute
Int -> ReadS Attribute
ReadS [Attribute]
(Int -> ReadS Attribute)
-> ReadS [Attribute]
-> ReadPrec Attribute
-> ReadPrec [Attribute]
-> Read Attribute
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Attribute
readsPrec :: Int -> ReadS Attribute
$creadList :: ReadS [Attribute]
readList :: ReadS [Attribute]
$creadPrec :: ReadPrec Attribute
readPrec :: ReadPrec Attribute
$creadListPrec :: ReadPrec [Attribute]
readListPrec :: ReadPrec [Attribute]
Read, Int -> Attribute -> ShowS
[Attribute] -> ShowS
Attribute -> String
(Int -> Attribute -> ShowS)
-> (Attribute -> String)
-> ([Attribute] -> ShowS)
-> Show Attribute
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Attribute -> ShowS
showsPrec :: Int -> Attribute -> ShowS
$cshow :: Attribute -> String
show :: Attribute -> String
$cshowList :: [Attribute] -> ShowS
showList :: [Attribute] -> ShowS
Show, Attribute -> Attribute -> Bool
(Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool) -> Eq Attribute
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Attribute -> Attribute -> Bool
== :: Attribute -> Attribute -> Bool
$c/= :: Attribute -> Attribute -> Bool
/= :: Attribute -> Attribute -> Bool
Eq, Eq Attribute
Eq Attribute =>
(Attribute -> Attribute -> Ordering)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Attribute)
-> (Attribute -> Attribute -> Attribute)
-> Ord Attribute
Attribute -> Attribute -> Bool
Attribute -> Attribute -> Ordering
Attribute -> Attribute -> Attribute
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
$ccompare :: Attribute -> Attribute -> Ordering
compare :: Attribute -> Attribute -> Ordering
$c< :: Attribute -> Attribute -> Bool
< :: Attribute -> Attribute -> Bool
$c<= :: Attribute -> Attribute -> Bool
<= :: Attribute -> Attribute -> Bool
$c> :: Attribute -> Attribute -> Bool
> :: Attribute -> Attribute -> Bool
$c>= :: Attribute -> Attribute -> Bool
>= :: Attribute -> Attribute -> Bool
$cmax :: Attribute -> Attribute -> Attribute
max :: Attribute -> Attribute -> Attribute
$cmin :: Attribute -> Attribute -> Attribute
min :: Attribute -> Attribute -> Attribute
Ord, Typeable Attribute
Typeable Attribute =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Attribute -> c Attribute)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Attribute)
-> (Attribute -> Constr)
-> (Attribute -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Attribute))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attribute))
-> ((forall b. Data b => b -> b) -> Attribute -> Attribute)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Attribute -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Attribute -> r)
-> (forall u. (forall d. Data d => d -> u) -> Attribute -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Attribute -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Attribute -> m Attribute)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Attribute -> m Attribute)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Attribute -> m Attribute)
-> Data Attribute
Attribute -> Constr
Attribute -> DataType
(forall b. Data b => b -> b) -> Attribute -> Attribute
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Attribute -> u
forall u. (forall d. Data d => d -> u) -> Attribute -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Attribute -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Attribute -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Attribute -> m Attribute
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Attribute -> m Attribute
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Attribute
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Attribute -> c Attribute
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Attribute)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attribute)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Attribute -> c Attribute
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Attribute -> c Attribute
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Attribute
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Attribute
$ctoConstr :: Attribute -> Constr
toConstr :: Attribute -> Constr
$cdataTypeOf :: Attribute -> DataType
dataTypeOf :: Attribute -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Attribute)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Attribute)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attribute)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attribute)
$cgmapT :: (forall b. Data b => b -> b) -> Attribute -> Attribute
gmapT :: (forall b. Data b => b -> b) -> Attribute -> Attribute
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Attribute -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Attribute -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Attribute -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Attribute -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Attribute -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Attribute -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Attribute -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Attribute -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Attribute -> m Attribute
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Attribute -> m Attribute
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Attribute -> m Attribute
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Attribute -> m Attribute
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Attribute -> m Attribute
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Attribute -> m Attribute
Data, (forall x. Attribute -> Rep Attribute x)
-> (forall x. Rep Attribute x -> Attribute) -> Generic Attribute
forall x. Rep Attribute x -> Attribute
forall x. Attribute -> Rep Attribute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Attribute -> Rep Attribute x
from :: forall x. Attribute -> Rep Attribute x
$cto :: forall x. Rep Attribute x -> Attribute
to :: forall x. Rep Attribute x -> Attribute
Generic, (forall (m :: * -> *). Quote m => Attribute -> m Exp)
-> (forall (m :: * -> *). Quote m => Attribute -> Code m Attribute)
-> Lift Attribute
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Attribute -> m Exp
forall (m :: * -> *). Quote m => Attribute -> Code m Attribute
$clift :: forall (m :: * -> *). Quote m => Attribute -> m Exp
lift :: forall (m :: * -> *). Quote m => Attribute -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => Attribute -> Code m Attribute
liftTyped :: forall (m :: * -> *). Quote m => Attribute -> Code m Attribute
TH.Lift)
deriving anyclass (Eq Attribute
Eq Attribute =>
(Int -> Attribute -> Int)
-> (Attribute -> Int) -> Hashable Attribute
Int -> Attribute -> Int
Attribute -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Attribute -> Int
hashWithSalt :: Int -> Attribute -> Int
$chash :: Attribute -> Int
hash :: Attribute -> Int
Hashable)
instance IsString PrimitiveAttribute where
fromString :: String -> PrimitiveAttribute
fromString = Text -> PrimitiveAttribute
TextAttribute (Text -> PrimitiveAttribute)
-> (String -> Text) -> String -> PrimitiveAttribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. IsString a => String -> a
fromString
instance IsString Attribute where
fromString :: String -> Attribute
fromString = PrimitiveAttribute -> Attribute
AttributeValue (PrimitiveAttribute -> Attribute)
-> (String -> PrimitiveAttribute) -> String -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> PrimitiveAttribute
forall a. IsString a => String -> a
fromString
data PrimitiveAttribute
= TextAttribute Text
| BoolAttribute Bool
| DoubleAttribute Double
| IntAttribute Int64
deriving stock (ReadPrec [PrimitiveAttribute]
ReadPrec PrimitiveAttribute
Int -> ReadS PrimitiveAttribute
ReadS [PrimitiveAttribute]
(Int -> ReadS PrimitiveAttribute)
-> ReadS [PrimitiveAttribute]
-> ReadPrec PrimitiveAttribute
-> ReadPrec [PrimitiveAttribute]
-> Read PrimitiveAttribute
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PrimitiveAttribute
readsPrec :: Int -> ReadS PrimitiveAttribute
$creadList :: ReadS [PrimitiveAttribute]
readList :: ReadS [PrimitiveAttribute]
$creadPrec :: ReadPrec PrimitiveAttribute
readPrec :: ReadPrec PrimitiveAttribute
$creadListPrec :: ReadPrec [PrimitiveAttribute]
readListPrec :: ReadPrec [PrimitiveAttribute]
Read, Int -> PrimitiveAttribute -> ShowS
[PrimitiveAttribute] -> ShowS
PrimitiveAttribute -> String
(Int -> PrimitiveAttribute -> ShowS)
-> (PrimitiveAttribute -> String)
-> ([PrimitiveAttribute] -> ShowS)
-> Show PrimitiveAttribute
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PrimitiveAttribute -> ShowS
showsPrec :: Int -> PrimitiveAttribute -> ShowS
$cshow :: PrimitiveAttribute -> String
show :: PrimitiveAttribute -> String
$cshowList :: [PrimitiveAttribute] -> ShowS
showList :: [PrimitiveAttribute] -> ShowS
Show, PrimitiveAttribute -> PrimitiveAttribute -> Bool
(PrimitiveAttribute -> PrimitiveAttribute -> Bool)
-> (PrimitiveAttribute -> PrimitiveAttribute -> Bool)
-> Eq PrimitiveAttribute
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PrimitiveAttribute -> PrimitiveAttribute -> Bool
== :: PrimitiveAttribute -> PrimitiveAttribute -> Bool
$c/= :: PrimitiveAttribute -> PrimitiveAttribute -> Bool
/= :: PrimitiveAttribute -> PrimitiveAttribute -> Bool
Eq, Eq PrimitiveAttribute
Eq PrimitiveAttribute =>
(PrimitiveAttribute -> PrimitiveAttribute -> Ordering)
-> (PrimitiveAttribute -> PrimitiveAttribute -> Bool)
-> (PrimitiveAttribute -> PrimitiveAttribute -> Bool)
-> (PrimitiveAttribute -> PrimitiveAttribute -> Bool)
-> (PrimitiveAttribute -> PrimitiveAttribute -> Bool)
-> (PrimitiveAttribute -> PrimitiveAttribute -> PrimitiveAttribute)
-> (PrimitiveAttribute -> PrimitiveAttribute -> PrimitiveAttribute)
-> Ord PrimitiveAttribute
PrimitiveAttribute -> PrimitiveAttribute -> Bool
PrimitiveAttribute -> PrimitiveAttribute -> Ordering
PrimitiveAttribute -> PrimitiveAttribute -> PrimitiveAttribute
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
$ccompare :: PrimitiveAttribute -> PrimitiveAttribute -> Ordering
compare :: PrimitiveAttribute -> PrimitiveAttribute -> Ordering
$c< :: PrimitiveAttribute -> PrimitiveAttribute -> Bool
< :: PrimitiveAttribute -> PrimitiveAttribute -> Bool
$c<= :: PrimitiveAttribute -> PrimitiveAttribute -> Bool
<= :: PrimitiveAttribute -> PrimitiveAttribute -> Bool
$c> :: PrimitiveAttribute -> PrimitiveAttribute -> Bool
> :: PrimitiveAttribute -> PrimitiveAttribute -> Bool
$c>= :: PrimitiveAttribute -> PrimitiveAttribute -> Bool
>= :: PrimitiveAttribute -> PrimitiveAttribute -> Bool
$cmax :: PrimitiveAttribute -> PrimitiveAttribute -> PrimitiveAttribute
max :: PrimitiveAttribute -> PrimitiveAttribute -> PrimitiveAttribute
$cmin :: PrimitiveAttribute -> PrimitiveAttribute -> PrimitiveAttribute
min :: PrimitiveAttribute -> PrimitiveAttribute -> PrimitiveAttribute
Ord, Typeable PrimitiveAttribute
Typeable PrimitiveAttribute =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PrimitiveAttribute
-> c PrimitiveAttribute)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrimitiveAttribute)
-> (PrimitiveAttribute -> Constr)
-> (PrimitiveAttribute -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrimitiveAttribute))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PrimitiveAttribute))
-> ((forall b. Data b => b -> b)
-> PrimitiveAttribute -> PrimitiveAttribute)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveAttribute -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveAttribute -> r)
-> (forall u.
(forall d. Data d => d -> u) -> PrimitiveAttribute -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PrimitiveAttribute -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PrimitiveAttribute -> m PrimitiveAttribute)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveAttribute -> m PrimitiveAttribute)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveAttribute -> m PrimitiveAttribute)
-> Data PrimitiveAttribute
PrimitiveAttribute -> Constr
PrimitiveAttribute -> DataType
(forall b. Data b => b -> b)
-> PrimitiveAttribute -> PrimitiveAttribute
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> PrimitiveAttribute -> u
forall u. (forall d. Data d => d -> u) -> PrimitiveAttribute -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveAttribute -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveAttribute -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PrimitiveAttribute -> m PrimitiveAttribute
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveAttribute -> m PrimitiveAttribute
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrimitiveAttribute
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PrimitiveAttribute
-> c PrimitiveAttribute
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrimitiveAttribute)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PrimitiveAttribute)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PrimitiveAttribute
-> c PrimitiveAttribute
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PrimitiveAttribute
-> c PrimitiveAttribute
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrimitiveAttribute
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrimitiveAttribute
$ctoConstr :: PrimitiveAttribute -> Constr
toConstr :: PrimitiveAttribute -> Constr
$cdataTypeOf :: PrimitiveAttribute -> DataType
dataTypeOf :: PrimitiveAttribute -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrimitiveAttribute)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrimitiveAttribute)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PrimitiveAttribute)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PrimitiveAttribute)
$cgmapT :: (forall b. Data b => b -> b)
-> PrimitiveAttribute -> PrimitiveAttribute
gmapT :: (forall b. Data b => b -> b)
-> PrimitiveAttribute -> PrimitiveAttribute
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveAttribute -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveAttribute -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveAttribute -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrimitiveAttribute -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PrimitiveAttribute -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> PrimitiveAttribute -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PrimitiveAttribute -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PrimitiveAttribute -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PrimitiveAttribute -> m PrimitiveAttribute
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PrimitiveAttribute -> m PrimitiveAttribute
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveAttribute -> m PrimitiveAttribute
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveAttribute -> m PrimitiveAttribute
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveAttribute -> m PrimitiveAttribute
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PrimitiveAttribute -> m PrimitiveAttribute
Data, (forall x. PrimitiveAttribute -> Rep PrimitiveAttribute x)
-> (forall x. Rep PrimitiveAttribute x -> PrimitiveAttribute)
-> Generic PrimitiveAttribute
forall x. Rep PrimitiveAttribute x -> PrimitiveAttribute
forall x. PrimitiveAttribute -> Rep PrimitiveAttribute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PrimitiveAttribute -> Rep PrimitiveAttribute x
from :: forall x. PrimitiveAttribute -> Rep PrimitiveAttribute x
$cto :: forall x. Rep PrimitiveAttribute x -> PrimitiveAttribute
to :: forall x. Rep PrimitiveAttribute x -> PrimitiveAttribute
Generic, (forall (m :: * -> *). Quote m => PrimitiveAttribute -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
PrimitiveAttribute -> Code m PrimitiveAttribute)
-> Lift PrimitiveAttribute
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => PrimitiveAttribute -> m Exp
forall (m :: * -> *).
Quote m =>
PrimitiveAttribute -> Code m PrimitiveAttribute
$clift :: forall (m :: * -> *). Quote m => PrimitiveAttribute -> m Exp
lift :: forall (m :: * -> *). Quote m => PrimitiveAttribute -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
PrimitiveAttribute -> Code m PrimitiveAttribute
liftTyped :: forall (m :: * -> *).
Quote m =>
PrimitiveAttribute -> Code m PrimitiveAttribute
TH.Lift)
deriving anyclass (Eq PrimitiveAttribute
Eq PrimitiveAttribute =>
(Int -> PrimitiveAttribute -> Int)
-> (PrimitiveAttribute -> Int) -> Hashable PrimitiveAttribute
Int -> PrimitiveAttribute -> Int
PrimitiveAttribute -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> PrimitiveAttribute -> Int
hashWithSalt :: Int -> PrimitiveAttribute -> Int
$chash :: PrimitiveAttribute -> Int
hash :: PrimitiveAttribute -> Int
Hashable)
class ToAttribute a where
toAttribute :: a -> Attribute
default toAttribute :: (ToPrimitiveAttribute a) => a -> Attribute
toAttribute = PrimitiveAttribute -> Attribute
AttributeValue (PrimitiveAttribute -> Attribute)
-> (a -> PrimitiveAttribute) -> a -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> PrimitiveAttribute
forall a. ToPrimitiveAttribute a => a -> PrimitiveAttribute
toPrimitiveAttribute
instance ToPrimitiveAttribute PrimitiveAttribute where
toPrimitiveAttribute :: PrimitiveAttribute -> PrimitiveAttribute
toPrimitiveAttribute = PrimitiveAttribute -> PrimitiveAttribute
forall a. a -> a
id
instance ToAttribute PrimitiveAttribute where
toAttribute :: PrimitiveAttribute -> Attribute
toAttribute = PrimitiveAttribute -> Attribute
AttributeValue
instance ToPrimitiveAttribute Text where
toPrimitiveAttribute :: Text -> PrimitiveAttribute
toPrimitiveAttribute = Text -> PrimitiveAttribute
TextAttribute
instance ToAttribute Text
instance ToPrimitiveAttribute Bool where
toPrimitiveAttribute :: Bool -> PrimitiveAttribute
toPrimitiveAttribute = Bool -> PrimitiveAttribute
BoolAttribute
instance ToAttribute Bool
instance ToPrimitiveAttribute Double where
toPrimitiveAttribute :: Double -> PrimitiveAttribute
toPrimitiveAttribute = Double -> PrimitiveAttribute
DoubleAttribute
instance ToAttribute Double
instance ToPrimitiveAttribute Int64 where
toPrimitiveAttribute :: Int64 -> PrimitiveAttribute
toPrimitiveAttribute = Int64 -> PrimitiveAttribute
IntAttribute
instance ToAttribute Int64
instance ToPrimitiveAttribute Int where
toPrimitiveAttribute :: Int -> PrimitiveAttribute
toPrimitiveAttribute = Int64 -> PrimitiveAttribute
IntAttribute (Int64 -> PrimitiveAttribute)
-> (Int -> Int64) -> Int -> PrimitiveAttribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance ToAttribute Int
instance ToAttribute Attribute where
toAttribute :: Attribute -> Attribute
toAttribute = Attribute -> Attribute
forall a. a -> a
id
instance (ToPrimitiveAttribute a) => ToAttribute [a] where
toAttribute :: [a] -> Attribute
toAttribute = [PrimitiveAttribute] -> Attribute
AttributeArray ([PrimitiveAttribute] -> Attribute)
-> ([a] -> [PrimitiveAttribute]) -> [a] -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> PrimitiveAttribute) -> [a] -> [PrimitiveAttribute]
forall a b. (a -> b) -> [a] -> [b]
map a -> PrimitiveAttribute
forall a. ToPrimitiveAttribute a => a -> PrimitiveAttribute
toPrimitiveAttribute
unsafeMergeAttributesIgnoringLimits :: Attributes -> Attributes -> Attributes
unsafeMergeAttributesIgnoringLimits :: Attributes -> Attributes -> Attributes
unsafeMergeAttributesIgnoringLimits Attributes
left Attributes
right = HashMap Text Attribute -> Int -> Int -> Attributes
Attributes HashMap Text Attribute
hm Int
c Int
d
where
hm :: HashMap Text Attribute
hm = Attributes -> HashMap Text Attribute
attributes Attributes
left HashMap Text Attribute
-> HashMap Text Attribute -> HashMap Text Attribute
forall a. Semigroup a => a -> a -> a
<> Attributes -> HashMap Text Attribute
attributes Attributes
right
c :: Int
c = HashMap Text Attribute -> Int
forall k v. HashMap k v -> Int
H.size HashMap Text Attribute
hm
d :: Int
d = Attributes -> Int
attributesDropped Attributes
left Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Attributes -> Int
attributesDropped Attributes
right
unsafeAttributesFromListIgnoringLimits :: [(Text, Attribute)] -> Attributes
unsafeAttributesFromListIgnoringLimits :: [(Text, Attribute)] -> Attributes
unsafeAttributesFromListIgnoringLimits [(Text, Attribute)]
l = HashMap Text Attribute -> Int -> Int -> Attributes
Attributes HashMap Text Attribute
hm Int
c Int
0
where
hm :: HashMap Text Attribute
hm = [(Text, Attribute)] -> HashMap Text Attribute
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
H.fromList [(Text, Attribute)]
l
c :: Int
c = HashMap Text Attribute -> Int
forall k v. HashMap k v -> Int
H.size HashMap Text Attribute
hm