json-to-type-4.0.1: Automatic type declaration for JSON input data
Safe HaskellSafe-Inferred
LanguageHaskell2010

JsonToType.Extract

Description

Extraction and unification of AutoType's Type from Aeson Value.

Synopsis

Documentation

valueSize :: Value -> Int Source #

Compute total number of nodes (and leaves) within the value tree. Each simple JavaScript type (including String) is counted as of size 1, whereas both Array or object types are counted as 1+sum of the sizes of their member values.

valueTypeSize :: Value -> Int Source #

Compute total size of the type of the Value. For: * simple types it is always 1, * for arrays it is just 1+_maximum_ size of the (single) element type, * for objects it is _sum_ of the sizes of fields (since each field type is assumed to be different.)

valueDepth :: Value -> Int Source #

Compute total depth of the value. For: * simple types it is 1 * for either Array or Object, it is 1 + maximum of depths of their members

newtype Dict Source #

Dictionary of types indexed by names.

Constructors

Dict 

Fields

Instances

Instances details
Out Dict Source # 
Instance details

Defined in JsonToType.Pretty

Methods

docPrec :: Int -> Dict -> Doc #

doc :: Dict -> Doc #

docList :: [Dict] -> Doc #

Data Dict Source # 
Instance details

Defined in JsonToType.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 :: forall r r'. (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 #

Generic Dict Source # 
Instance details

Defined in JsonToType.Type

Associated Types

type Rep Dict :: Type -> Type #

Methods

from :: Dict -> Rep Dict x #

to :: Rep Dict x -> Dict #

Show Dict Source # 
Instance details

Defined in JsonToType.Type

Methods

showsPrec :: Int -> Dict -> ShowS #

show :: Dict -> String #

showList :: [Dict] -> ShowS #

Eq Dict Source # 
Instance details

Defined in JsonToType.Type

Methods

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

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

Ord Dict Source # 
Instance details

Defined in JsonToType.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 #

type Rep Dict Source # 
Instance details

Defined in JsonToType.Type

type Rep Dict

data Type Source #

Union types for JSON values.

Instances

Instances details
Out Type Source # 
Instance details

Defined in JsonToType.Pretty

Methods

docPrec :: Int -> Type -> Doc #

doc :: Type -> Doc #

docList :: [Type] -> Doc #

Data Type Source # 
Instance details

Defined in JsonToType.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 :: forall r r'. (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 #

Generic Type Source # 
Instance details

Defined in JsonToType.Type

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Show Type Source # 
Instance details

Defined in JsonToType.Type

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Eq Type Source # 
Instance details

Defined in JsonToType.Type

Methods

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

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

Ord Type Source # 
Instance details

Defined in JsonToType.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 #

Uniplate Type Source # 
Instance details

Defined in JsonToType.Type

type Rep Type Source # 
Instance details

Defined in JsonToType.Type

type Rep Type = D1 ('MetaData "Type" "JsonToType.Type" "json-to-type-4.0.1-1PiB5NFEco7L6iRIrMaVW7" 'False) (((C1 ('MetaCons "TNull" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TBool" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TString" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TInt" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TDouble" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TUnion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Type)))) :+: (C1 ('MetaCons "TLabel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "TObj" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dict)) :+: C1 ('MetaCons "TArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))))

emptyType :: Type Source #

Empty type

extractType :: Value -> Type Source #

Check if a number is integral, or floating point | Extract Type from the JSON Value. Unifying types of array elements, if necessary.

unifyTypes :: Type -> Type -> Type Source #

Standard unification procedure on Types, with inclusion of Type unions.

typeCheck :: Value -> Type -> Bool Source #

Type check the value with the derived type.