GeometrySpec.F90 Source File


This file depends on

sourcefile~~geometryspec.f90~~EfferentGraph sourcefile~geometryspec.f90 GeometrySpec.F90 sourcefile~geom_mgr.f90 geom_mgr.F90 sourcefile~geometryspec.f90->sourcefile~geom_mgr.f90 sourcefile~verticalgrid.f90 VerticalGrid.F90 sourcefile~geometryspec.f90->sourcefile~verticalgrid.f90 sourcefile~geomspec.f90 GeomSpec.F90 sourcefile~geom_mgr.f90->sourcefile~geomspec.f90 sourcefile~geomutilities.f90 GeomUtilities.F90 sourcefile~geom_mgr.f90->sourcefile~geomutilities.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~verticalgrid.f90->sourcefile~errorhandling.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~geomutilities.f90->sourcefile~errorhandling.f90

Files dependent on this one

sourcefile~~geometryspec.f90~~AfferentGraph sourcefile~geometryspec.f90 GeometrySpec.F90 sourcefile~componentspec.f90 ComponentSpec.F90 sourcefile~componentspec.f90->sourcefile~geometryspec.f90 sourcefile~componentspecparser.f90 ComponentSpecParser.F90 sourcefile~componentspecparser.f90->sourcefile~geometryspec.f90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~outermetacomponent.f90->sourcefile~geometryspec.f90

Source Code

#include "MAPL_Generic.h"

module mapl3g_GeometrySpec
   use mapl3g_geom_mgr, only: GeomSpec
   use mapl3g_VerticalGrid
   implicit none
   private

   public :: GeometrySpec

   public :: GEOMETRY_NONE
   public :: GEOMETRY_PROVIDER
   public :: GEOMETRY_FROM_PARENT
   public :: GEOMETRY_FROM_CHILD

   enum, bind(c)
      enumerator :: GEOMETRY_NONE
      enumerator :: GEOMETRY_PROVIDER
      enumerator :: GEOMETRY_FROM_PARENT ! MAPL Default
      enumerator :: GEOMETRY_FROM_CHILD
   end enum

   type GeometrySpec
      integer :: kind= GEOMETRY_FROM_PARENT
      character(len=:), allocatable :: provider ! name of child
      class(GeomSpec), allocatable :: geom_spec
      class(VerticalGrid), allocatable :: vertical_grid
   end type GeometrySpec


   interface GeometrySpec
      module procedure new_GeometrySpecSimple
      module procedure new_GeometryFromChild
      module procedure new_GeometryProvider
   end interface GeometrySpec


contains

   function new_GeometrySpecSimple(kind) result(spec)
      type(GeometrySpec) :: spec
      integer, intent(in) :: kind
      spec%kind = kind
   end function new_GeometrySpecSimple

   function new_GeometryFromChild(provider) result(spec)
      type(GeometrySpec) :: spec
      character(*), intent(in) :: provider
      spec%kind = GEOMETRY_FROM_CHILD
      spec%provider = provider
   end function new_GeometryFromChild

   function new_GeometryProvider(geom_spec, vertical_grid) result(spec)
      type(GeometrySpec) :: spec
      class(GeomSpec), optional, intent(in) :: geom_spec
      class(VerticalGrid), optional, intent(in) :: vertical_grid
      spec%kind = GEOMETRY_PROVIDER
      if (present(geom_spec)) spec%geom_spec = geom_spec
      if (present(vertical_grid)) spec%vertical_grid = vertical_grid
   end function new_GeometryProvider



end module mapl3g_GeometrySpec