ChildSpec.F90 Source File


This file depends on

sourcefile~~childspec.f90~~EfferentGraph sourcefile~childspec.f90 ChildSpec.F90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~childspec.f90->sourcefile~keywordenforcer.f90 sourcefile~usersetservices.f90 UserSetServices.F90 sourcefile~childspec.f90->sourcefile~usersetservices.f90 sourcefile~dso_utilities.f90 DSO_Utilities.F90 sourcefile~usersetservices.f90->sourcefile~dso_utilities.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~usersetservices.f90->sourcefile~errorhandling.f90 sourcefile~esmf_interfaces.f90 ESMF_Interfaces.F90 sourcefile~usersetservices.f90->sourcefile~esmf_interfaces.f90 sourcefile~filesystemutilities.f90 FileSystemUtilities.F90 sourcefile~dso_utilities.f90->sourcefile~filesystemutilities.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90

Files dependent on this one

sourcefile~~childspec.f90~~AfferentGraph sourcefile~childspec.f90 ChildSpec.F90 sourcefile~add_child_by_name.f90 add_child_by_name.F90 sourcefile~add_child_by_name.f90->sourcefile~childspec.f90 sourcefile~childspecmap.f90 ChildSpecMap.F90 sourcefile~add_child_by_name.f90->sourcefile~childspecmap.f90 sourcefile~componentspecparser.f90 ComponentSpecParser.F90 sourcefile~add_child_by_name.f90->sourcefile~componentspecparser.f90 sourcefile~childspecmap.f90->sourcefile~childspec.f90 sourcefile~componentspecparser.f90->sourcefile~childspec.f90 sourcefile~componentspecparser.f90->sourcefile~childspecmap.f90 sourcefile~componentspec.f90 ComponentSpec.F90 sourcefile~componentspecparser.f90->sourcefile~componentspec.f90 sourcefile~setservices.f90 SetServices.F90 sourcefile~setservices.f90->sourcefile~childspec.f90 sourcefile~setservices.f90->sourcefile~childspecmap.f90 sourcefile~setservices.f90->sourcefile~componentspecparser.f90 sourcefile~test_componentspecparser.pf Test_ComponentSpecParser.pf sourcefile~test_componentspecparser.pf->sourcefile~childspec.f90 sourcefile~test_componentspecparser.pf->sourcefile~childspecmap.f90 sourcefile~test_componentspecparser.pf->sourcefile~componentspecparser.f90 sourcefile~componentspec.f90->sourcefile~childspecmap.f90 sourcefile~parse_child.f90 parse_child.F90 sourcefile~parse_child.f90->sourcefile~componentspecparser.f90 sourcefile~parse_children.f90 parse_children.F90 sourcefile~parse_children.f90->sourcefile~componentspecparser.f90 sourcefile~parse_component_spec.f90 parse_component_spec.F90 sourcefile~parse_component_spec.f90->sourcefile~componentspecparser.f90 sourcefile~parse_connections.f90 parse_connections.F90 sourcefile~parse_connections.f90->sourcefile~componentspecparser.f90 sourcefile~parse_geometry_spec.f90 parse_geometry_spec.F90 sourcefile~parse_geometry_spec.f90->sourcefile~componentspecparser.f90 sourcefile~parse_setservices.f90 parse_setservices.F90 sourcefile~parse_setservices.f90->sourcefile~componentspecparser.f90 sourcefile~parse_var_specs.f90 parse_var_specs.F90 sourcefile~parse_var_specs.f90->sourcefile~componentspecparser.f90 sourcefile~mapl_generic.f90~2 MAPL_Generic.F90 sourcefile~mapl_generic.f90~2->sourcefile~componentspec.f90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~outermetacomponent.f90->sourcefile~componentspec.f90

Source Code

#include "MAPL_ErrLog.h"

module mapl3g_ChildSpec
   use mapl3g_UserSetServices
   use mapl_KeywordEnforcer
   implicit none
   private

   public :: ChildSpec
   public :: operator(==)
   public :: operator(/=)

   public :: dump
   
   type :: ChildSpec
      class(AbstractUserSetServices), allocatable :: user_setservices
      character(:), allocatable :: config_file
      ! Prevent default structure constructor
      integer, private ::  hack
   contains
      procedure :: write_formatted
      generic :: write(formatted) => write_formatted
   end type ChildSpec

   interface ChildSpec
      module procedure new_ChildSpec
   end interface ChildSpec

   interface operator(==)
      module procedure equal
   end interface operator(==)
      
   interface operator(/=)
      module procedure not_equal
   end interface operator(/=)


contains

   function new_ChildSpec(user_setservices, unusable, config_file) result(spec)
      type(ChildSpec) :: spec
      class(AbstractUserSetServices), intent(in) :: user_setservices
      class(KeywordEnforcer), optional, intent(in) :: unusable
      character(*), optional, intent(in) :: config_file

      spec%user_setservices = user_setservices
      if (present(config_file)) spec%config_file = config_file

      _UNUSED_DUMMY(unusable)
   end function new_ChildSpec
      

   logical function equal(a, b)
      type(ChildSpec), intent(in) :: a
      type(ChildSpec), intent(in) :: b

      equal = (a%user_setservices == b%user_setservices)
      if (.not. equal) return
      
      equal = equal_alloc_str(a%config_file, b%config_file)
      if (.not. equal) return

   contains

      logical function equal_alloc_str(a, b) result(equal)
         character(:), allocatable, intent(in) :: a
         character(:), allocatable, intent(in) :: b

         equal = (allocated(a) .eqv. allocated(b))
         if (.not. equal) return

         if (allocated(a)) equal = (a == b)

      end function equal_alloc_str

   end function equal

   logical function not_equal(a, b)
      type(ChildSpec), intent(in) :: a
      type(ChildSpec), intent(in) :: b

      not_equal = .not. (a == b)
   end function not_equal

   subroutine dump(x)
      type(ChildSpec) :: x

      select type (q => x%user_setservices)
      type is (Dsosetservices)
         print*,__FILE__,__LINE__, q%sharedObj, '::', q%userRoutine
      end select
   end subroutine dump

   subroutine write_formatted(this, unit, iotype, v_list, iostat, iomsg)
      class(ChildSpec), intent(in) :: this
      integer, intent(in) :: unit
      character(*), intent(in) :: iotype
      integer, intent(in) :: v_list(:)
      integer, intent(out) :: iostat
      character(*), intent(inout) :: iomsg

      character(:), allocatable :: file

      if (allocated(this%config_file)) then
         file = this%config_file
      else
         file = '<none>'
      end if

      write(unit,'(a,a)',iostat=iostat, iomsg=iomsg) 'Config file: ', file
      if (iostat /= 0) return

      write(unit,'(a, DT)', iostat=iostat, iomsg=iomsg) 'UserSetServices: ', this%user_setservices

      _UNUSED_DUMMY(iotype)
      _UNUSED_DUMMY(v_list)
      
   end subroutine write_formatted



end module mapl3g_ChildSpec