utCFIO_Nbits.F90 Source File


This file depends on

sourcefile~~utcfio_nbits.f90~~EfferentGraph sourcefile~utcfio_nbits.f90 utCFIO_Nbits.F90 sourcefile~base_base.f90 Base_Base.F90 sourcefile~utcfio_nbits.f90->sourcefile~base_base.f90 sourcefile~esmf_cfiomod.f90 ESMF_CFIOMod.F90 sourcefile~utcfio_nbits.f90->sourcefile~esmf_cfiomod.f90 sourcefile~mapl_cfio.f90 MAPL_CFIO.F90 sourcefile~utcfio_nbits.f90->sourcefile~mapl_cfio.f90 sourcefile~mapl_comms.f90 MAPL_Comms.F90 sourcefile~utcfio_nbits.f90->sourcefile~mapl_comms.f90 sourcefile~constants.f90 Constants.F90 sourcefile~base_base.f90->sourcefile~constants.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~base_base.f90->sourcefile~keywordenforcer.f90 sourcefile~mapl_range.f90 MAPL_Range.F90 sourcefile~base_base.f90->sourcefile~mapl_range.f90 sourcefile~maplgrid.f90 MaplGrid.F90 sourcefile~base_base.f90->sourcefile~maplgrid.f90 sourcefile~esmf_cfiofilemod.f90 ESMF_CFIOFileMod.F90 sourcefile~esmf_cfiomod.f90->sourcefile~esmf_cfiofilemod.f90 sourcefile~esmf_cfiogridmod.f90 ESMF_CFIOGridMod.F90 sourcefile~esmf_cfiomod.f90->sourcefile~esmf_cfiogridmod.f90 sourcefile~esmf_cfiosdfmod.f90 ESMF_CFIOSdfMod.F90 sourcefile~esmf_cfiomod.f90->sourcefile~esmf_cfiosdfmod.f90 sourcefile~esmf_cfioutilmod.f90 ESMF_CFIOUtilMod.F90 sourcefile~esmf_cfiomod.f90->sourcefile~esmf_cfioutilmod.f90 sourcefile~esmf_cfiovarinfomod.f90 ESMF_CFIOVarInfoMod.F90 sourcefile~esmf_cfiomod.f90->sourcefile~esmf_cfiovarinfomod.f90 sourcefile~mapl_cfio.f90->sourcefile~base_base.f90 sourcefile~mapl_cfio.f90->sourcefile~esmf_cfiomod.f90 sourcefile~mapl_cfio.f90->sourcefile~mapl_comms.f90 sourcefile~cfiocollection.f90 CFIOCollection.F90 sourcefile~mapl_cfio.f90->sourcefile~cfiocollection.f90 sourcefile~mapl_cfio.f90->sourcefile~constants.f90 sourcefile~mapl_cfio.f90->sourcefile~esmf_cfiofilemod.f90 sourcefile~mapl_cfio.f90->sourcefile~esmf_cfioutilmod.f90 sourcefile~esmfl_mod.f90 ESMFL_Mod.F90 sourcefile~mapl_cfio.f90->sourcefile~esmfl_mod.f90 sourcefile~mapl_abstractgridfactory.f90 MAPL_AbstractGridFactory.F90 sourcefile~mapl_cfio.f90->sourcefile~mapl_abstractgridfactory.f90 sourcefile~mapl_abstractregridder.f90 MAPL_AbstractRegridder.F90 sourcefile~mapl_cfio.f90->sourcefile~mapl_abstractregridder.f90 sourcefile~mapl_config.f90 MAPL_Config.F90 sourcefile~mapl_cfio.f90->sourcefile~mapl_config.f90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~mapl_cfio.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~mapl_getlatloncoord.f90 MAPL_GetLatLonCoord.F90 sourcefile~mapl_cfio.f90->sourcefile~mapl_getlatloncoord.f90 sourcefile~mapl_gridmanager.f90 MAPL_GridManager.F90 sourcefile~mapl_cfio.f90->sourcefile~mapl_gridmanager.f90 sourcefile~mapl_io.f90 MAPL_IO.F90 sourcefile~mapl_cfio.f90->sourcefile~mapl_io.f90 sourcefile~mapl_latlongridfactory.f90 MAPL_LatLonGridFactory.F90 sourcefile~mapl_cfio.f90->sourcefile~mapl_latlongridfactory.f90 sourcefile~mapl_memutils.f90 MAPL_MemUtils.F90 sourcefile~mapl_cfio.f90->sourcefile~mapl_memutils.f90 sourcefile~mapl_regriddermanager.f90 MAPL_RegridderManager.F90 sourcefile~mapl_cfio.f90->sourcefile~mapl_regriddermanager.f90 sourcefile~mapl_sort.f90 MAPL_Sort.F90 sourcefile~mapl_cfio.f90->sourcefile~mapl_sort.f90 sourcefile~newregriddermanager.f90 NewRegridderManager.F90 sourcefile~mapl_cfio.f90->sourcefile~newregriddermanager.f90 sourcefile~pfio.f90 pFIO.F90 sourcefile~mapl_cfio.f90->sourcefile~pfio.f90 sourcefile~regridmethods.f90 RegridMethods.F90 sourcefile~mapl_cfio.f90->sourcefile~regridmethods.f90 sourcefile~shmem.f90 Shmem.F90 sourcefile~mapl_cfio.f90->sourcefile~shmem.f90 sourcefile~stringtemplate.f90 StringTemplate.F90 sourcefile~mapl_cfio.f90->sourcefile~stringtemplate.f90 sourcefile~mapl_comms.f90->sourcefile~base_base.f90 sourcefile~mapl_comms.f90->sourcefile~constants.f90 sourcefile~mapl_comms.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~mapl_comms.f90->sourcefile~shmem.f90

Source Code

!
! Simple unit test for CFIO Read/Write Bundle with variable NBIT precision
!

#include "MAPL_Generic.h"

   Program utCFIO

   use ESMF_Mod

   use MAPL_BaseMod
   use MAPL_CommsMod

   use ESMF_CfioMod
   use MAPL_CfioMod

   implicit NONE

   type(ESMF_Grid)     :: grid
   type (ESMF_VM)      :: VM
   type(ESMF_DELayout) :: layout

   integer             :: nymd, nhms
   type(ESMF_Time)     :: fTime, dTime
   type(ESMF_TimeInterval)  :: fTimeStep, dTimeStep
   type(ESMF_Clock)    :: fClock, dClock

   type(ESMF_Bundle)   :: fBundle, dBundle

   type(ESMF_CFIO) :: cfio

   integer :: IM_WORLD = 288, JM_WORLD = 181, KM_WORLD = 72   ! globalc72
   integer :: i, j, k, im, jm, km                                      ! local

   character(len=*), parameter :: &
       dirname = '/share/dasilva/fvInput/fvchem/c/aero_clm',       &
     fFilename = dirname // '/gfedv2.aero.eta.200207clm.hdf'
   character(len=255) :: fname ! output file name

   integer :: status, rc, nbits
   logical :: IamRoot
   integer, pointer :: resolution(:), levels(:)

   character(len=*), parameter :: Iam = 'utCFIO'

!                             -----
    
    call test_main()

CONTAINS

    subroutine test_main()

!   Initialize framework
!   --------------------
    call ESMF_Initialize (vm=vm, rc=status)
    _VERIFY(status)

    IamRoot = MAPL_am_I_root()

!   Get the global vm
!   -----------------
    call ESMF_VMGetGlobal(vm, rc=status)
    _VERIFY(status)

!   Create a grid
!   -------------
    grid = MyGridCreate_ ( vm, rc=status )
    _VERIFY(status)

!   Create empty bundles
!   --------------------
    fBundle = ESMF_BundleCreate ( name='Francesca', grid=grid, rc=status )
    _VERIFY(status)
    dBundle = ESMF_BundleCreate ( name='Denise',    grid=grid, rc=status )
    _VERIFY(status)

!   Set the time as the one on the hardwired file name
!   --------------------------------------------------
    call ESMF_CalendarSetDefault ( ESMF_CAL_GREGORIAN, rc=status )
    _VERIFY(STATUS)
    call ESMF_TimeSet( fTime, yy=2002, mm=7, dd=15, h=12, m=0, s=0, rc=status )
    _VERIFY(STATUS)
    call ESMF_TimeIntervalSet( fTimeStep, h=6, m=0, s=0, rc=status )
    _VERIFY(STATUS)
    fClock = ESMF_ClockCreate ( name="Clovis", timeStep=fTimeStep, &
                                startTime=fTime, rc=status )
    _VERIFY(STATUS)

!   Read Bundle from file on a clean slate
!   --------------------------------------
    if ( IamRoot ) print *, 'Reading ' // fFilename
    call ESMF_ioRead  ( fFilename, fTime, fBundle, rc=status, &
                        verbose=.true., force_regrid=.true.   )
    _VERIFY(status)

!   Setup data types need for write
!   -------------------------------
    allocate ( resolution(2), levels(KM_WORLD), stat=status )
    _VERIFY(status)
    resolution = (/ IM_WORLD/2, JM_WORLD/2 /)
    levels     = (/ (k, k=1,KM_WORLD) /)

!   Write the same bundle to a different file, each time with
!    different precision
!   ----------------------------------------------------------
     nbits = 32 ! full precision
     write(fname,"('test.aero.eta.',I2.2)") nbits

     call ESMF_ioCreate ( cfio, fname, fClock, fBundle, fTimeStep, &
                          resolution, levels, 'Bundle Write Test', rc=status )
     _VERIFY(status)

     call ESMF_ioWrite ( cfio, fClock, fBundle, fTimeStep, levels, rc=status, &
                         verbose = .true. ) ! omit nbits
     _VERIFY(status)

     call ESMF_ioDestroy ( cfio )

    do nbits = 16, 8, -2

     write(fname,"('test.aero.eta.',I2.2)") nbits

     call ESMF_ioCreate ( cfio, fname, fClock, fBundle, fTimeStep, &
                          resolution, levels, 'Bundle Write Test', rc=status )
     _VERIFY(status)

     call ESMF_ioWrite ( cfio, fClock, fBundle, fTimeStep, levels, rc=status, &
                         nbits = nbits, verbose = .true. )
     _VERIFY(status)

     call ESMF_ioDestroy ( cfio )

    end do ! precision loop

!   All done
!   --------
    call ESMF_Finalize ( rc=status )
    _VERIFY(STATUS)
    
  end subroutine test_main

!........................................................................

  function MyGridCreate_ ( vm, rc) result(grid)

    type (ESMF_VM),    intent(IN   ) :: VM
    integer, optional, intent(OUT)   :: rc
    type (ESMF_Grid)                 :: grid

! Local vars
    integer                                 :: status
    character(len=ESMF_MAXSTR), parameter   :: IAm='MyGridCreate'

    integer                         :: LM
    integer                         :: L
    integer                         :: NX, NY
    integer, allocatable            :: IMXY(:), JMXY(:)
    character(len=ESMF_MAXSTR)      :: gridname
    real(ESMF_KIND_R8)              :: minCoord(3)
    real(ESMF_KIND_R8)              :: deltaX, deltaY, deltaZ
    real                            :: LON0, LAT0

    real :: pi, d2r

! grid create

    lm = KM_WORLD   ! no. vertical layers
    nx = 2
    ny = 2

     pi  = 4.0 * atan ( 1.0 ) 
    d2r  = pi / 180.
    LON0 = -180  * d2r
    LAT0 = -90.0 * d2r

! Get the IMXY vector
! -------------------
    allocate( imxy(0:nx-1) )  
    call MAPL_GET_LOCAL_DIMS ( IM_WORLD, imxy, nx )

! Get the JMXY vector
! -------------------
    allocate( jmxy(0:ny-1) )  
    call MAPL_GET_LOCAL_DIMS ( JM_WORLD, jmxy, ny )

    deltaX = 2.0*pi/IM_WORLD
    deltaY = pi/(JM_WORLD-1)
    deltaZ = 1.0

    if ( MAPL_Am_I_Root() ) then
       print *, 'nx : imxy = ', nx, ' : ', imxy
       print *, 'ny : jmxy = ', ny, ' : ', jmxy
    endif

! Define South-West Corner of First Grid-Box
! ------------------------------------------
    minCoord(1) = LON0 - deltaX/2 
    minCoord(2) = LAT0 - deltaY/2
    minCoord(3) = deltaZ/2.

    layout = ESMF_DELayoutCreate(vm, deCountList=(/NX, NY/), rc=status)
    _VERIFY(STATUS)

    grid = ESMF_GridCreateHorzLatLonUni(         &
         counts = (/IM_WORLD, JM_WORLD/),        &
         minGlobalCoordPerDim=minCoord(1:2),     &
         deltaPerDim=(/deltaX, deltaY /),        &
         horzStagger=ESMF_Grid_Horz_Stagger_A,   &
         periodic=(/ESMF_TRUE, ESMF_FALSE/),     &
         name='Beatrice', rc=status)
    _VERIFY(STATUS)

    call ESMF_GridAddVertHeight(grid,            &
         delta=(/(deltaZ, L=1,LM) /),            &
         rc=status)
    _VERIFY(STATUS)

    call ESMF_GridDistribute(grid,               &
         deLayout=layout,                        &
         countsPerDEDim1=imxy,                   &
         countsPerDEDim2=jmxy,                   &
         rc=status)
    _VERIFY(STATUS)

    deallocate(imxy)
    deallocate(jmxy)

    _RETURN(STATUS)

  end function MyGridCreate_

end Program utCFIO