MAPL_demo_fargparse.F90 Source File


This file depends on

sourcefile~~mapl_demo_fargparse.f90~~EfferentGraph sourcefile~mapl_demo_fargparse.f90 MAPL_demo_fargparse.F90 sourcefile~mapl.f90 MAPL.F90 sourcefile~mapl_demo_fargparse.f90->sourcefile~mapl.f90 sourcefile~base.f90 Base.F90 sourcefile~mapl.f90->sourcefile~base.f90 sourcefile~esmf_cfiomod.f90 ESMF_CFIOMod.F90 sourcefile~mapl.f90->sourcefile~esmf_cfiomod.f90 sourcefile~fieldbundleread.f90 FieldBundleRead.F90 sourcefile~mapl.f90->sourcefile~fieldbundleread.f90 sourcefile~fieldbundlewrite.f90 FieldBundleWrite.F90 sourcefile~mapl.f90->sourcefile~fieldbundlewrite.f90 sourcefile~fieldutils.f90 FieldUtils.F90 sourcefile~mapl.f90->sourcefile~fieldutils.f90 sourcefile~mapl_generic.f90 MAPL_Generic.F90 sourcefile~mapl.f90->sourcefile~mapl_generic.f90 sourcefile~mapl_gridcomps.f90 MAPL_GridComps.F90 sourcefile~mapl.f90->sourcefile~mapl_gridcomps.f90 sourcefile~mapl_profiler.f90 MAPL_Profiler.F90 sourcefile~mapl.f90->sourcefile~mapl_profiler.f90 sourcefile~openmp_support.f90 OpenMP_Support.F90 sourcefile~mapl.f90->sourcefile~openmp_support.f90 sourcefile~pfio.f90 pFIO.F90 sourcefile~mapl.f90->sourcefile~pfio.f90 sourcefile~stubcomponent.f90 StubComponent.F90 sourcefile~mapl.f90->sourcefile~stubcomponent.f90 sourcefile~varspecmiscmod.f90 VarSpecMiscMod.F90 sourcefile~mapl.f90->sourcefile~varspecmiscmod.f90

Source Code

!------------------------------------------------------------------------------
!># Standalone Program for Testing fargparse
!
!------------------------------------------------------------------------------

! We use a module here because we need two levels of contains

#include "MAPL_ErrLog.h"
module main_mod

   use MAPL
   use mpi
   use fargparse

   implicit none

   contains

      subroutine run(rc)

         integer, intent(out), optional :: rc

         type(FargparseCLI_Type) :: cli
         type(MAPL_CapOptions)   :: cap_options

         integer :: status
         character(len=:), allocatable :: input_file

         call MPI_Init(status)
         _VERIFY(status)

         ! Read and parse the command line, and set parameters
         ! If you have extra options, you need to make two procedures as seen below:
         ! 1. a procedure to declare the options
         ! 2. a procedure to cast the options
         cap_options = FargparseCLI(extra_options=extra_options, cast_extras=cast_extras)

         write(*,*) "done with MAPL_FargparseCLI"
         write(*,*) "  cap_options%with_esmf_moab = ", cap_options%with_esmf_moab
         write(*,*) "  cap_options%npes_input_server = ", cap_options%npes_input_server
         write(*,*) "  cap_options%nodes_input_server = ", cap_options%nodes_input_server
         write(*,*) "  cap_options%npes_output_server = ", cap_options%npes_output_server
         write(*,*) "  cap_options%nodes_output_server = ", cap_options%nodes_output_server
         write(*,*) "  cap_options%egress_file = ", cap_options%egress_file
         write(*,*) ""
         write(*,*) "Extra arguments"
         write(*,*) "  input file = ", input_file

         _RETURN(_SUCCESS)

         contains

            subroutine extra_options(parser, rc)
               type (ArgParser), intent(inout) :: parser
               integer, intent(out), optional :: rc

               call parser%add_argument('-f', '--file', &
                  help='A file to read', &
                  type='string', &
                  default='default.config', &
                  action='store')

               !_RETURN(_SUCCESS)
               if (present(rc)) rc = 0

            end subroutine extra_options

            subroutine cast_extras(cli, rc)
               type(FargparseCLI_Type), intent(inout) :: cli
               integer, intent(out), optional :: rc

               class(*), pointer :: option

               option => cli%options%at('file')
               if (associated(option)) then
                  call cast(option, input_file, _RC)
               end if

               !_RETURN(_SUCCESS)
               if (present(rc)) rc = 0

            end subroutine cast_extras

      end subroutine run

end module main_mod

#define I_AM_MAIN
#include "MAPL_ErrLog.h"
#include "unused_dummy.H"

program main
      use main_mod

      implicit none

      integer :: status

!------------------------------------------------------------------------------

      call run(_RC)

end program main