KeywordEnforcer.F90 Source File


Files dependent on this one

KeywordEnforcer.F90wAbstractCollectiveDataMessage.F90
w
wAbstractDataMessage.F90
w
wAbstractDirectoryService.F90
w
wActualConnectionPt.F90
w
wApplicationSupport.F90
w
wBase.F90
w
wBase_Base.F90
w
wBase_Base_implementation.F90
w
wBaseProfiler.F90
w
wBracketSpec.F90
w
wCap.F90
w
wCapOptions.F90
w
wChildSpec.F90
w
wClientManager.F90
w
wClientThread.F90
w
wCollectivePrefetchDataMessage.F90
w
wCollectiveStageDataMessage.F90
w
wCommGroupDescription.F90
w
wCoordinateVariable.F90
w
wcreate_basic_grid.F90
w
wCSR_SparseMatrix.F90
w
wCubedSphereDecomposition.F90
w
wCubedSphereDecomposition_smod.F90
w
wCubedSphereGeomFactory.F90
w
wCubedSphereGeomFactory_smod.F90
w
wDecoratorComponent.F90
w
wDirectoryService.F90
w
wExtDataAbstractFileHandler.F90
w
wExtDataBracket.F90
w
wExtDataClimFileHandler.F90
w
wExtDataConfig.F90
w
wExtDataDerived.F90
w
wExtDataFileStream.F90
w
wExtDataGridComp_private.F90
w
wExtDataMasking.F90
w
wExtDataNode.F90
w
wExtDataOldTypesCreator.F90
w
wExtDataRule.F90
w
wExtDataSample.F90
w
wExtDataSimpleFileHandler.F90
w
wExtDataUpdatePointer.F90
w
wFargparseCLI.F90
w
wFastClientThread.F90
w
wFieldSpec.F90
w
wFileMetadata.F90
w
wFileMetadataUtilities.F90
w
wfill_coordinates.F90
w
wForwardDataAndMessage.F90
w
wForwardDataMessage.F90
w
wGenericGridComp.F90
w
wGlobalProfilers.F90
w
wGriddedComponentDriver.F90
w
wHistoryGridComp_private.F90
w
wHorizontalFluxRegridder.F90
w
wInvalidSpec.F90
w
wLatLonDecomposition.F90
w
wLatLonGeomFactory.F90
w
wmake_file_metadata.F90
w
wmake_geom.F90
w
wmake_gridded_dims.F90
w
wMAPL_AbstractGridFactory.F90
w
wMAPL_AbstractRegridder.F90
w
wMAPL_Cap.F90
w
wMAPL_CapGridComp.F90
w
wMAPL_CF_Time.F90
w
wMAPL_Config.F90
w
wMAPL_CubedSphereGridFactory.F90
w
wMAPL_DateTime_Parsing_ESMF.F90
w
wMAPL_DirPath.F90
w
wMAPL_EsmfRegridder.F90
w
wMAPL_EtaHybridVerticalCoordinate.F90
w
wMAPL_ExternalGridFactory.F90
w
wMAPL_Generic.F90
w
wMAPL_Generic.F90
w
wMAPL_GeosatMaskMod.F90
w
wMAPL_GridManager.F90
w
wMAPL_IdentityRegridder.F90
w
wMAPL_ISO8601_DateTime.F90
w
wMAPL_ISO8601_DateTime_ESMF.F90
w
wMAPL_LatLonGridFactory.F90
w
wMAPL_LatLonToLatLonRegridder.F90
w
wMAPL_LocStreamFactoryMod.F90
w
wMAPL_LocstreamRegridder.F90
w
wMAPL_NetCDF.F90
w
wMAPL_Profiler.F90
w
wMAPL_RegridderManager.F90
w
wMAPL_Resource.F90
w
wMAPL_SimpleBundleMod.F90
w
wMAPL_SphericalGeometry.F90
w
wMAPL_SwathGridFactory.F90
w
wMAPL_TilingRegridder.F90
w
wMAPL_TrajectoryMod_smod.F90
w
wMAPL_TransposeRegridder.F90
w
wMAPL_TripolarGridFactory.F90
w
wMAPL_XYGridFactory.F90
w
wMaplComponent.F90
w
wMaplFramework.F90
w
wMaplGenericComponent.F90
w
wMaplGrid.F90
w
wMaplShared.F90
w
wMatchConnection.F90
w
wMemoryProfiler.F90
w
wMethodPhasesMap.F90
w
wMockClientThread.F90
w
wMockGridFactory.F90
w
wMockItemSpec.F90
w
wMockRegridder.F90
w
wModifyMetadataMessage.F90
w
wMultiCommServer.F90
w
wMultiGroupServer.F90
w
wMultiLayerServer.F90
w
wMultiState.F90
w
wNetCDF4_FileFormatter.F90
w
wNewRegridderManager.F90
w
wOpenMP_Support.F90
w
wOuterMetaComponent.F90
w
wPlain_netCDF_Time.F90
w
wPrefetchDataMessage.F90
w
wReexportConnection.F90
w
wRegridderSpec.F90
w
wRegridderTypeSpec.F90
w
wReplaceMetadataMessage.F90
w
wServerManager.F90
w
wSimpleCommSplitter.F90
w
wSimpleConnection.F90
w
wStageDataMessage.F90
w
wStateSpec.F90
w
wStringTemplate.F90
w
wStubComponent.F90
w
wStubProfiler.F90
w
wTest_CompositeComponent.pf
w
wTest_SimpleParentGridComp.pf
w
wTimeProfiler.F90
w
wTimeStringConversion.F90
w
wtypesafe_make_file_metadata.F90
w
wtypesafe_make_geom.F90
w
wUserComponent.F90
w
wVarConnPoint.F90
w
wVariable.F90
w
wVariableSpec.F90
w
wVirtualConnectionPt.F90
w
wWildcardSpec.F90
w

Source Code

   ! This module implements a mechanism that can be used to enforce
   ! keyword association for dummy arguments in an interface.  The
   ! concept is to have a derived type for which no actual argument can
   ! ever be provided.
   
   ! The original idea comes (AFAIK) from ESMF which uses a PUBLIC
   ! derived type that is simply not exported in the main ESMF
   ! package.  That approach has one weakness, which is that a clever
   ! user can still access the module that defines the type.  Various
   ! workarounds for that are possible such as using a truly PRIVATE
   ! type, but these encounter further issues for type-bound
   ! procedures which are then overridden in a subclass.

   ! The approach here, suggested by Dan Nagle, is to use an ABSTRACT
   ! type which prevents variables from being declared with that type.
   ! Tom Clune improved upon this by introducing a DEFERRED type-bound
   ! procedure that prevents extending the type to a non-abstract
   ! class.  A DEFERRED, PRIVATE type-bound procedure is attached to
   ! the type and cannot be overridden outside of this module.  Any
   ! non-abstract extension must implement the method.  (Note that
   ! ABSTRACT extensions can be created, but do not circumvent the
   ! keyword enforcement.

module mapl_KeywordEnforcer
   implicit none
   private

   public :: KeywordEnforcer

   type, abstract :: KeywordEnforcer
   contains
      procedure (nonimplementable), deferred, nopass, private :: nonimplementable
   end type KeywordEnforcer

   abstract interface
      subroutine nonimplementable()
      end subroutine nonimplementable
   end interface

end module mapl_KeywordEnforcer

module mapl_KeywordEnforcerMod
   use mapl_KeywordEnforcer
end module mapl_KeywordEnforcerMod