Read_TestHarness_Specifier Subroutine

public subroutine Read_TestHarness_Specifier(srcPath, returnrc)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: srcPath
integer, intent(inout) :: returnrc

Source Code

  subroutine Read_TestHarness_Specifier(srcPath, returnrc)
!
! !ARGUMENTS:
  character(len=*), intent (in)   :: srcPath
  integer,          intent(inout) :: returnrc

!
! !DESCRIPTION:
! the routine conducts the three tasks needed to conduct the test runs:
!
! 1. Reads the problem descriptor files, storing each problem descriptor string
! and the names of the accompaning support files in the harness descriptor record.
!
! 2. Parse the descriptor strings and store the information in the harness
! descriptor record.
!
! 3. Read the grid and distribution specifier files and store the configurations
! in the harness descriptor record.
!
!===============================================================================

  ! local ESMF types

  ! local parameters
  ! logical :: flag = .true.

  ! local integer variables
  integer :: nPEs
  integer :: k, kfile, kstr
  integer :: iDfile, iGfile, iD, iG
  integer :: nDfiles, nGfiles, nstatus
  integer :: nDspec, nGspec
  integer :: localrc
  integer :: allocRcToTest

  ! initialize return flag
  returnrc = ESMF_RC_NOT_IMPL
  localrc = ESMF_RC_NOT_IMPL

  !-----------------------------------------------------------------------------
  ! read each of the problem descriptor files obtained from read_testharness_config
  ! and extract the problem descriptor strings and the accompanying specifier
  ! filenames.
  !-----------------------------------------------------------------------------
  call read_descriptor_files(srcPath, har%numRecords,har%rcrd,localrc)
  if (ESMF_LogFoundError(localrc, msg="ERROR with read descriptor files",       &
     rcToReturn=returnrc)) return

  !-----------------------------------------------------------------------------
  ! loops through the list of descriptor files and reads each problem
  ! descriptor string and its associated specifer files for (1) class, (2)
  ! distribution ensemble, and (3) grid ensemble.
  !-----------------------------------------------------------------------------

  !-----------------------------------------------------------------------------
  ! parse each problem descriptor string in each of the numRecords files
  !-----------------------------------------------------------------------------
  do kfile=1,har%numRecords
     do kstr=1,har%rcrd(kfile)%numStrings
        call parse_descriptor_string(har%rcrd(kfile)%numStrings,               &
                  har%rcrd(kfile)%str(kstr), localrc)
        if (ESMF_LogFoundError(localrc,msg=" error in problem descriptor file " &
           // trim(adjustL(har%rcrd(kfile)%filename)),                         &
           rcToReturn=returnrc)) return

        ! read distribution specifier files
        do k=1,har%rcrd(kfile)%str(kstr)%nDfiles
           nPEs = petCount
           call read_dist_specification(nPEs,                                  &
                    har%rcrd(kfile)%str(kstr)%Dfiles(k),                       &
                    har%rcrd(kfile)%str(kstr)%DstMem,                          &
                    har%rcrd(kfile)%str(kstr)%SrcMem, localrc)
           if (ESMF_LogFoundError(localrc,msg=" error reading dist specifier"   &
              // " file "  //                                                  &
              trim(adjustL(har%rcrd(kfile)%str(kstr)%Dfiles(k)%filename)),     &
              rcToReturn=returnrc)) return
        enddo   ! k

        ! read grid specifier files
        do k=1,har%rcrd(kfile)%str(kstr)%nGfiles
           call read_grid_specification(har%rcrd(kfile)%str(kstr)%Gfiles(k),   &
                    localrc)
           if (ESMF_LogFoundError(localrc,msg=" error reading grid specifier"   &
              // " file "  //                                                  &
              trim(adjustL(har%rcrd(kfile)%str(kstr)%Gfiles(k)%filename)),     &
              rcToReturn=returnrc)) return
        enddo   ! k

        ! allocate and initialize test status
        nDfiles = har%rcrd(kfile)%str(kstr)%nDfiles
        nGfiles = har%rcrd(kfile)%str(kstr)%nGfiles
        allocate( har%rcrd(kfile)%str(kstr)%test_record(nDfiles,nGfiles),      &
                  stat=allocRcToTest )
        if (ESMF_LogFoundAllocError(allocRcToTest, msg="rcrd type "//           &
           " in Read_TestHarness_Config", rcToReturn=returnrc)) then
        endif

        ! initialize test result to UNDEFINED
        do iDfile=1,har%rcrd(kfile)%str(kstr)%nDfiles
        do iGfile=1,har%rcrd(kfile)%str(kstr)%nGfiles
           nDspec = har%rcrd(kfile)%str(kstr)%Dfiles(iDfile)%nDspecs
           nGspec = har%rcrd(kfile)%str(kstr)%Gfiles(iGfile)%nGspecs
        !  print*,'==== file  sizes',iDfile,iGfile,nDspec,nGspec
           ! allocate work space for test result
           allocate( har%rcrd(kfile)%str(kstr)%test_record(iDfile,iGfile)%     &
              test_status(nDspec,nGspec), stat=allocRcToTest )
           if (ESMF_LogFoundAllocError(allocRcToTest, msg="test status type"//  &
              " in Read_TestHarness_Config", rcToReturn=returnrc)) then
           endif
           ! allocate work space for test string
           allocate( har%rcrd(kfile)%str(kstr)%test_record(iDfile,iGfile)%     &
              test_string(nDspec,nGspec), stat=allocRcToTest )
           if (ESMF_LogFoundAllocError(allocRcToTest, msg="test status type"//  &
              " in Read_TestHarness_Config", rcToReturn=returnrc)) then
           endif

           do iD=1, nDspec
           do iG=1, nGspec
             har%rcrd(kfile)%str(kstr)%test_record(iDfile,iGfile)%             &
                 test_status(iD,iG) = HarnessTest_UNDEFINED
           enddo   ! iG
           enddo   ! iD

        enddo   ! iGfile
        enddo   ! iDfile

     enddo  ! kstr
  enddo    ! kfile

  !-----------------------------------------------------------------------------
  ! list imported problem configurations before continuing
  !-----------------------------------------------------------------------------
  nstatus= 0
  if( trim(har%setupReportType) == "TRUE" )  nstatus= 1
  do kfile=1,har%numrecords
     do kstr=1,har%rcrd(kfile)%numStrings
        call construct_descriptor_string(har%rcrd(kfile)%str(kstr),nstatus, &
                                         localPet, localrc)
     enddo  ! kstr
  enddo    ! kfile

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

  !-----------------------------------------------------------------------------
  ! if I've gotten this far without an error, then the routine has succeeded.
  !-----------------------------------------------------------------------------
  returnrc = ESMF_SUCCESS

!===============================================================================
  end subroutine Read_TestHarness_Specifier