morpheus-graphql-0.0.1: Morpheus GraphQL

Safe HaskellSafe
LanguageHaskell2010

Data.Morpheus.Types.Describer

Documentation

newtype a ::-> b Source #

Constructors

Resolver (a -> IO (Either String b)) 
Instances
(Data a, Data b) => Data (a ::-> b) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a ::-> b) -> c (a ::-> b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a ::-> b) #

toConstr :: (a ::-> b) -> Constr #

dataTypeOf :: (a ::-> b) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a ::-> b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a ::-> b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a ::-> b) -> a ::-> b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a ::-> b) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a ::-> b) -> r #

gmapQ :: (forall d. Data d => d -> u) -> (a ::-> b) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> (a ::-> b) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a ::-> b) -> m (a ::-> b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a ::-> b) -> m (a ::-> b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a ::-> b) -> m (a ::-> b) #

Show (a ::-> b) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Methods

showsPrec :: Int -> (a ::-> b) -> ShowS #

show :: (a ::-> b) -> String #

showList :: [a ::-> b] -> ShowS #

Generic (a ::-> b) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Associated Types

type Rep (a ::-> b) :: Type -> Type #

Methods

from :: (a ::-> b) -> Rep (a ::-> b) x #

to :: Rep (a ::-> b) x -> a ::-> b #

(GQLObject a, GQLArgs p) => GQLObject (p ::-> a) Source # 
Instance details

Defined in Data.Morpheus.Kind.GQLObject

type Rep (a ::-> b) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

type Rep (a ::-> b) = D1 (MetaData "::->" "Data.Morpheus.Types.Describer" "morpheus-graphql-0.0.1-9yOQmuk6QYrGODa72tt3vl" True) (C1 (MetaCons "Resolver" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (a -> IO (Either String b)))))

newtype WithDeprecationArgs a Source #

Constructors

WithDeprecationArgs 
Instances
Data a => Data (WithDeprecationArgs a) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WithDeprecationArgs a -> c (WithDeprecationArgs a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WithDeprecationArgs a) #

toConstr :: WithDeprecationArgs a -> Constr #

dataTypeOf :: WithDeprecationArgs a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WithDeprecationArgs a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WithDeprecationArgs a)) #

gmapT :: (forall b. Data b => b -> b) -> WithDeprecationArgs a -> WithDeprecationArgs a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WithDeprecationArgs a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WithDeprecationArgs a -> r #

gmapQ :: (forall d. Data d => d -> u) -> WithDeprecationArgs a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WithDeprecationArgs a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WithDeprecationArgs a -> m (WithDeprecationArgs a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WithDeprecationArgs a -> m (WithDeprecationArgs a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WithDeprecationArgs a -> m (WithDeprecationArgs a) #

Show a => Show (WithDeprecationArgs a) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Generic (WithDeprecationArgs a) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Associated Types

type Rep (WithDeprecationArgs a) :: Type -> Type #

GQLObject a => GQLObject (WithDeprecationArgs a) Source # 
Instance details

Defined in Data.Morpheus.Kind.GQLObject

type Rep (WithDeprecationArgs a) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

type Rep (WithDeprecationArgs a) = D1 (MetaData "WithDeprecationArgs" "Data.Morpheus.Types.Describer" "morpheus-graphql-0.0.1-9yOQmuk6QYrGODa72tt3vl" True) (C1 (MetaCons "WithDeprecationArgs" PrefixI True) (S1 (MetaSel (Just "unpackDeprecationArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype EnumOf a Source #

Constructors

EnumOf 

Fields

Instances
Functor EnumOf Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Methods

fmap :: (a -> b) -> EnumOf a -> EnumOf b #

(<$) :: a -> EnumOf b -> EnumOf a #

Applicative EnumOf Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Methods

pure :: a -> EnumOf a #

(<*>) :: EnumOf (a -> b) -> EnumOf a -> EnumOf b #

liftA2 :: (a -> b -> c) -> EnumOf a -> EnumOf b -> EnumOf c #

(*>) :: EnumOf a -> EnumOf b -> EnumOf b #

(<*) :: EnumOf a -> EnumOf b -> EnumOf a #

Data a => Data (EnumOf a) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnumOf a -> c (EnumOf a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (EnumOf a) #

toConstr :: EnumOf a -> Constr #

dataTypeOf :: EnumOf a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (EnumOf a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (EnumOf a)) #

gmapT :: (forall b. Data b => b -> b) -> EnumOf a -> EnumOf a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnumOf a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnumOf a -> r #

gmapQ :: (forall d. Data d => d -> u) -> EnumOf a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EnumOf a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnumOf a -> m (EnumOf a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumOf a -> m (EnumOf a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumOf a -> m (EnumOf a) #

Show a => Show (EnumOf a) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Methods

showsPrec :: Int -> EnumOf a -> ShowS #

show :: EnumOf a -> String #

showList :: [EnumOf a] -> ShowS #

Generic (EnumOf a) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Associated Types

type Rep (EnumOf a) :: Type -> Type #

Methods

from :: EnumOf a -> Rep (EnumOf a) x #

to :: Rep (EnumOf a) x -> EnumOf a #

(GQLEnum a, GQLKind a) => GQLInput (EnumOf a) Source # 
Instance details

Defined in Data.Morpheus.Kind.GQLInput

(Show a, GQLKind a, GQLEnum a) => GQLObject (EnumOf a) Source # 
Instance details

Defined in Data.Morpheus.Kind.GQLObject

type Rep (EnumOf a) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

type Rep (EnumOf a) = D1 (MetaData "EnumOf" "Data.Morpheus.Types.Describer" "morpheus-graphql-0.0.1-9yOQmuk6QYrGODa72tt3vl" True) (C1 (MetaCons "EnumOf" PrefixI True) (S1 (MetaSel (Just "unpackEnum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype ScalarOf a Source #

Constructors

ScalarOf 

Fields

Instances
Data a => Data (ScalarOf a) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScalarOf a -> c (ScalarOf a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ScalarOf a) #

toConstr :: ScalarOf a -> Constr #

dataTypeOf :: ScalarOf a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ScalarOf a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ScalarOf a)) #

gmapT :: (forall b. Data b => b -> b) -> ScalarOf a -> ScalarOf a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScalarOf a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScalarOf a -> r #

gmapQ :: (forall d. Data d => d -> u) -> ScalarOf a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ScalarOf a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScalarOf a -> m (ScalarOf a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalarOf a -> m (ScalarOf a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalarOf a -> m (ScalarOf a) #

Show a => Show (ScalarOf a) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Methods

showsPrec :: Int -> ScalarOf a -> ShowS #

show :: ScalarOf a -> String #

showList :: [ScalarOf a] -> ShowS #

Generic (ScalarOf a) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

Associated Types

type Rep (ScalarOf a) :: Type -> Type #

Methods

from :: ScalarOf a -> Rep (ScalarOf a) x #

to :: Rep (ScalarOf a) x -> ScalarOf a #

(GQLScalar a, GQLKind a) => GQLInput (ScalarOf a) Source # 
Instance details

Defined in Data.Morpheus.Kind.GQLInput

GQLScalar a => GQLObject (ScalarOf a) Source # 
Instance details

Defined in Data.Morpheus.Kind.GQLObject

type Rep (ScalarOf a) Source # 
Instance details

Defined in Data.Morpheus.Types.Describer

type Rep (ScalarOf a) = D1 (MetaData "ScalarOf" "Data.Morpheus.Types.Describer" "morpheus-graphql-0.0.1-9yOQmuk6QYrGODa72tt3vl" True) (C1 (MetaCons "ScalarOf" PrefixI True) (S1 (MetaSel (Just "unpackScalar") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))