{-# LANGUAGE CPP #-}{-# LANGUAGE DeriveDataTypeable #-}{-# LANGUAGE GADTs #-}{-# LANGUAGE TemplateHaskellQuotes #-}-- |-- Strong type for JSON keys.---- @since 2.0.0.0moduleData.Aeson.Key(Key ,fromString ,toString ,toText ,fromText ,coercionToText ,toShortText ,fromShortText ,)whereimportPrelude(Eq,Ord,(.),Show(..),String,Maybe(..))importControl.Applicative((<$>))importControl.DeepSeq(NFData(..))importData.Data(Data)importData.Hashable(Hashable(..))importData.Monoid(Monoid(mempty,mappend))importData.Semigroup(Semigroup((<>)))importData.Text(Text)importData.Type.Coercion(Coercion(..))importData.Typeable(Typeable)importText.Read(Read(..))importqualifiedData.StringimportqualifiedData.TextasTimportqualifiedData.Text.ShortasSTimportqualifiedLanguage.Haskell.TH.SyntaxasTHimportqualifiedTest.QuickCheckasQCnewtypeKey =Key {Key -> Text
unKey ::Text}deriving(Key -> Key -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c== :: Key -> Key -> Bool
Eq,Eq Key
Key -> Key -> Bool
Key -> Key -> Ordering
Key -> Key -> Key
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
min :: Key -> Key -> Key
$cmin :: Key -> Key -> Key
max :: Key -> Key -> Key
$cmax :: Key -> Key -> Key
>= :: Key -> Key -> Bool
$c>= :: Key -> Key -> Bool
> :: Key -> Key -> Bool
$c> :: Key -> Key -> Bool
<= :: Key -> Key -> Bool
$c<= :: Key -> Key -> Bool
< :: Key -> Key -> Bool
$c< :: Key -> Key -> Bool
compare :: Key -> Key -> Ordering
$ccompare :: Key -> Key -> Ordering
Ord,Typeable,Typeable Key
Key -> DataType
Key -> Constr
(forall b. Data b => b -> b) -> Key -> Key
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) -> Key -> u
forall u. (forall d. Data d => d -> u) -> Key -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Key -> m Key
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Key -> m Key
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Key
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Key -> c Key
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Key)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Key)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Key -> m Key
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Key -> m Key
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Key -> m Key
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Key -> m Key
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Key -> m Key
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Key -> m Key
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Key -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Key -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Key -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Key -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r
gmapT :: (forall b. Data b => b -> b) -> Key -> Key
$cgmapT :: (forall b. Data b => b -> b) -> Key -> Key
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Key)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Key)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Key)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Key)
dataTypeOf :: Key -> DataType
$cdataTypeOf :: Key -> DataType
toConstr :: Key -> Constr
$ctoConstr :: Key -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Key
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Key
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Key -> c Key
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Key -> c Key
Data)fromString ::String->Key fromString :: String -> Key
fromString =Text -> Key
Key forall b c a. (b -> c) -> (a -> b) -> a -> c
.String -> Text
T.packtoString ::Key ->StringtoString :: Key -> String
toString (Key Text
k )=Text -> String
T.unpackText
k fromText ::Text->Key fromText :: Text -> Key
fromText =Text -> Key
Key toText ::Key ->TexttoText :: Key -> Text
toText =Key -> Text
unKey -- | @'coercing r1 r2'@ will evaluate to @r1@ if 'Key' is 'Coercible' to 'Text',-- and to @r2@ otherwise.---- Using 'coercing' we can make more efficient implementations-- when 'Key' is backed up by 'Text' without exposing internals.-- coercionToText ::Maybe(CoercionKey Text)coercionToText :: Maybe (Coercion Key Text)
coercionToText =forall a. a -> Maybe a
Justforall {k} (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion{-# INLINEcoercionToText #-}-- | @since 2.0.2.0toShortText ::Key ->ST.ShortTexttoShortText :: Key -> ShortText
toShortText =Text -> ShortText
ST.fromTextforall b c a. (b -> c) -> (a -> b) -> a -> c
.Key -> Text
unKey -- | @since 2.0.2.0fromShortText ::ST.ShortText->Key fromShortText :: ShortText -> Key
fromShortText =Text -> Key
Key forall b c a. (b -> c) -> (a -> b) -> a -> c
.ShortText -> Text
ST.toText--------------------------------------------------------------------------------- instances-------------------------------------------------------------------------------instanceReadKey wherereadPrec :: ReadPrec Key
readPrec=String -> Key
fromString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>forall a. Read a => ReadPrec a
readPrecinstanceShowKey whereshowsPrec :: Int -> Key -> ShowS
showsPrecInt
d (Key Text
k )=forall a. Show a => Int -> a -> ShowS
showsPrecInt
d Text
k instanceData.String.IsStringKey wherefromString :: String -> Key
fromString=String -> Key
fromString instanceHashableKey wherehashWithSalt :: Int -> Key -> Int
hashWithSaltInt
salt (Key Text
k )=forall a. Hashable a => Int -> a -> Int
hashWithSaltInt
salt Text
k instanceNFDataKey wherernf :: Key -> ()
rnf(Key Text
k )=forall a. NFData a => a -> ()
rnfText
k instanceSemigroupKey whereKey Text
x <> :: Key -> Key -> Key
<>Key Text
y =Text -> Key
Key (Text
x forall a. Semigroup a => a -> a -> a
<>Text
y )instanceMonoidKey wheremempty :: Key
mempty=Text -> Key
Key forall a. Monoid a => a
memptymappend :: Key -> Key -> Key
mappend=forall a. Semigroup a => a -> a -> a
(<>)instanceTH.LiftKey where
#if MIN_VERSION_text(1,2,4)
lift :: forall (m :: * -> *). Quote m => Key -> m Exp
lift(Key Text
k )=[|Keyk|]
#else
liftk=[|fromStringk'|]wherek'=toStringk
#endif

#if MIN_VERSION_template_haskell(2,17,0)
liftTyped :: forall (m :: * -> *). Quote m => Key -> Code m Key
liftTyped=forall a (m :: * -> *). Quote m => m Exp -> Code m a
TH.unsafeCodeCoerceforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
TH.lift
#elif MIN_VERSION_template_haskell(2,16,0)
liftTyped=TH.unsafeTExpCoerce.TH.lift
#endif
-- | @since 2.0.3.0instanceQC.ArbitraryKey wherearbitrary :: Gen Key
arbitrary=String -> Key
fromString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>forall a. Arbitrary a => Gen a
QC.arbitraryshrink :: Key -> [Key]
shrinkKey
k =String -> Key
fromString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>forall a. Arbitrary a => a -> [a]
QC.shrink(Key -> String
toString Key
k )-- | @since 2.0.3.0instanceQC.CoArbitraryKey wherecoarbitrary :: forall b. Key -> Gen b -> Gen b
coarbitrary=forall a b. CoArbitrary a => a -> Gen b -> Gen b
QC.coarbitraryforall b c a. (b -> c) -> (a -> b) -> a -> c
.Key -> String
toString -- | @since 2.0.3.0instanceQC.FunctionKey wherefunction :: forall b. (Key -> b) -> Key :-> b
function=forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
QC.functionMapKey -> String
toString String -> Key
fromString 

AltStyle によって変換されたページ (->オリジナル) /