ESMF_ConfigUTest.F90 Source File


Source Code

! $Id$
!==============================================================================
! Earth System Modeling Framework
!
! Copyright (c) 2002-2023, University Corporation for Atmospheric Research, 
! Massachusetts Institute of Technology, Geophysical Fluid Dynamics 
! Laboratory, University of Michigan, National Centers for Environmental 
! Prediction, Los Alamos National Laboratory, Argonne National Laboratory, 
! NASA Goddard Space Flight Center.
! Licensed under the University of Illinois-NCSA License.
!==============================================================================
!
!
! !TITLE: ESMF Congiguration Management Test File \\ Version 1.01
!
! !AUTHORS: Leonid Zaslavsky and Arlindo da Silva
!
! !AFFILIATION: Data Assimilation Office, NASA/GSFC, Greenbelt, MD 20771
!
! !DATE: April 7, 2003
!
!
! This test file provides tests for ESMF Configuration Management System
! implemented in ESMF\_ConfigMod.F90.
!
! !REVISION HISTORY:
!
!       7apr2003 Leonid Zaslavsky Created.
!      14apr2003 Leonid Zaslavsky Corrected.
!      27apr2003 Leonid Zaslavsky Further corrected and debugged.
!------------------------------------------------------------------------

#include "ESMF.h"

module config_subrs

        use ESMF_TestMod
        use ESMF
        implicit none

        public

      type (ESMF_Config), save :: cf, cf1, cf2
      type (ESMF_Config), save :: cf_alias
      
      ! individual test failure message
      character(ESMF_MAXSTR) :: failMsg
      character(ESMF_MAXSTR) :: name
      integer :: result = 0
      logical :: isCreated   


      character(*), parameter :: fname = 'ESMF_Resource_File_Sample.rc'
      character(len=ESMF_MAXPATHLEN) :: restart_file
      integer :: rc, npets
      logical :: unique
      integer   :: nDE
      real(ESMF_KIND_R4) :: tau
      logical   :: optimize
      logical   :: Doing_QC
      character(len=1)   :: answer
      character(len=10) :: u_dataType, v_dataType, vf_dataType
      integer           :: nu, nv
      real(ESMF_KIND_R4) :: sigU(6), sigV(6)
      logical           :: sigVf(6)
      integer, parameter :: MAXLEV = 100, EOL = 111
      real(ESMF_KIND_R4) :: plev(MAXLEV), vCorr(MAXLEV, MAXLEV)
      integer :: nlev
      integer :: line, col, nlines
      integer, allocatable, dimension(:) :: ncol
      logical :: end
      real(ESMF_KIND_R4) temp
      type(ESMF_VM),save:: vm
      
      integer :: counter_total, counter_success
      integer :: rc_opening
      real(ESMF_KIND_R4) :: success_rate

        contains
!--------------------------------------------------------------------
      subroutine Initialization()
!--------------------------------------------------------------------

        character(ESMF_MAXSTR) :: failMsg
        character(ESMF_MAXSTR) :: name
        integer :: result = 0
        character(ESMF_MAXSTR) :: msg
        integer :: msg_l
        rc = 0

        
        !------------------------------------------------------------------------
        !EX_UTest
        ! Create Config Test
        write(failMsg, *) "Did not return ESMF_SUCCESS"
        write(name, *) "Create Config Test"
        cf = ESMF_ConfigCreate(rc=rc)
        call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
      
        if ( rc /= ESMF_SUCCESS ) then 
           print *,'ESMF_ConfigCreate: catastrophic error, rc =', rc
           return
        endif

        !------------------------------------------------------------------------
        !EX_UTest
        ! Test ESMF_ConfigAssignment(=)(Config,Config)
        write(failMsg, *) "Did not return ESMF_SUCCESS"
        write(name, *) "Config assignment Test"
        cf_alias = cf
        rc = merge (ESMF_SUCCESS, ESMF_FAILURE, associated (cf%cptr, cf_alias%cptr))
        call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
       
        !------------------------------------------------------------------------
        !EX_UTest
        ! Test ESMF_ConfigOperator(==)(Config,Config)
        write(failMsg, *) "Did not return ESMF_SUCCESS"
        write(name, *) "Config equality with same Config Test"
        rc = merge (ESMF_SUCCESS, ESMF_FAILURE, cf == cf_alias)
        call ESMF_Test((rc == ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

        !------------------------------------------------------------------------
        !EX_UTest
        ! Test ESMF_ConfigOperator(==)(Config,Config)
        write(failMsg, *) "Did not return ESMF_SUCCESS"
        write(name, *) "Config equality with different Config Test"
        rc = merge (ESMF_SUCCESS, ESMF_FAILURE, .not. (cf == cf1))
        call ESMF_Test((rc == ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

        !------------------------------------------------------------------------
        !EX_UTest
        ! Test ESMF_ConfigOperator(/=)(Config,Config)
        write(failMsg, *) "Did not return ESMF_SUCCESS"
        write(name, *) "Config inequality with same Config Test"
        rc = merge (ESMF_SUCCESS, ESMF_FAILURE, .not. (cf /= cf_alias))
        call ESMF_Test((rc == ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

        !------------------------------------------------------------------------
        !EX_UTest
        ! Test ESMF_ConfigOperator(/=)(Config,Config)
        write(failMsg, *) "Did not return ESMF_SUCCESS"
        write(name, *) "Config inequality with different Config Test"
        rc = merge (ESMF_SUCCESS, ESMF_FAILURE, cf /= cf1)
        call ESMF_Test((rc == ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

        !------------------------------------------------------------------------
        !EX_UTest
        ! Config Load File Test
        write(failMsg, *) "Did not return ESMF_RC_DUP_NAME"
        write(name, *) "Config Load File Test"
        call ESMF_ConfigLoadFile( cf, fname, unique = .true., rc = rc)
        call ESMF_Test((rc.eq.ESMF_RC_DUP_NAME), name, failMsg, result, ESMF_SRCLINE)

        if (rc == ESMF_RC_MEM) then 
           print *,' ESMF_ConfigLoadFile: Out of memory: exceeded NBUF_MAX'
        endif
        if ( rc /= ESMF_RC_DUP_NAME ) then
           call ESMF_LogRc2Msg (rc, msg=msg, msglen=msg_l)
           print *,' ESMF_ConfigLoadFile:  loading file ', trim (fname), &
                ' catastrophic error, rc = ', msg(:msg_l)
           return
        else
           counter_total =counter_total + 1
           counter_success =counter_success + 1         
           print *,' File contains duplicate labels - check logfile.' 
        endif


        return
        
      end subroutine Initialization
      
!--------------------------------------------------------------------
     subroutine SinglePar()
!--------------------------------------------------------------------
      integer, parameter   :: nDE_0 = 32      
      real(ESMF_KIND_R4), parameter      :: tau_0 = 14.0
      character(*), parameter :: restart_file_0 = 'RestartFile123'
      character(ESMF_MAXSTR), parameter   :: answer_0 = 'y'
      character(ESMF_MAXSTR) :: token_string
      logical, parameter     :: optimize_0 = .false.
      character(ESMF_MAXSTR) :: failMsg
      character(ESMF_MAXSTR) :: name
      character(8) :: restart_file_tooshort
      integer :: result = 0

      rc = 0

!''''''''''''''''''''''''''''

     !------------------------------------------------------------------------
     !EX_UTest
     ! Non initialized Config Get Attribute Int Test
     write(failMsg, *) "Did not return ESMF_RC_OBJ_NOT_CREATED"
     write(name, *) "Non initialized Config Get Attribute Int Test"
     call ESMF_ConfigGetAttribute( cf1, nDE, label ='Number_of_DEs:', & 
           default=7, rc = rc )
     call ESMF_Test((rc.eq.ESMF_RC_OBJ_NOT_CREATED), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Int Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Attribute Int Test"
     call ESMF_ConfigGetAttribute( cf, nDE, label ='Number_of_DEs:', & 
           default=7, rc = rc )
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

!''''''''''''''''''''''''''''
      
      counter_total =counter_total + 1
      if ( rc /= ESMF_SUCCESS ) then      
         print *,'ESMF_ConfigGetAttribute(int) got nDE =', nDE,' rc =', rc
      else
         if (nDE == nDE_0) then
            counter_success =counter_success + 1
         else
            print *,'ESMF_ConfigGetAttribute(int) ERROR: got nDE =', nDE, &
              ' should be ', nDE_0
         endif
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Verification Test
     write(failMsg, *) "Attribute integer value is incorrect"
     write(name, *) "Verify Attribute Value Test"
     call ESMF_Test((nDE.eq.NDE_0), name, failMsg, result, ESMF_SRCLINE)


! Floating point

      rc = 0
!''''''''''''''''''''''''''''
   
     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Float Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Attribute Float Test"
      call ESMF_ConfigGetAttribute(cf, tau, &
           label = 'Relaxation_time_scale_in_days:', rc = rc)
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''
   
      counter_total =counter_total + 1
      if ( rc /= ESMF_SUCCESS ) then      
         print *,'ESMF_ConfigGetAttribute(float) got tau =', tau,' rc =', rc
      else
         if (tau == tau_0) then
            counter_success =counter_success + 1
         else
            print *,'ESMF_ConfigGetAttribute(float) ERROR: got tau =', tau, &
              ' should be ', tau_0
         endif
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute FLoat Verification Test
     write(failMsg, *) "Attribute float value is incorrect"
     write(name, *) "Verify Attribute Float Value Test"
     call ESMF_Test((tau.eq.tau_0), name, failMsg, result, ESMF_SRCLINE)


! Character

      rc = 0
!''''''''''''''''''''''''''''
     !------------------------------------------------------------------------
     !EX_UTest
     ! Non-created Config Get Attribute Char Test
     write(failMsg, *) "Did not return ESMF_RC_OBJ_NOT_CREATED"
     write(name, *) "Config Get Attribute Char Test"
     call ESMF_ConfigGetChar( cf1, answer, label='Do_you_want_quality_control:', &
                                    rc = rc )
     call ESMF_Test((rc.eq.ESMF_RC_OBJ_NOT_CREATED), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Char Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Attribute Char Test"
     call ESMF_ConfigGetChar( cf, answer, label='Do_you_want_quality_control:', &
                                    rc = rc )
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if ( rc /= ESMF_SUCCESS ) then      
         print *,'ESMF_ConfigGetAttribute(char) got answer =', &
                 answer,' rc =', rc
      else
         if (answer == answer_0) then
            counter_success =counter_success + 1
         else
            print *,'ESMF_ConfigGetAttribute(char) ERROR: got answer =', &
                     answer, ' should be ', answer_0
         endif
      endif
     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Char Verification Test
     write(failMsg, *) "Attribute char value is incorrect"
     write(name, *) "Verify Attribute Char Value Test"
     call ESMF_Test((answer.eq.answer_0), name, failMsg, result, ESMF_SRCLINE)


! String

     rc = 0
!''''''''''''''''''''''''''''

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String too short Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Attribute String too short Test"
     call ESMF_ConfigGetAttribute( cf, restart_file_tooshort ,label='restart_file_name:', &
           rc = rc )
     call ESMF_Test((rc /= ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String too short w/default Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Attribute String too short w/default Test"
     call ESMF_ConfigGetAttribute( cf, restart_file_tooshort ,label='restart_file_name:', &
           default='restart_file_001.dat', rc = rc )
     call ESMF_Test((rc /= ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Attribute String Test"
     call ESMF_ConfigGetAttribute( cf, restart_file ,label='restart_file_name:', &
           rc = rc )
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if ( rc /= ESMF_SUCCESS ) then      
         print *,'ESMF_ConfigGetAttribute(string) got =', &
                  restart_file,' rc =', rc
      else
         if (answer == answer_0) then
            counter_success =counter_success + 1
         else
            print *,'ESMF_ConfigGetAttribute(string) ERROR: got  =', &
                     restart_file, ' should be ', restart_file_0
         endif
      endif
     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String Verification Test
     write(failMsg, *) "Attribute char value is incorrect"
     write(name, *) "Verify Attribute String Value Test"
     call ESMF_Test((answer.eq.answer_0), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String multi-word token Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Attribute String Multi-word apostrophe Token Test"
     call ESMF_ConfigGetAttribute( cf, token_string ,label='Token_Example_1:', &
           rc = rc )
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String multi-word token value Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Attribute String Multi-word apostrophe Token value Test"
     rc = merge (ESMF_SUCCESS, ESMF_FAILURE, token_string == 'This is a token example')
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String multi-word token Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Attribute String Multi-word quoted Token Test"
     token_string = 'xxxx'
     call ESMF_ConfigGetAttribute( cf, token_string ,label='Token_Example_2:', &
           rc = rc )
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String multi-word token value Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Attribute String Multi-word quoted Token value Test"
     rc = merge (ESMF_SUCCESS, ESMF_FAILURE, token_string == "This is a token example")
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

! Logical

      rc = 0
!''''''''''''''''''''''''''''
     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Logical Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Attribute Logical Test"
     call ESMF_ConfigGetAttribute( cf, optimize, label='Optimization:', rc = rc )
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if ( rc /= ESMF_SUCCESS ) then      
         print *,'ESMF_ConfigGetAttribute(logical) got optimize = ', &
                 optimize,' rc =', rc
      else
         if (optimize .eqv. optimize_0) then
            counter_success =counter_success + 1
         else
            print *,'ESMF_ConfigGetAttribute(logical) ERROR: got optimize =', &
                     optimize, ' should be ', optimize_0
         endif
      endif
     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Logical Verification Test
     write(failMsg, *) "Attribute logical value is incorrect"
     write(name, *) "Verify Attribute Logical Value Test"
     call ESMF_Test((optimize.eqv.optimize_0), name, failMsg, result, &
                     ESMF_SRCLINE)


    end subroutine SinglePar



!--------------------------------------------------------------------
    subroutine MultPar_SingleLine_U()
!--------------------------------------------------------------------
      character(len=12), parameter :: u_dataType_0 = 'u_UprAir'
      character(len=10) :: directions_expected(8) = (/  &
          'north     ', 'north east', 'east      ', 'south east', &
          'south     ', 'south west', 'west      ', 'north west'  &
      /)
      integer, parameter   :: nu_0 = 6
      real(ESMF_KIND_R4), dimension(nu_0), parameter :: sigU_0 = &
           (/ 2.0, 2.0, 2.2, 2.3, 2.7, 3.2 /)
      character(len=10) :: directions(8)
      character(len=2)  :: directions_tooshort(8)
 
      character(ESMF_MAXSTR) :: failMsg
      character(ESMF_MAXSTR) :: name
      integer :: result = 0

      rc = 0
 
!''''''''''''''''''''''''''''
     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Find Label Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Find Label Test"
     call ESMF_ConfigFindLabel( cf, 'u-wind_error:', rc=rc) ! identifies label
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc == ESMF_SUCCESS) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigFindLabel failed, label = u-wind_error:, rc =', rc 
         return
      endif

!''''''''''''''''''''''''''''
     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get String Test"
     call ESMF_ConfigGetAttribute( cf, u_dataType, rc =rc )  ! first token   
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(string) failed, rc =', rc
         return
      endif

      if(u_dataType ==  u_dataType_0) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigGetAttribute(string) ERROR: got  =', &
                 u_dataType, ' should be ', u_dataType_0
         return
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String Verification Test
     write(failMsg, *) "Attribute String value is incorrect"
     write(name, *) "Verify Attribute String Value Test"
     call ESMF_Test((u_dataType.eq.u_dataType_0), name, failMsg, result, ESMF_SRCLINE)


!''''''''''''''''''''''''''''
     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Int Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Int Test"
     call ESMF_ConfigGetAttribute( cf, nu, rc = rc )            ! second token
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(int) failed, rc =', rc
         return
      endif

      if( nu == nu_0 ) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigGetAttribute(int) ERROR: got  =', nu, &
              ' should be ', nu_0 
         return
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Int Verification Test
     write(failMsg, *) "Attribute Int value is incorrect"
     write(name, *) "Verify Attribute Int Value Test"
     call ESMF_Test((nu.eq.nu_0), name, failMsg, result, ESMF_SRCLINE)

!''''''''''''''''''''''''''''
     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Floats Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Floats Test"
     call ESMF_ConfigGetAttribute(cf, sigU, count=nu, rc=rc)     ! tokens 3 thru 8
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)


!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(floats) failed, rc =', rc
         return
      endif

      if( any(sigU /= sigU_0) ) then
         print *,'ESMF_ConfigGetAttribute(floats) ERROR: got sigU =', &
                  sigU(1:nu), ' should be sigU =', sigU_0(1:nu) 
         return
      else
         counter_success =counter_success + 1
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Floats Verification Test
     write(failMsg, *) "Attribute Floats values are incorrect"
     write(name, *) "Verify Attribute Floats Values Test"
     call ESMF_Test((all(sigU.eq.sigU_0)), name, failMsg, result, ESMF_SRCLINE)

     ! Quoted strings

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Quoted String Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Quoted String Array too short Test"
     call ESMF_ConfigGetAttribute( cf, directions_tooshort, label='directions:', rc =rc )  ! first token
     call ESMF_Test((rc /= ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Quoted String Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Quoted String Array too short default Test"
     call ESMF_ConfigGetAttribute( cf, directions, label='directions:',  &
         default='no direction', rc =rc )  ! first token
     call ESMF_Test((rc /= ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Quoted String Test
     write(failMsg, *) "Did not return ESMF_SUCCESS"
     write(name, *) "Config Get Quoted String Array Test"
     call ESMF_ConfigGetAttribute( cf, directions, label='directions:', rc =rc )  ! first token
     call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Quoted String Verification Test
     write(failMsg, *) "Attribute String value is incorrect"
     write(name, *) "Verify Attribute Quoted String Array Value Test"
     call ESMF_Test(all (directions == directions_expected), name, failMsg, result, ESMF_SRCLINE)

    end subroutine MultPar_SingleLine_U


!--------------------------------------------------------------------
subroutine MultPar_SingleLine_V
!--------------------------------------------------------------------
      character(len=12), parameter :: v_dataType_0 = 'v_UprAir'
      integer, parameter   :: nv_0 = 6
      real(ESMF_KIND_R4), dimension(nv_0), parameter :: sigV_0 = &
           (/ 2.2, 2.2, 2.3, 2.7, 3.2, 3.4 /)
      character(ESMF_MAXSTR) :: failMsg
      character(ESMF_MAXSTR) :: name
      integer :: result = 0

      rc = 0

!''''''''''''''''''''''''''''
      !------------------------------------------------------------------------
      !EX_UTest
      ! Config Find Label Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Find Label Test"
      call ESMF_ConfigFindLabel( cf, 'v-wind_error:', rc=rc)
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc == ESMF_SUCCESS) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigFindLabel failed, label = v-wind_error:, rc =', rc
         return        
      endif

!''''''''''''''''''''''''''''
      !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get String Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get String Test"
      call ESMF_ConfigGetAttribute( cf, v_dataType, rc = rc )
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(string) failed, rc =', rc
         return
      endif

      if(v_dataType ==  v_dataType_0) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigGetAttribute(string) ERROR: got  =', v_dataType, &
              ' should be ', v_dataType_0
         return
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String Verification Test
     write(failMsg, *) "Attribute String values are incorrect"
     write(name, *) "Verify Attribute String Values Test"
     call ESMF_Test((v_dataType.eq.v_dataType_0), name, failMsg, result, ESMF_SRCLINE)

!''''''''''''''''''''''''''''

      !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get Int Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get Int Test"
      call ESMF_ConfigGetAttribute( cf, nv, rc = rc )
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(int) failed, rc =', rc
         return
      endif

      if( nv == nv_0 ) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigGetAttribute(int) ERROR: got  =', nv, &
              ' should be ', nv_0 
         return
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Int Verification Test
     write(failMsg, *) "Attribute Int values are incorrect"
     write(name, *) "Verify Attribute Int Values Test"
     call ESMF_Test((nv.eq.nv_0), name, failMsg, result, ESMF_SRCLINE)

!''''''''''''''''''''''''''''

      !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get Floats Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get Floats Test"
      call ESMF_ConfigGetAttribute( cf, sigV, count=nv, rc=rc )
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(floats) failed, rc =', rc
         return
      endif

      if( any(sigV /= sigV_0) ) then
         print *,'ESMF_ConfigGetAttribute(floats) ERROR: got sigV =', &
                 sigV(1:nv), ' should be sigV =', sigV_0(1:nv) 
         return
      else
        counter_success =counter_success + 1
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Floats Verification Test
     write(failMsg, *) "Attribute Floats values are incorrect"
     write(name, *) "Verify Attribute Floats Values Test"
     call ESMF_Test((all(sigV.eq.sigV_0)), name, failMsg, result, ESMF_SRCLINE)

    end subroutine MultPar_SingleLine_V

!--------------------------------------------------------------------
subroutine MultPar_SingleLine_Vf
!--------------------------------------------------------------------
!  array of logicals
      character(len=6), parameter :: vf_dataType_0 = 'v_Flag'
      integer, parameter   :: nv_0 = 6
      logical, dimension(nv_0), parameter :: sigVf_0 = &
           (/ .true., .false., .true., .true., .false., .false. /)
      character(ESMF_MAXSTR) :: failMsg
      character(ESMF_MAXSTR) :: name
      integer :: result = 0

      rc = 0

!''''''''''''''''''''''''''''
      !------------------------------------------------------------------------
      !EX_UTest
      ! Non-created Config Find Label Test
      write(failMsg, *) "Did not return ESMF_RC_OBJ_NOT_CREATED"
      write(name, *) "Non-create Config Find Label Test"
      call ESMF_ConfigFindLabel( cf1, 'v-wind_flag:', rc=rc)
      call ESMF_Test((rc.eq.ESMF_RC_OBJ_NOT_CREATED), name, failMsg, result, ESMF_SRCLINE)

      !------------------------------------------------------------------------
      !EX_UTest
      ! Config Find Label Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Find Label Test"
      call ESMF_ConfigFindLabel( cf, 'v-wind_flag:', rc=rc)
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc == ESMF_SUCCESS) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigFindLabel failed, label = v-wind_flag:, rc =', rc
         return        
      endif

!''''''''''''''''''''''''''''
      !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get String Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get String Test"
      call ESMF_ConfigGetAttribute( cf, vf_dataType, rc = rc )
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(string) failed, rc =', rc
         return
      endif

      if(vf_dataType ==  vf_dataType_0) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigGetAttribute(string) ERROR: got  =', vf_dataType, &
              ' should be ', vf_dataType_0
         return
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String Verification Test
     write(failMsg, *) "Attribute String values are incorrect"
     write(name, *) "Verify Attribute String Values Test"
     call ESMF_Test((vf_dataType.eq.vf_dataType_0), name, failMsg, result, ESMF_SRCLINE)

!''''''''''''''''''''''''''''

      !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get Int Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get Int Test"
      call ESMF_ConfigGetAttribute( cf, nv, rc = rc )
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(int) failed, rc =', rc
         return
      endif

      if( nv == nv_0 ) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigGetAttribute(int) ERROR: got  =', nv, &
              ' should be ', nv_0 
         return
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Int Verification Test
     write(failMsg, *) "Attribute Int values are incorrect"
     write(name, *) "Verify Attribute Int Values Test"
     call ESMF_Test((nv.eq.nv_0), name, failMsg, result, ESMF_SRCLINE)

!''''''''''''''''''''''''''''

      !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get Logicals Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get Logicals Test"
      call ESMF_ConfigGetAttribute( cf, sigVf, count=nv_0, rc=rc )
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(logicals) failed, rc =', rc
         return
      endif

      if( any(sigVf .neqv. sigVf_0) ) then
         print *,'ESMF_ConfigGetAttribute(logicals) ERROR: got sigVf =', &
                 sigVf(1:nv), ' should be sigVf =', sigVf_0(1:nv) 
         return
      else
        counter_success =counter_success + 1
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Logicals Verification Test
     write(failMsg, *) "Attribute Logicals values are incorrect"
     write(name, *) "Verify Attribute Logicals Values Test"
     call ESMF_Test((all(sigVf.eqv.sigVf_0)), name, failMsg, result, &
                     ESMF_SRCLINE)

    end subroutine MultPar_SingleLine_Vf

!--------------------------------------------------------------------
    subroutine MultPar_MultLines()
!--------------------------------------------------------------------
      character(len=10), parameter :: u_dataType_1 = 'u_UprAir.u'
      character(len=10), parameter :: v_dataType_1 = 'v_UprAir.u'
      integer, parameter   :: nu_1 = 6
      integer, parameter   :: nv_1 = 6
      real(ESMF_KIND_R4), dimension(nu_1), parameter :: sigU_1 = &
           (/ 2.0, 2.0, 2.2, 2.3, 2.7, 3.2 /)
      real(ESMF_KIND_R4), dimension(nv_1), parameter :: sigV_1 = &
           (/ 2.0, 2.0, 2.2, 2.3, 2.7, 3.2 /)  
      character(ESMF_MAXSTR) :: failMsg
      character(ESMF_MAXSTR) :: name
      integer :: result = 0

      rc = 0

!''''''''''''''''''''''''''''

      !------------------------------------------------------------------------
      !EX_UTest
      ! Config Find Label Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Find Label Test"
      call ESMF_ConfigFindLabel( cf, 'ObsErr*QSCAT::', rc=rc) ! identify label
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc == ESMF_SUCCESS) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigFindLabel failed, label = ObsErr*QSCAT::, rc =', rc 
         return        
      endif

!''''''''''''''''''''''''''''

      !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get Next Line Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get Next Line Test"
      call ESMF_ConfigNextLine( cf, rc=rc )               ! move down 1 line
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc == ESMF_SUCCESS) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigNextLine failed, rc =', rc 
         return        
      endif

!''''''''''''''''''''''''''''

      !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get String Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get String Test"
      call ESMF_ConfigGetAttribute( cf, u_dataType, rc=rc )  ! first token
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(string) failed, rc =', rc
         return
      endif

      if(u_dataType ==  u_dataType_1) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigGetAttribute(string) ERROR: got  =', &
                 u_dataType, ' should be ', u_dataType_1
         return
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String Verification Test
     write(failMsg, *) "Attribute String values are incorrect"
     write(name, *) "Verify Attribute String Values Test"
     call ESMF_Test((u_dataType.eq.u_dataType_1), name, failMsg, result, ESMF_SRCLINE)

!''''''''''''''''''''''''''''

     !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get Int Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get Int Test"
      call ESMF_ConfigGetAttribute( cf, nu, rc=rc )              ! second token
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(int) failed, rc =', rc
         return
      endif

      if( nu == nu_1 ) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigGetAttribute(int) ERROR: got  =', nu, &
              ' should be ', nu_1 
         return
      endif

!''''''''''''''''''''''''''''

     !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get Floats Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get Floats Test"
      call ESMF_ConfigGetAttribute( cf, sigU, count=6, rc=rc ) ! tokens 3 thru 8
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

     counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(floats) failed, rc =', rc
         return
      endif

      if( any(sigU /= sigU_1) ) then
         print *,'ESMF_ConfigGetAttribute(floats) ERROR: got sigU =', &
                  sigU(1:nu), ' should be sigU =', sigU_1(1:nu_1) 
         return
      else
        counter_success =counter_success + 1
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Floats Verification Test
     write(failMsg, *) "Attribute Floats values are incorrect"
     write(name, *) "Verify Attribute Floats Values Test"
     call ESMF_Test((all(sigU.eq.sigU_1)), name, failMsg, result, ESMF_SRCLINE)


!      Similarly for v
!''''''''''''''''''''''''''''

     !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get Next LIne Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get Next Line Test"
      call ESMF_ConfigNextLine( cf, rc=rc )
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc == ESMF_SUCCESS) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigNextLine failed, rc =', rc 
         return        
      endif

!''''''''''''''''''''''''''''

     !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get STring Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get String Test"
      call ESMF_ConfigGetAttribute( cf, v_dataType, rc=rc )
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(string) failed, rc =', rc
         return
      endif

      if(v_dataType ==  v_dataType_1) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigGetAttribute(string) ERROR: got  =', &
                  v_dataType, ' should be ', v_dataType_1
         return
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute String Verification Test
     write(failMsg, *) "Attribute String values are incorrect"
     write(name, *) "Verify Attribute String Values Test"
     call ESMF_Test((v_dataType.eq.v_dataType_1), name, failMsg, result, ESMF_SRCLINE)

!''''''''''''''''''''''''''''
     !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get Int Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get Int Test"
      call ESMF_ConfigGetAttribute( cf, nv, rc=rc )
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(int) failed, rc =', rc
         return
      endif

      if( nv == nv_1 ) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigGetAttribute(int) ERROR: got  =', nv, &
              ' should be ', nv_1 
         return
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Int Verification Test
     write(failMsg, *) "Attribute Int values are incorrect"
     write(name, *) "Verify Attribute Int Values Test"
     call ESMF_Test((nv.eq.nv_1), name, failMsg, result, ESMF_SRCLINE)


!''''''''''''''''''''''''''''
     !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get Floats Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get Floats Test"
      call ESMF_ConfigGetAttribute( cf, sigV, count=6,rc=rc )
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

     counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetAttribute(floats) failed, rc =', rc
         return
      endif

      if( any(sigV /= sigV_1) ) then
         print *,'ESMF_ConfigGetAttribute(floats) ERROR: got sigV =', &
                 sigV(1:nv), ' should be sigV =', sigV_1(1:nv_1) 
         return
      else
        counter_success =counter_success + 1
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Attribute Floats Verification Test
     write(failMsg, *) "Attribute Floats values are incorrect"
     write(name, *) "Verify Attribute Floats Values Test"
     call ESMF_Test((all(sigV.eq.sigV_1)), name, failMsg, result, ESMF_SRCLINE)

    end subroutine MultPar_MultLines


!--------------------------------------------------------------------
    subroutine Table()
!--------------------------------------------------------------------
      integer, parameter   :: nlines_0 = 11
      integer, dimension(nlines_0), parameter :: ncol_0 = &
           (/ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11/)
      real(ESMF_KIND_R4), dimension(nlines_0), parameter ::plev_0 = &
           (/1000, 925, 850, 700, 500, 400, 300, 250, 200, 150, 100/)
      real(ESMF_KIND_R4), dimension(nlines_0, nlines_0) :: vCorr_0
!!!      real(ESMF_KIND_R4) :: vCorr_aux(121)
      character(ESMF_MAXSTR) :: failMsg
      character(ESMF_MAXSTR) :: name
      integer :: memstat

      integer :: result = 0
     
      vCorr_0 = RESHAPE (  (/ &
           1.00, 0., 0., 0., 0., 0., 0.,0., 0., 0., 0., &
           0.84, 1.00, 0., 0., 0., 0.,0., 0.,0., 0., 0., &
           0.68, 0.84, 1.00, 0., 0., 0., 0.,0., 0.,0., 0., & 
           0.53, 0.67, 0.81, 1.00, 0., 0., 0., 0.,0., 0.,0., & 
           0.35, 0.46, 0.56, 0.81, 1.00, 0., 0., 0., 0.,0., 0., & 
           0.27, 0.35, 0.44, 0.64, 0.79, 1.00, 0., 0., 0., 0.,0., & 
           0.18, 0.25, 0.32, 0.46, 0.58, 0.75, 1.00, 0., 0., 0., 0.,& 
           0.13, 0.19, 0.25, 0.38, 0.48, 0.62, 0.83, 1.00,  0., 0., 0., & 
           0.09, 0.14, 0.19, 0.29, 0.38, 0.49, 0.66, 0.80, 1.00, 0., 0., & 
           0.06, 0.09, 0.13, 0.20, 0.28, 0.36, 0.49, 0.59, 0.75, 1.00, 0., & 
           0.00, 0.03, 0.06, 0.10, 0.17, 0.23, 0.32, 0.39, 0.50, 0.75, 1.00  &
           /),  (/11,11/)  )


      
!            Get dimension, label and start getting lines

      rc = 0

!''''''''''''''''''''''''''''

     !------------------------------------------------------------------------
      !EX_UTest
      ! Config Get Dim Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Get Dim Test"
      call ESMF_ConfigGetDim(cf, nlines, col, label='ObsErr*vCor_HH-7::', rc=rc)
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''
      counter_total =counter_total + 1
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetDim failed, rc =', rc
         return
      endif

      if( nlines == nlines_0 ) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigGetDim ERROR: got  =', nlines, &
              ' should be ', nlines_0 
         return
      endif

     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Dim Verification Test
     write(failMsg, *) "Attribute Dim values are incorrect"
     write(name, *) "Verify Attribute Dim Values Test"
     call ESMF_Test((nlines.eq.nlines_0), name, failMsg, result, ESMF_SRCLINE)

      
!''''''''''''''''''''''''''''         

     !------------------------------------------------------------------------
      !EX_UTest
      ! Config Find Label Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Find Label Test"
      call ESMF_ConfigFindLabel( cf,'ObsErr*vCor_HH-7::', rc=rc)
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''
      counter_total =counter_total + 1
      if (rc == ESMF_SUCCESS) then
         counter_success =counter_success + 1
      else
          print *,'ESMF_ConfigFindLabel failed, label ObsErr*vCor_HH-7::, = rc =', rc 
         return        
      endif

!''''''''''''''''''''''''''''     
         allocate(ncol(1:nlines), STAT= memstat)
!''''''''''''''''''''''''''''
      if (memstat /= 0) then
         print *,'array allocation failed, stat =', memstat
         rc = ESMF_RC_MEM
         return
      endif
      
      counter_total =counter_total + 1
!'''''''''''''''''''''''''''' 
      do line = 1, nlines

      call ESMF_ConfigNextLine(cf, rc = rc)
!''''''''''''''''''''''''''''
         if (rc /= ESMF_SUCCESS) then
            print *,'ESMF_ConfigNextLine failed, rc =', rc 
            exit        
         endif
!''''''''''''''''''''''''''''    
      ncol(line) = ESMF_ConfigGetLen(cf, rc = rc) - 1
!''''''''''''''''''''''''''''  
      if (rc /= ESMF_SUCCESS) then
         print *,'ESMF_ConfigGetLen failed, rc =', rc
         exit
      endif
!''''''''''''''''''''''''''''  
      enddo
!''''''''''''''''''''''''''''


     !------------------------------------------------------------------------
     !EX_UTest
     ! Config Get Next Line and Get Len Verification Test
     write(failMsg, *) "Attribute Line values are incorrect"
     write(name, *) "Verify Attribute Line Values Test"
     call ESMF_Test((all(ncol.eq.ncol_0)), name, failMsg, result, ESMF_SRCLINE)

      if( any(ncol /= ncol_0 )) then
         print *,'ESMF_ConfigGetInt ERROR: got ncol =', ncol(1:nlines), &
              ' should be ncol =', ncol_0(1:nlines_0) 
         return
      else
         counter_success =counter_success + 1
      endif


!            Looping over lines

!''''''''''''''''''''''''''''   
     !------------------------------------------------------------------------
      !EX_UTest
      ! Config Find Label Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Bad Label Test"
      call ESMF_ConfigFindLabel( cf,'Bad', rc=rc)
      call ESMF_Test(rc /= ESMF_SUCCESS, name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
      !EX_UTest
      ! Config Find Label Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Find Label Test"
      call ESMF_ConfigFindLabel( cf,'ObsErr*vCor_HH-7::', rc=rc)
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''
      counter_total =counter_total + 1
      if (rc == ESMF_SUCCESS) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigFindLabel failed, label = ObsErr*vCor_HH-7::, rc =', rc 
         return        
      endif


!''''''''''''''''''''''''''''
      do line = 1, nlines
         call ESMF_ConfigNextLine( cf, tableEnd=end, rc=rc)
!''''''''''''''''''''''''''''

         if (rc /= ESMF_SUCCESS) then
            print *,'ESMF_ConfigNextLine failed, rc =', rc 
            exit        
         endif
            
!               Retrieve pressure level
!               -----------------------
         counter_total =counter_total + 1
!''''''''''''''''''''''''''''
            call ESMF_ConfigGetAttribute( cf, plev(line), rc=rc )
!''''''''''''''''''''''''''''
         if (rc /= ESMF_SUCCESS) then
            print *,'ESMF_ConfigAttribute failed, rc =', rc 
            exit
         endif

         if( plev(line) /= plev_0(line) ) then
            print *,'ESMF_ConfigGetAttribute(float) ERROR: got plev =', &
                 plev(line), ' should be plev =', plev_0(line) 
            exit
         else
            counter_success =counter_success + 1
         endif
            
!               Looping over columns
!               --------------------
         counter_total =counter_total + 1
!''''''''''''''''''''''''''''
         do col =1, ncol(line)
            call ESMF_ConfigGetAttribute( cf, temp, rc=rc)
            if (rc == ESMF_SUCCESS) then 
               vCorr(line,col) = temp 
            end if
         end do
!''''''''''''''''''''''''''''
         if (rc /= ESMF_SUCCESS) then
            print *,'ESMF_ConfigGetAttribute(float) failed, rc =', rc 
            exit        
         endif

         
         do col =1, ncol(line)
            if (vCorr(line, col) /= vCorr_0(col, line)) then
               print *,'ESMF_ConfigGetAttribute(float):  Wrong value in vCorr line =', &
                   line,' col =', col,' VCorr = ', vCorr(col, line), &
                   ' should be ', vCorr_0(line, col)
               exit
            endif
         end do
         counter_success = counter_success + 1

!''''''''''''''''''''''''''''    
      end do
!''''''''''''''''''''''''''''
!''''''''''''''''''''''''''''     
      deallocate(ncol, STAT= memstat)
!''''''''''''''''''''''''''''
      if (memstat /= 0) then
         print *,'array deallocation failed, stat =', memstat
         rc = ESMF_RC_MEM
      endif


      return
    end subroutine Table

!--------------------------------------------------------------------
    subroutine SingleParSet()
!--------------------------------------------------------------------
      integer :: memberNum, numMembers, numConstituents, numDelegates
      character(ESMF_MAXSTR) :: failMsg
      character(ESMF_MAXSTR) :: name
      integer :: result = 0

      rc = 0

!''''''''''''''''''''''''''''

     !-----------------------------------------------------------------------
     !EX_UTest
     ! Config Set Attribute Int Test 1: Append to end of config object
     write(failMsg, *) "Did not return Member_Number 20 and ESMF_SUCCESS"
     write(name, *) "Config Set Attribute IntI4 Test 1"
     call ESMF_ConfigSetAttribute(cf, 20, label = 'Member_Number:', rc = rc)
     call ESMF_ConfigGetAttribute(cf, memberNum, &
                                  label = 'Member_Number:', rc = rc)
     call ESMF_Test((memberNum.eq.20 .and. rc.eq.ESMF_SUCCESS), &
                     name, failMsg, result, ESMF_SRCLINE)

!''''''''''''''''''''''''''''
      
      counter_total =counter_total + 1
      if ( rc /= ESMF_SUCCESS ) then      
         print *,'ESMF_ConfigSetAttribute(intI4) got Member_Num =', memberNum, &
                 ' rc =', rc
      else
        if (memberNum == 20) then
          counter_success =counter_success + 1
        else
          print *,'ESMF_ConfigSetAttribute(intI4) ERROR: got Member_Number =', &
                    memberNum, ' should be 20'
        endif
      endif

     !-----------------------------------------------------------------------
     !EX_UTest
     ! Config Set Attribute Int Test 2:  Overwrite; same number of characters
     write(failMsg, *) "Did not return Number_of_Members 40 and ESMF_SUCCESS"
     write(name, *) "Config Set Attribute IntI4 Test 2"
     call ESMF_ConfigSetAttribute(cf, 40, label = 'Number_of_Members:', rc = rc)
     call ESMF_ConfigGetAttribute(cf, numMembers, &
                                  label = 'Number_of_Members:', rc = rc)
     call ESMF_Test((numMembers.eq.40 .and. rc.eq.ESMF_SUCCESS), &
                     name, failMsg, result, ESMF_SRCLINE)

!''''''''''''''''''''''''''''
      
      counter_total =counter_total + 1
      if ( rc /= ESMF_SUCCESS ) then      
         print *,'ESMF_ConfigSetAttribute(intI4) got numMembers=', numMembers, &
                 ' rc =', rc
      else
        if (numMembers == 40) then
          counter_success =counter_success + 1
        else
          print *,'ESMF_ConfigSetAttribute(intI4) ERROR: got numMembers= ', &
                    numMembers, ' should be 40'
        endif
      endif

     !-----------------------------------------------------------------------
     !EX_UTest
     ! Config Set Attribute Int Test 3: Overwrite; insert 1 extra character
     write(failMsg, *) &
           "Did not return Number_of_Constituents 123 and ESMF_SUCCESS"
     write(name, *) "Config Set Attribute IntI4 Test 3"
     call ESMF_ConfigSetAttribute(cf, 123, label = 'Number_of_Constituents:', &
                                  rc = rc)
     call ESMF_ConfigGetAttribute(cf, numConstituents, &
                                  label = 'Number_of_Constituents:', rc = rc)
     call ESMF_Test((numConstituents.eq.123 .and. rc.eq.ESMF_SUCCESS), &
                     name, failMsg, result, ESMF_SRCLINE)

!''''''''''''''''''''''''''''
      
      counter_total =counter_total + 1
      if ( rc /= ESMF_SUCCESS ) then      
         print *,'ESMF_ConfigSetAttribute(intI4) got numConstituents=', &
                  numConstituents, ' rc =', rc
      else
        if (numConstituents == 123) then
          counter_success =counter_success + 1
        else
          print *, &
              'ESMF_ConfigSetAttribute(intI4) ERROR: got numConstituents= ', &
                    numConstituents, ' should be 123'
        endif
      endif

     !-----------------------------------------------------------------------
     !EX_UTest
     ! Config Set Attribute Int Test 4:  Overwrite; delete 1 extra character
     write(failMsg, *) "Did not return Number_of_Delegates 5 and ESMF_SUCCESS"
     write(name, *) "Config Set Attribute IntI4 Test 4"
     call ESMF_ConfigSetAttribute(cf, 5, label = 'Number_of_Delegates:', &
                                  rc = rc)
     call ESMF_ConfigGetAttribute(cf, numDelegates, &
                                  label = 'Number_of_Delegates:', rc = rc)
     call ESMF_Test((numDelegates.eq.5 .and. rc.eq.ESMF_SUCCESS), &
                     name, failMsg, result, ESMF_SRCLINE)

!''''''''''''''''''''''''''''
      
      counter_total =counter_total + 1
      if ( rc /= ESMF_SUCCESS ) then      
         print *, 'ESMF_ConfigSetAttribute(intI4) got numDelegates=', &
                   numDelegates, ' rc =', rc
      else
        if (numDelegates == 5) then
          counter_success =counter_success + 1
        else
          print *,'ESMF_ConfigSetAttribute(intI4) ERROR: got numDelegates= ', &
                    numDelegates, ' should be 5'
        endif
      endif

    end subroutine SingleParSet

!--------------------------------------------------------------------
    subroutine Sections()
!--------------------------------------------------------------------

      character(ESMF_MAXSTR) :: failMsg
      character(ESMF_MAXSTR) :: name
      character(ESMF_MAXSTR) :: token_string
      integer :: result = 0
      integer :: columnCount, lineCount, m, n
      logical :: success
      real :: rvalue

      integer, parameter :: ncol = 5
      integer, parameter :: nrow = 3
      integer, parameter :: nval = 9
      real, dimension(nval), parameter :: data_values = &
        (/ 0.71, 1.37, 2.63, 5.00, 9.50, 18.1, 34.5, 65.5, 125.0 /)
      real, dimension(nrow,ncol), parameter :: table_values = &
        reshape((/ &
          0.1, 0.2, 0.3, 0.4, 0.5, &
          1.1, 1.2, 1.3, 1.4, 1.5, &
          2.1, 2.2, 2.3, 2.4, 2.5  &
        /), (/nrow,ncol/), order=(/2,1/))

      rc = 0
!''''''''''''''''''''''''''''
      !EX_UTest
      ! Test Config Create From Empty Section
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Create From Empty Section Test"
      cf2 = ESMF_ConfigCreate(cf, "%section_empty_open", "%section_empty_close", rc=rc)
      success = rc.eq.ESMF_SUCCESS
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

      !------------------------------------------------------------------------
      !EX_UTest
      ! Test Config From Empty Section Destroy
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config From Empty Section Log Test"
      call ESMF_ConfigLog(cf2, prefix="Config From Empty Section: ", rc=rc)
      success = rc.eq.ESMF_SUCCESS
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

      !------------------------------------------------------------------------
      !EX_UTest
      ! Test Config From Empty Section Destroy
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config From Empty Section Destroy Test"
      call ESMF_ConfigDestroy(cf2, rc=rc)
      success = rc.eq.ESMF_SUCCESS
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

      !------------------------------------------------------------------------
      !EX_UTest
      ! Test Config Create From Section
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Create From Section Test"
      cf2 = ESMF_ConfigCreate(cf, "%section_open", "%section_close", rc=rc)
      success = rc.eq.ESMF_SUCCESS
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

      !------------------------------------------------------------------------
      !EX_UTest
      ! Test Config From Section Log
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config from Section Log Test"
      call ESMF_ConfigLog(cf2, prefix="Config from Section: ", rc=rc)
      success = rc.eq.ESMF_SUCCESS
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

      !------------------------------------------------------------------------
      !EX_UTest
      ! Test Config From Section Destroy
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config From Section Destroy Test"
      call ESMF_ConfigDestroy( cf2, rc=rc)
      success = rc.eq.ESMF_SUCCESS
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

      !------------------------------------------------------------------------
      !EX_UTest
      ! Test Config Create From Section with Table
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Create From Section with Table Test"
      cf2 = ESMF_ConfigCreate(cf, "%section_with_table", "%%", rc=rc)
      success = rc.eq.ESMF_SUCCESS
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

      !------------------------------------------------------------------------
      !EX_UTest
      ! Test Config From Section with Table Log
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Create From Section with Table Log Test"
      call ESMF_ConfigLog(cf2, prefix="Config Create From Section with Table: ", rc=rc)
      success = rc.eq.ESMF_SUCCESS
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

      !------------------------------------------------------------------------
      !EX_UTest
      ! Config Section Get Attribute String multi-word token Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Section Get Attribute String Multi-word Token"
      call ESMF_ConfigGetAttribute(cf2, token_string, &
        label='section_table_token:', rc=rc)
      success = rc.eq.ESMF_SUCCESS
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

      !------------------------------------------------------------------------
      !EX_UTest
      ! Config Section Validate Attribute String multi-word token Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Section Validate Attribute String Multi-word apostrophe Token Test"
      success = (token_string == 'This example deals with sections including a table')
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: did not validate'
        print *,'read in : ' // trim(token_string)
        print *,'expected: ' // 'This example deals with sections including a table'
      end if

      !-----------------------------------------------------------------------
      !EX_UTest
      ! Config Section Find Next Label section_data_values Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Section Find Next Label section_data_values Test"
      call ESMF_ConfigFindNextLabel(cf2, label='section_data_values:', isPresent=success, rc=rc)
      success = success .and. (rc.eq.ESMF_SUCCESS)
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

      !-----------------------------------------------------------------------
      !EX_UTest
      ! Config Section Get Attribute section_data_num Test
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Section Get Attribute section_data_num Test"
      call ESMF_ConfigGetAttribute(cf2, m, label='section_data_num:', rc=rc)
      success = (rc.eq.ESMF_SUCCESS)
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

      !-----------------------------------------------------------------------
      !EX_UTest
      ! Config Section Validate Attribute section_data_num Values Test
      write(failMsg, *) "Did not validate section_data_num value"
      write(name, *) "Config Section Validate Attribute section_data_num Value Test"
      success = (m.eq.nval)
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: did not validate'
        print *,'read in : ', m
        print *,'expected: ', nval
      end if

      !-----------------------------------------------------------------------
      !EX_UTest
      ! Config Section Get Attribute section_data_values Test
      write(failMsg, *) "Did not return section_data_values and ESMF_SUCCESS"
      write(name, *) "Config Section Get Attribute section_data_values Test"

      call ESMF_ConfigFindLabel(cf2, "section_data_values:", rc=rc)
      success = rc.eq.ESMF_SUCCESS
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

      !-----------------------------------------------------------------------
      !EX_UTest
      ! Config Section Attribute Validate section_data_values Values Test
      write(failMsg, *) "Did not validate section_data_values: multiple values"
      write(name, *) "Config Section Validate Attribute section_data_values Values Test"

      counter_total = counter_total + 1

      if (success) then
        n = 0
        do while (success .and. (n.lt.m))
          n = n + 1
          call ESMF_ConfigGetAttribute(cf2, rvalue, default=0.0, rc=rc)
          success = (rc.eq.ESMF_SUCCESS) .and. (rvalue.eq.data_values(n))
        end do

        call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

        if (success) then
          counter_success = counter_success + 1
        else
          if (rc.eq.ESMF_SUCCESS) then
            print *, trim(name) // ' ERROR: did not validate'
            print *,'read in : ', m
            print *,'expected: ', nval
          else
            print *, trim(name) // ' ERROR: rc = ', rc
          end if
        end if
      else
        call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)
      end if

      !------------------------------------------------------------------------
      !EX_UTest
      ! TEST Config Section Read Table
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Section Read Table Test"

      call ESMF_ConfigFindLabel(cf2, "section_table::", rc=rc)
      success = rc.eq.ESMF_SUCCESS
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

      !------------------------------------------------------------------------
      !EX_UTest
      ! TEST Config Section Validate Table Dimensions
      write(failMsg, *) "Did not validate table dimensions"
      write(name, *) "Config Section Read Table Dimensions Test"

      counter_total = counter_total + 1

      if (success) then
        columnCount = 0
        lineCount = 0
        call ESMF_ConfigGetDim(cf2, lineCount, columnCount, rc=rc)
        success = (columnCount.eq.ncol) .and. (lineCount.eq.nrow)
        success = success .and. rc.eq.ESMF_SUCCESS

        call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

        if (success) then
          counter_success = counter_success + 1
        else
          if (rc.eq.ESMF_SUCCESS) then
            print *, trim(name) // ' ERROR: did not validate'
            print *,'read in : ', lineCount, columnCount
            print *,'expected: ', nrow, ncol
          else
            print *, trim(name) // ' ERROR: rc = ', rc
          end if
        end if
      else
        call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)
      end if

      !------------------------------------------------------------------------
      !EX_UTest
      ! TEST Config Section Validate Table Values
      write(failMsg, *) "Did not validate table values"
      write(name, *) "Config Section Read Table Values Test"

      call ESMF_ConfigFindLabel(cf2, "section_table::", rc=rc)
      success = rc.eq.ESMF_SUCCESS

      counter_total = counter_total + 1

      if (success) then
        m = 0
        do while (success .and. (m.lt.lineCount))
          m = m + 1
          call ESMF_ConfigNextLine(cf2, rc=rc)
          success = rc.eq.ESMF_SUCCESS
          n = 0
          do while (success .and. (n.lt.columnCount))
            n = n + 1
            call ESMF_ConfigGetAttribute(cf2, rvalue, default=0.0, rc=rc)
            success = (rc.eq.ESMF_SUCCESS) .and. (rvalue.eq.table_values(m,n))
          end do
        end do

        call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

        if (success) then
          counter_success = counter_success + 1
        else
          if (rc.eq.ESMF_SUCCESS) then
            print *, trim(name) // ' ERROR: did not validate'
            print *,'read in : ', rvalue
            print *,'expected: ', table_values(m,n)
          else
            print *, trim(name) // ' ERROR: rc = ', rc
          end if
        end if
      else
        call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)
      end if

      !------------------------------------------------------------------------
      !EX_UTest
      ! Test Config Validate
      write(failMsg, *) "Did not return ESMF_RC_ATTR_UNUSED"
      write(name, *) "Config From Section Validate Test"
      call ESMF_ConfigValidate(cf2, options="unusedAttributes", rc=rc)
      call ESMF_Test((rc.eq.ESMF_RC_ATTR_UNUSED), name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (rc == ESMF_RC_ATTR_UNUSED) then
         counter_success = counter_success + 1
      else
         print *,'ESMF_ConfigValidate failed, rc =', rc
      endif

      !------------------------------------------------------------------------
      !EX_UTest
      ! Test Config From Section Destroy
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config From Section Destroy Test"
      call ESMF_ConfigDestroy(cf2, rc=rc)
      success = rc.eq.ESMF_SUCCESS
      call ESMF_Test(success, name, failMsg, result, ESMF_SRCLINE)

      counter_total = counter_total + 1
      if (success) then
        counter_success = counter_success + 1
      else
        print *, trim(name) // ' ERROR: rc = ', rc
      end if

    end subroutine Sections

!--------------------------------------------------------------------
    subroutine Finalization()
!--------------------------------------------------------------------

      character(ESMF_MAXSTR) :: failMsg
      character(ESMF_MAXSTR) :: name
      integer :: result = 0
      rc = 0
!''''''''''''''''''''''''''''
      !------------------------------------------------------------------------
      !EX_UTest
      ! Test Config Validate
      write(failMsg, *) "Did not return ESMF_RC_ATTR_UNUSED"
      write(name, *) "Config Validate Test"
      call ESMF_ConfigValidate( cf, options="unusedAttributes", rc=rc)
      call ESMF_Test((rc.eq.ESMF_RC_ATTR_UNUSED), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc == ESMF_RC_ATTR_UNUSED) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigValidate failed, rc =', rc 
      endif

!''''''''''''''''''''''''''''
      !------------------------------------------------------------------------
      !EX_UTest
      ! Test Config Destroy
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Destroy Test"
      call ESMF_ConfigDestroy( cf, rc=rc) 
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
!''''''''''''''''''''''''''''

      counter_total =counter_total + 1
      if (rc == ESMF_SUCCESS) then
         counter_success =counter_success + 1
      else
         print *,'ESMF_ConfigDestroy failed, rc =', rc 
      endif
      
    end subroutine Finalization

end module config_subrs



    program ESMF_Config_Test


!USES
      use ESMF_TestMod     ! test methods
      use ESMF
      use config_subrs

      implicit none

!------------------------------------------------------------------------------
! The following line turns the CVS identifier string into a printable variable.
      character(*), parameter :: version = &
      '$Id$'
!------------------------------------------------------------------------------

      counter_total = 0
      counter_success = 0
 
!-------------------------------------------------------------------------------
! The unit tests are divided into Sanity and Exhaustive. The Sanity tests are
! always run. When the environment variable, EXHAUSTIVE, is set to ON then
! the EXHAUSTIVE and sanity tests both run. If the EXHAUSTIVE variable is set
! to OFF, then only the sanity unit tests.
! Special strings (Non-exhaustive and exhaustive) have been
! added to allow a script to count the number and types of unit tests.
!-------------------------------------------------------------------------------


      call ESMF_TestStart(ESMF_SRCLINE, rc=rc)
      if (rc /= ESMF_SUCCESS) call ESMF_Finalize(endflag=ESMF_END_ABORT)


      !------------------------------------------------------------------------
      !NEX_UTest
      write(name, *) "Testing Config IsCreated for uncreated object"
      write(failMsg, *) "Did not return .false."
      isCreated = ESMF_ConfigIsCreated(cf)
      call ESMF_Test((isCreated .eqv. .false.), name, failMsg, result, ESMF_SRCLINE)
      !------------------------------------------------------------------------

      !------------------------------------------------------------------------
      !NEX_UTest
      write(name, *) "Testing Config IsCreated for uncreated object"
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      isCreated = ESMF_ConfigIsCreated(cf, rc=rc)
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
      !------------------------------------------------------------------------

      !------------------------------------------------------------------------
      !NEX_UTest
      write(name, *) "Create test Config for IsCreated"
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      cf = ESMF_ConfigCreate(rc=rc)
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
      !------------------------------------------------------------------------

      !------------------------------------------------------------------------
      !NEX_UTest
      write(name, *) "Testing Config IsCreated for created object"
      write(failMsg, *) "Did not return .true."
      isCreated = ESMF_ConfigIsCreated(cf)
      call ESMF_Test((isCreated .eqv. .true.), name, failMsg, result, ESMF_SRCLINE)
      !------------------------------------------------------------------------

      !------------------------------------------------------------------------
      !NEX_UTest
      write(name, *) "Testing Config IsCreated for created object"
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      isCreated = ESMF_ConfigIsCreated(cf, rc=rc)
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
      !------------------------------------------------------------------------

      !------------------------------------------------------------------------
      !NEX_UTest
      write(name, *) "Destroy test Config for IsCreated"
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      call ESMF_ConfigDestroy(cf, rc=rc)
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
      !------------------------------------------------------------------------

      !------------------------------------------------------------------------
      !NEX_UTest
      write(name, *) "Testing Config IsCreated for destroyed object"
      write(failMsg, *) "Did not return .false."
      isCreated = ESMF_ConfigIsCreated(cf)
      call ESMF_Test((isCreated .eqv. .false.), name, failMsg, result, ESMF_SRCLINE)
      !------------------------------------------------------------------------

      !------------------------------------------------------------------------
      !NEX_UTest
      write(name, *) "Testing Config IsCreated for destroyed object"
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      isCreated = ESMF_ConfigIsCreated(cf, rc=rc)
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)
      !------------------------------------------------------------------------

      !------------------------------------------------------------------------
      !NEX_UTest
      ! Test Config Create
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Create Test"
      cf = ESMF_ConfigCreate(rc=rc)
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

      !------------------------------------------------------------------------
      !NEX_UTest
      ! Test Config Print
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Print Test"
      call ESMF_ConfigPrint(cf, rc=rc)
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

      !------------------------------------------------------------------------
      !NEX_UTest
      ! Test Config Destroy
      write(failMsg, *) "Did not return ESMF_SUCCESS"
      write(name, *) "Config Destroy Test"
      call ESMF_ConfigDestroy( cf, rc=rc) 
      call ESMF_Test((rc.eq.ESMF_SUCCESS), name, failMsg, result, ESMF_SRCLINE)

#ifdef ESMF_TESTEXHAUSTIVE

      !------------------------------------------------------------------------
      !EX_UTest
      ! Test Config Destroy of a destroyed Config
      write(failMsg, *) "Did not return ESMF_RC_OBJ_DELETED"
      write(name, *) "Destroy a destroyed Config Test"
      call ESMF_ConfigDestroy( cf, rc=rc) 
      call ESMF_Test((rc.eq.ESMF_RC_OBJ_DELETED), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Destroyed Config Get Attribute Int Test
     write(failMsg, *) "Did not return ESMF_RC_OBJ_DELETED"
     write(name, *) "Destroyed Config Get Attribute Int Test"
     call ESMF_ConfigGetAttribute( cf, nDE, label ='Number_of_DEs:', &
           default=7, rc = rc )
     call ESMF_Test((rc.eq.ESMF_RC_OBJ_DELETED), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Destroyed Config Get Attribute Char Test
     write(failMsg, *) "Did not return ESMF_RC_OBJ_DELETED"
     write(name, *) "Destroyed Config Get Attribute Char Test"
     call ESMF_ConfigGetChar( cf, answer, label='Do_you_want_quality_control:', &
                                    rc = rc )
     call ESMF_Test((rc.eq.ESMF_RC_OBJ_DELETED), name, failMsg, result, ESMF_SRCLINE)

     !------------------------------------------------------------------------
     !EX_UTest
     ! Destroyed Config Find Label Test
      write(failMsg, *) "Did not return ESMF_RC_OBJ_DELETED"
      write(name, *) "Non-create Config Find Label Test"
      call ESMF_ConfigFindLabel( cf, 'v-wind_flag:', rc=rc)
      call ESMF_Test((rc.eq.ESMF_RC_OBJ_DELETED), name, failMsg, result, ESMF_SRCLINE)




! Initialization:
!----------------
      call Initialization()
      if (rc /= ESMF_RC_DUP_NAME) then
        call ESMF_ConfigDestroy( cf, rc=rc) 
        call ESMF_TestEnd(ESMF_SRCLINE)
        STOP            ! Catastropic Error
      endif

! Retrieval of single parameters
!--------------------------------
      call SinglePar()


! Retrieval of a group of parameters on a single line
! ----------------------------------------------------

      call  MultPar_SingleLine_U()
      call  MultPar_SingleLine_V()
      call  MultPar_SingleLine_Vf()


! Retrieval of a group of parameters on multiple lines
!   ----------------------------------------------------
      call MultPar_MultLines()


! Retrieval of Tables of unknown length
! ---------------------------------------

      call Table()

!
! Setting of single parameters
! ------------------------------
      call SingleParSet()

! Sections
! ------------------------------
      call Sections()


! Finalization
! ------------
 
      call Finalization()

! REPORTING
! ------------
      
      !EX_UTest
      write(failMsg, *) "Config Unit test failed"
      write(name, *) "Config Unit Test"
      call ESMF_Test((counter_success.eq.counter_total), name, failMsg, result, ESMF_SRCLINE)
      if  (counter_total > 0) then
         if( counter_success == counter_total ) then 
            print *,'ESMF_Config: All tests were successful'
         else
            success_rate = 100.0 * counter_success / counter_total 
            print *,'ESMF_Config: Success rate: ', nint(success_rate),'%' 
         endif
      endif

#endif

      call ESMF_TestEnd(ESMF_SRCLINE)


  end program ESMF_Config_Test