bond-0.5.0.0: Bond schema compiler and code generator

Copyright(c) Microsoft
LicenseMIT
Maintaineradamsap@microsoft.com
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Language.Bond.Syntax.Util

Contents

Description

 

Synopsis

Type classification

Functions that test if a type belongs to a particular category. These functions will resolve type aliases and return answer based on the type the alias resolves to.

isScalar :: Type -> Bool Source #

Returns True if the type represents a scalar.

isUnsigned :: Type -> Bool Source #

Returns True if the type represents unsigned integer.

isSigned :: Type -> Bool Source #

Returns True if the type represents signed integer.

isFloat :: Type -> Bool Source #

Returns True if the type represents floating point number.

isString :: Type -> Bool Source #

Returns True if the type represents a string.

isContainer :: Type -> Bool Source #

Returns True if the type represents a container (i.e. list, vector, set or map).

isList :: Type -> Bool Source #

Returns True if the type represents a list or a vector.

isAssociative :: Type -> Bool Source #

Returns True if the type represents a map or a set.

isNullable :: Type -> Bool Source #

Returns True if the type represents a nullable type.

isStruct :: Type -> Bool Source #

Returns True if the type represents a struct or a struct forward declaration.

isEnum :: Type -> Bool Source #

Returns True if the type represents an enum

isMetaName :: Type -> Bool Source #

Returns True if the type represents a meta-name type.

Type mapping

fmapType :: (Type -> Type) -> Type -> Type Source #

Recursively map a Type into another Type.

Examples

Change lists into vectors:

listToVector = fmapType f
 where
   f (BT_List x) = BT_Vector x
   f x = x

Folds

foldMapFields :: Monoid m => (Field -> m) -> Type -> m Source #

Maps all fields, including fields of the base, to a Monoid, and combines the results. Returns mempty if type is not a struct.

Examples

Check if there are any container fields:

anyContainerFields :: Type -> Bool
anyContainerFields = getAny . foldMapFields (Any . isContainer . fieldType)

foldMapStructFields :: Monoid m => (Field -> m) -> Declaration -> m Source #

Like foldMapFields but takes a Declaration as an argument instead of Type.

foldMapType :: Monoid m => (Type -> m) -> Type -> m Source #

Maps all parts of a Type to a Monoid and combines the results.

Examples

For a type:

list<nullable<int32>>

the result is:

   f (BT_List (BT_Nullable BT_Int32))
<> f (BT_Nullable BT_Int32)
<> f BT_Int32

foldMapType resolves type aliases. E.g. given the following type alias declaration (Bond IDL syntax):

using Array<T, N> = vector<T>;

the result for the following type:

Array<int32, 10>

is:

   f (BT_UserDefined Alias{..} [BT_Int32, BT_IntTypeArg 10])
<> f (BT_Vector BT_Int32)
<> f BT_Int32

Helper functions

resolveAlias :: Declaration -> [Type] -> Type Source #

Resolves a type alias declaration with given type arguments. Note that the function resolves one level of aliasing and thus may return a type alias.