antiope-messages-7.5.0: Please see the README on Github at <https://github.com/arbor/antiope#readme>

Safe HaskellNone
LanguageHaskell2010

Antiope.Messages.Types

Synopsis

Documentation

newtype WithEncoded (fld :: Symbol) a Source #

Represents a JSON value of type a that is encoded as a string in a field fld

Constructors

WithEncoded a 
Instances
FromWith (WithEncoded x) Source # 
Instance details

Defined in Antiope.Messages.Types

Methods

fromWith :: WithEncoded x a -> a Source #

Eq a => Eq (WithEncoded fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

Methods

(==) :: WithEncoded fld a -> WithEncoded fld a -> Bool #

(/=) :: WithEncoded fld a -> WithEncoded fld a -> Bool #

Ord a => Ord (WithEncoded fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

Methods

compare :: WithEncoded fld a -> WithEncoded fld a -> Ordering #

(<) :: WithEncoded fld a -> WithEncoded fld a -> Bool #

(<=) :: WithEncoded fld a -> WithEncoded fld a -> Bool #

(>) :: WithEncoded fld a -> WithEncoded fld a -> Bool #

(>=) :: WithEncoded fld a -> WithEncoded fld a -> Bool #

max :: WithEncoded fld a -> WithEncoded fld a -> WithEncoded fld a #

min :: WithEncoded fld a -> WithEncoded fld a -> WithEncoded fld a #

Show a => Show (WithEncoded fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

Methods

showsPrec :: Int -> WithEncoded fld a -> ShowS #

show :: WithEncoded fld a -> String #

showList :: [WithEncoded fld a] -> ShowS #

Generic (WithEncoded fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

Associated Types

type Rep (WithEncoded fld a) :: Type -> Type #

Methods

from :: WithEncoded fld a -> Rep (WithEncoded fld a) x #

to :: Rep (WithEncoded fld a) x -> WithEncoded fld a #

(KnownSymbol fld, ToJSON a) => ToJSON (WithEncoded fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

(KnownSymbol fld, FromJSON a) => FromJSON (WithEncoded fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

type Rep (WithEncoded fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

type Rep (WithEncoded fld a) = D1 (MetaData "WithEncoded" "Antiope.Messages.Types" "antiope-messages-7.5.0-JfE6Nr6AI4H6n1MUDSzcdn" True) (C1 (MetaCons "WithEncoded" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype With (fld :: Symbol) a Source #

Represents a JSON value of type a in a field fld

Constructors

With a 
Instances
FromWith (With x) Source # 
Instance details

Defined in Antiope.Messages.Types

Methods

fromWith :: With x a -> a Source #

Eq a => Eq (With fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

Methods

(==) :: With fld a -> With fld a -> Bool #

(/=) :: With fld a -> With fld a -> Bool #

Ord a => Ord (With fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

Methods

compare :: With fld a -> With fld a -> Ordering #

(<) :: With fld a -> With fld a -> Bool #

(<=) :: With fld a -> With fld a -> Bool #

(>) :: With fld a -> With fld a -> Bool #

(>=) :: With fld a -> With fld a -> Bool #

max :: With fld a -> With fld a -> With fld a #

min :: With fld a -> With fld a -> With fld a #

Show a => Show (With fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

Methods

showsPrec :: Int -> With fld a -> ShowS #

show :: With fld a -> String #

showList :: [With fld a] -> ShowS #

Generic (With fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

Associated Types

type Rep (With fld a) :: Type -> Type #

Methods

from :: With fld a -> Rep (With fld a) x #

to :: Rep (With fld a) x -> With fld a #

(KnownSymbol fld, ToJSON a) => ToJSON (With fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

Methods

toJSON :: With fld a -> Value #

toEncoding :: With fld a -> Encoding #

toJSONList :: [With fld a] -> Value #

toEncodingList :: [With fld a] -> Encoding #

(KnownSymbol fld, FromJSON a) => FromJSON (With fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

Methods

parseJSON :: Value -> Parser (With fld a) #

parseJSONList :: Value -> Parser [With fld a] #

type Rep (With fld a) Source # 
Instance details

Defined in Antiope.Messages.Types

type Rep (With fld a) = D1 (MetaData "With" "Antiope.Messages.Types" "antiope-messages-7.5.0-JfE6Nr6AI4H6n1MUDSzcdn" True) (C1 (MetaCons "With" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

class FromWith f where Source #

Extracts value from With and WithEncoded wrappers

Will probably be deprecated soon, try using coerce instead.

Methods

fromWith Source #

Arguments

:: f a 
-> a

Extracts value from With and WithEncoded

Instances
FromWith (With x) Source # 
Instance details

Defined in Antiope.Messages.Types

Methods

fromWith :: With x a -> a Source #

FromWith (WithEncoded x) Source # 
Instance details

Defined in Antiope.Messages.Types

Methods

fromWith :: WithEncoded x a -> a Source #

fromWith2 :: (FromWith f, FromWith g) => f (g a) -> a Source #

Extracts a value from any combination of two With and/or WithEncoded

fromWith2 @(With "one" (WithEncoded "two" True)) == True

fromWith3 :: (FromWith f, FromWith g, FromWith h) => f (g (h a)) -> a Source #

Extracts a value from any combination of two With and/or WithEncoded

fromWith3 @(With "one" (WithEncoded "two" (With "three" True))) == True

fromWith4 :: (FromWith f, FromWith g, FromWith h, FromWith k) => f (g (h (k a))) -> a Source #

fromWith5 :: (FromWith f, FromWith g, FromWith h, FromWith k, FromWith p) => f (g (h (k (p a)))) -> a Source #

fromWith6 :: (FromWith f, FromWith g, FromWith h, FromWith k, FromWith p, FromWith q) => f (g (h (k (p (q a))))) -> a Source #