Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module defines a normalised representation of APIs, used for comparing them in the migrations changelog, and to analyse dependencies.
Synopsis
- type NormAPI = Map TypeName NormTypeDecl
- data NormTypeDecl
- type NormRecordType = Map FieldName APIType
- type NormUnionType = Map FieldName APIType
- type NormEnumType = Set FieldName
- apiNormalForm :: API -> NormAPI
- declNF :: Spec -> NormTypeDecl
- typeDeclsFreeVars :: NormAPI -> Set TypeName
- typeDeclFreeVars :: NormTypeDecl -> Set TypeName
- typeFreeVars :: APIType -> Set TypeName
- typeDeclaredInApi :: TypeName -> NormAPI -> Bool
- typeUsedInApi :: TypeName -> NormAPI -> Bool
- typeUsedInTransitiveDep :: TypeName -> TypeName -> NormAPI -> Bool
- transitiveDeps :: NormAPI -> Set TypeName -> Set TypeName
- transitiveReverseDeps :: NormAPI -> Set TypeName -> Set TypeName
- apiInvariant :: NormAPI -> Either (Set TypeName) ()
- declIsValid :: NormTypeDecl -> NormAPI -> Either (Set TypeName) ()
- typeIsValid :: APIType -> NormAPI -> Either (Set TypeName) ()
- substTypeDecl :: (TypeName -> APIType) -> NormTypeDecl -> NormTypeDecl
- substType :: (TypeName -> APIType) -> APIType -> APIType
- renameTypeUses :: TypeName -> TypeName -> NormAPI -> NormAPI
Normalised API types
type NormAPI = Map TypeName NormTypeDecl Source #
The API type has too much extra info for us to be able to simply compare
them with (==)
. Our strategy is to strip out ancillary information and
normalise into a canonical form, and then we can use a simple (==)
compare.
Our normalised API discards most of the details of each type, keeping just essential information about each type. We discard order of types and fields, so we can use just associative maps.
data NormTypeDecl Source #
The normal or canonical form for a type declaration, an APINode
.
Equality of the normal form indicates equivalence of APIs.
We track all types.
NRecordType NormRecordType | |
NUnionType NormUnionType | |
NEnumType NormEnumType | |
NTypeSynonym APIType | |
NNewtype BasicType |
Instances
Eq NormTypeDecl Source # | |
Defined in Data.API.NormalForm (==) :: NormTypeDecl -> NormTypeDecl -> Bool # (/=) :: NormTypeDecl -> NormTypeDecl -> Bool # | |
Show NormTypeDecl Source # | |
Defined in Data.API.NormalForm showsPrec :: Int -> NormTypeDecl -> ShowS # show :: NormTypeDecl -> String # showList :: [NormTypeDecl] -> ShowS # | |
NFData NormTypeDecl Source # | |
Defined in Data.API.NormalForm rnf :: NormTypeDecl -> () # | |
PPLines NormTypeDecl Source # | |
Defined in Data.API.NormalForm ppLines :: NormTypeDecl -> [String] Source # |
type NormRecordType = Map FieldName APIType Source #
The canonical form of a record type is a map from fields to values...
type NormUnionType = Map FieldName APIType Source #
...similarly a union is a map from fields to alternatives...
type NormEnumType = Set FieldName Source #
...and an enum is a set of values.
Converting to normal form
apiNormalForm :: API -> NormAPI Source #
Compute the normal form of an API, discarding extraneous information.
declNF :: Spec -> NormTypeDecl Source #
Compute the normal form of a single type declaration.
Dependency analysis
typeDeclFreeVars :: NormTypeDecl -> Set TypeName Source #
Find the set of type names used in a declaration
typeUsedInTransitiveDep :: TypeName -> TypeName -> NormAPI -> Bool Source #
Check if the first type's transitive dependencies include the second type
transitiveDeps :: NormAPI -> Set TypeName -> Set TypeName Source #
Compute the transitive dependencies of a set of types
transitiveReverseDeps :: NormAPI -> Set TypeName -> Set TypeName Source #
Compute the set of types that depend (transitively) on the given types
Invariant validation
apiInvariant :: NormAPI -> Either (Set TypeName) () Source #
Test that all the types used in the API are declared. If not, return the set of undeclared types.
declIsValid :: NormTypeDecl -> NormAPI -> Either (Set TypeName) () Source #
Test that all the types used in a type declaration are declared in the API. If not, return the set of undeclared types.
typeIsValid :: APIType -> NormAPI -> Either (Set TypeName) () Source #
Test that all the free type names in a type are declared in the API. If not, return the set of undeclared types.
Modifying types
substTypeDecl :: (TypeName -> APIType) -> NormTypeDecl -> NormTypeDecl Source #
Substitute types for type names in a declaration