Safe Haskell | None |
---|---|
Language | Haskell2010 |
Extraction and unification of AutoType's Type
from Aeson Value
.
Synopsis
- valueSize :: Value -> Int
- valueTypeSize :: Value -> Int
- valueDepth :: Value -> Int
- newtype Dict = Dict {}
- data Type
- emptyType :: Type
- extractType :: Value -> Type
- unifyTypes :: Type -> Type -> Type
- typeCheck :: Value -> Type -> Bool
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
Dictionary of types indexed by names.
Instances
Eq Dict Source # | |
Data Dict Source # | |
Defined in Data.Aeson.AutoType.Type 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 # 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 # | |
Ord Dict Source # | |
Show Dict Source # | |
Generic Dict Source # | |
Out Dict Source # | |
type Rep Dict Source # | |
Defined in Data.Aeson.AutoType.Type |
Union types for JSON values.
Instances
Eq Type Source # | |
Data Type Source # | |
Defined in Data.Aeson.AutoType.Type 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 # 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 # | |
Ord Type Source # | |
Show Type Source # | |
Generic Type Source # | |
Out Type Source # | |
Uniplate Type Source # | |
Defined in Data.Aeson.AutoType.Type | |
type Rep Type Source # | |
Defined in Data.Aeson.AutoType.Type type Rep Type = D1 ('MetaData "Type" "Data.Aeson.AutoType.Type" "json-autotype-3.0.4-inplace" '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)))))) |
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.