json-autotype-2.0.0: Automatic type declaration for JSON input data

Safe HaskellNone
LanguageHaskell2010

Data.Aeson.AutoType.Type

Description

Union types describing JSON objects, and operations for querying these types.

Synopsis

Documentation

typeSize :: Type -> Int Source #

Size of the Type term.

newtype Dict Source #

Dictionary of types indexed by names.

Constructors

Dict 

Fields

Instances
Eq Dict Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

Methods

(==) :: Dict -> Dict -> Bool #

(/=) :: Dict -> Dict -> Bool #

Data Dict Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

Methods

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

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

toConstr :: Dict -> Constr #

dataTypeOf :: Dict -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Dict Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

Methods

compare :: Dict -> Dict -> Ordering #

(<) :: Dict -> Dict -> Bool #

(<=) :: Dict -> Dict -> Bool #

(>) :: Dict -> Dict -> Bool #

(>=) :: Dict -> Dict -> Bool #

max :: Dict -> Dict -> Dict #

min :: Dict -> Dict -> Dict #

Show Dict Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

Methods

showsPrec :: Int -> Dict -> ShowS #

show :: Dict -> String #

showList :: [Dict] -> ShowS #

Generic Dict Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

Associated Types

type Rep Dict :: * -> * #

Methods

from :: Dict -> Rep Dict x #

to :: Rep Dict x -> Dict #

Out Dict Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

Methods

docPrec :: Int -> Dict -> Doc #

doc :: Dict -> Doc #

docList :: [Dict] -> Doc #

type Rep Dict Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

type Rep Dict

keys :: Dict -> Set Text Source #

Take all keys from dictionary.

get :: Text -> Dict -> Type Source #

Lookup the Type within the dictionary.

withDict :: (Map Text Type -> Map Text Type) -> Dict -> Dict Source #

Make operation on a map to an operation on a Dict.

data Type Source #

Union types for JSON values.

Instances
Eq Type Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Data Type Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Type Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

Methods

compare :: Type -> Type -> Ordering #

(<) :: Type -> Type -> Bool #

(<=) :: Type -> Type -> Bool #

(>) :: Type -> Type -> Bool #

(>=) :: Type -> Type -> Bool #

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Show Type Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Generic Type Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

Associated Types

type Rep Type :: * -> * #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Out Type Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

Methods

docPrec :: Int -> Type -> Doc #

doc :: Type -> Doc #

docList :: [Type] -> Doc #

Uniplate Type Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

type Rep Type Source # 
Instance details

Defined in Data.Aeson.AutoType.Type

emptyType :: Type Source #

Empty type

isSimple :: Type -> Bool Source #

Is it a simple (non-compound) Type?

isArray :: Type -> Bool Source #

Is the top-level constructor a TArray? | Check if the given type has non-top TObj.

isObject :: Type -> Bool Source #

Is the top-level constructor a TObj?

typeAsSet :: Type -> Set Type Source #

Convert any type into union type (even if just singleton).

hasNonTopTObj :: Type -> Bool Source #

Check if the given type has non-top TObj.

hasTObj :: Type -> Bool Source #

Check if the given type has TObj on top or within array..

isNullable :: Type -> Bool Source #

Check if this is nullable (Maybe) type, or not. Nullable type will always accept TNull or missing key that contains it.

emptySetLikes :: Set Type Source #

"Null-ish" types