ESMF_CFIOSdfFileCreate Subroutine

public subroutine ESMF_CFIOSdfFileCreate(cfio, rc, expid)

ESMF_CFIOSdfFileCreate – Create a CFIO output file with meta data

Arguments

Type IntentOptional Attributes Name
type(ESMF_CFIO), intent(inout) :: cfio

a CFIO object

integer, intent(out), optional :: rc

Error return code: 0 all is well -1 Time increment is 0 -2 allocate memory error -3 Num of int/char/real elements and Cnt don’t match -12 error determining default precision -18 incorrect time increment -30 can’t open file -31 error from NF90_DEF_DIM -32 error from NF90_DEF_VAR (dimension variable) -33 error from NF90_PUT_ATT (dimension attribute) -34 error from NF90_DEF_VAR (variable) -35 error from NF90_PUT_ATT (variable attribute) -36 error from NF90_PUT_ATT (global attribute) -37 error from NF90_ENDDEF -38 error from NF90_VAR_PUT (dimension variable) -39 Num of real var elements and Cnt differ -55 error from NF90_REDEF (enter define mode) -56 error from NF90_ENDDEF (exit define mode)

character(len=*), intent(in), optional :: expid

Experiment ID


Calls

proc~~esmf_cfiosdffilecreate~~CallsGraph proc~esmf_cfiosdffilecreate ESMF_CFIOSdfFileCreate nf90_create nf90_create proc~esmf_cfiosdffilecreate->nf90_create nf90_def_dim nf90_def_dim proc~esmf_cfiosdffilecreate->nf90_def_dim nf90_def_var nf90_def_var proc~esmf_cfiosdffilecreate->nf90_def_var nf90_def_var_chunking nf90_def_var_chunking proc~esmf_cfiosdffilecreate->nf90_def_var_chunking nf90_def_var_deflate nf90_def_var_deflate proc~esmf_cfiosdffilecreate->nf90_def_var_deflate nf90_enddef nf90_enddef proc~esmf_cfiosdffilecreate->nf90_enddef nf90_put_att nf90_put_att proc~esmf_cfiosdffilecreate->nf90_put_att nf90_put_var nf90_put_var proc~esmf_cfiosdffilecreate->nf90_put_var proc~cfio_parseinttime CFIO_parseIntTime proc~esmf_cfiosdffilecreate->proc~cfio_parseinttime proc~cfio_putcharatt CFIO_PutCharAtt proc~esmf_cfiosdffilecreate->proc~cfio_putcharatt proc~cfio_putintatt CFIO_PutIntAtt proc~esmf_cfiosdffilecreate->proc~cfio_putintatt proc~cfio_putrealatt CFIO_PutRealAtt proc~esmf_cfiosdffilecreate->proc~cfio_putrealatt proc~err err proc~esmf_cfiosdffilecreate->proc~err proc~esmf_cfioget ESMF_CFIOGet proc~esmf_cfiosdffilecreate->proc~esmf_cfioget proc~esmf_cfioset ESMF_CFIOSet proc~esmf_cfiosdffilecreate->proc~esmf_cfioset proc~getlist getList proc~esmf_cfiosdffilecreate->proc~getlist proc~getmaxlencnt getMaxLenCnt proc~esmf_cfiosdffilecreate->proc~getmaxlencnt proc~strtemplate_ strTemplate_ proc~esmf_cfiosdffilecreate->proc~strtemplate_ proc~cfio_putcharatt->nf90_enddef proc~cfio_putcharatt->nf90_put_att proc~cfio_putcharatt->proc~err nf90_redef nf90_redef proc~cfio_putcharatt->nf90_redef proc~cfio_putintatt->nf90_enddef proc~cfio_putintatt->nf90_put_att proc~cfio_putintatt->proc~err proc~cfio_putintatt->nf90_redef proc~cfio_putrealatt->nf90_enddef proc~cfio_putrealatt->nf90_put_att proc~cfio_putrealatt->proc~err proc~cfio_putrealatt->nf90_redef proc~esmf_cfioget->proc~err proc~esmf_cfioset->proc~err proc~addlist addList proc~esmf_cfioset->proc~addlist proc~strtoint strToInt proc~esmf_cfioset->proc~strtoint proc~getlist->proc~getmaxlencnt proc~gx_ GX_ proc~strtemplate_->proc~gx_

Called by

proc~~esmf_cfiosdffilecreate~~CalledByGraph proc~esmf_cfiosdffilecreate ESMF_CFIOSdfFileCreate proc~esmf_cfiofilecreate ESMF_CFIOFileCreate proc~esmf_cfiofilecreate->proc~esmf_cfiosdffilecreate proc~mapl_cfiocreatewrite MAPL_CFIOCreatewrite proc~mapl_cfiocreatewrite->proc~esmf_cfiofilecreate program~test~10 test program~test~10->proc~esmf_cfiofilecreate program~test~11 test program~test~11->proc~esmf_cfiofilecreate program~test~12 test program~test~12->proc~esmf_cfiofilecreate program~test~13 test program~test~13->proc~esmf_cfiofilecreate program~test~14 test program~test~14->proc~esmf_cfiofilecreate program~test~3 test program~test~3->proc~esmf_cfiofilecreate program~test~5 test program~test~5->proc~esmf_cfiofilecreate program~test~7 test program~test~7->proc~esmf_cfiofilecreate program~test~8 test program~test~8->proc~esmf_cfiofilecreate program~test~9 test program~test~9->proc~esmf_cfiofilecreate

Source Code

      subroutine ESMF_CFIOSdfFileCreate (cfio, rc, expid)
!
! !INPUT PARAMETERS:
!
      type(ESMF_CFIO), intent(inout) :: cfio       !! a CFIO object
      character(len=*), intent(in), OPTIONAL  :: expid    !! Experiment ID
!
! !OUTPUT PARAMETERS:
!
      integer, intent(out), OPTIONAL :: rc      !! Error return code:
                      !! 0   all is well
                      !! -1 Time increment is 0
                      !! -2  allocate memory error
                      !! -3  Num of int/char/real elements and Cnt don't match
                      !! -12  error determining default precision
                      !! -18 incorrect time increment
                      !! -30 can't open file
                      !! -31 error from NF90_DEF_DIM
                      !! -32 error from NF90_DEF_VAR (dimension variable)
                      !! -33 error from NF90_PUT_ATT (dimension attribute)
                      !! -34 error from NF90_DEF_VAR (variable)
                      !! -35  error from NF90_PUT_ATT (variable attribute)
                      !! -36  error from NF90_PUT_ATT (global attribute)
                      !! -37  error from NF90_ENDDEF
                      !! -38  error from NF90_VAR_PUT (dimension variable)
                      !! -39 Num of real var elements and Cnt differ
                      !! -55  error from NF90_REDEF (enter define mode)
                      !! -56  error from NF90_ENDDEF (exit define mode)
!
!------------------------------------------------------------------------------
       integer :: i, rtcode
       !integer :: maxLen
       character(len=MLEN) :: fNameTmp     ! file name
       integer :: date, begTime
       character(len=MLEN) :: fName

       call ESMF_CFIOGet(cfio, date=date, begTime=begTime, fName=fName, rc=rtcode)
       if (rtcode .ne. 0) print *, "Problems in ESMF_CFIOGet"
!      checking file name template
       if (present(expid)) then
          call ESMF_CFIOSet(cfio, expid=expid)
          call strTemplate_(fNameTmp,fName,xid=expid,nymd=date, &
                            nhms=begTime, stat=rtcode)
       else
          call strTemplate_(fNameTmp,fName,nymd=date, nhms=begTime, stat=rtcode)
       end if

       if (trim(fNameTmp) .ne. trim(fName)) then
          call ESMF_CFIOSet(cfio, fNameTmplt=fName, fName=fNameTmp)
       end if

       call CFIO_Create_(cfio, rtcode)
       if (err("Error form CFIO_Create_",rtcode,rtcode) .lt. 0) then
          if ( present(rc) ) rc = rtcode
          return
       end if

!      put global attributes
       call CFIO_PutCharAtt(cfio%fid, 'History', len(trim(cfio%history)),    &
                             cfio%history, rtcode )
       if (err("can't write History",rtcode,rtcode) .lt. 0) then
          if ( present(rc) ) rc = rtcode
          return
       end if

       call CFIO_PutCharAtt(cfio%fid, 'Source', len(trim(cfio%source)),      &
                             cfio%source, rtcode )
       if (err("can't write Source",rtcode,rtcode) .lt. 0) then
          if ( present(rc) ) rc = rtcode
          return
       end if

       call CFIO_PutCharAtt(cfio%fid, 'Title', len(trim(cfio%title)),        &
                             cfio%title, rtcode )
       if (err("can't write Title",rtcode,rtcode) .lt. 0) then
          if ( present(rc) ) rc = rtcode
          return
       end if

       call CFIO_PutCharAtt(cfio%fid, 'Contact', len(trim(cfio%contact)),    &
                             cfio%contact, rtcode )
       if (err("can't write Contact",rtcode,rtcode) .lt. 0) then
          if ( present(rc) ) rc = rtcode
          return
       end if

       call CFIO_PutCharAtt(cfio%fid,'Conventions',len(trim(cfio%convention))&
                             ,cfio%convention, rtcode )
       if (err("can't write Conventions",rtcode,rtcode) .lt. 0) then
          if ( present(rc) ) rc = rtcode
          return
       end if

       call CFIO_PutCharAtt(cfio%fid,'Institution',                          &
                            len(trim(cfio%institution)),                     &
                            cfio%institution, rtcode )
       if (err("can't write Institution",rtcode,rtcode) .lt. 0) then
          if ( present(rc) ) rc = rtcode
          return
       end if

       call CFIO_PutCharAtt(cfio%fid,'References',len(trim(cfio%references)),&
                             cfio%references, rtcode )
       if (err("can't write References",rtcode,rtcode) .lt. 0) then
          if ( present(rc) ) rc = rtcode
          return
       end if

       call CFIO_PutCharAtt(cfio%fid,'Comment',len(trim(cfio%comment)),      &
                             cfio%comment, rtcode )
       if (err("can't write Comment",rtcode,rtcode) .lt. 0) then
          if ( present(rc) ) rc = rtcode
          return
       end if


!      get integer attributes from iList
       if ( associated(cfio%iList) ) then
!@@          call getMaxLenCnt(maxLen, cfio%nAttInt, iList=cfio%iList)
!@@          allocate(cfio%attIntNames(cfio%nAttInt),                           &
!@@                   cfio%attIntCnts(cfio%nAttInt),                            &
!@@                   cfio%attInts(cfio%nAttInt,maxLen), stat=rtcode)
!@@          if (err("can't allocate mem: attIntCnts",rtcode,-2) .lt. 0) then
!@@             if ( present(rc) ) rc = rtcode
!@@             return
!@@          end if

          call getList(iList=cfio%iList, intAttNames=cfio%attIntNames,       &
                       intAttCnts=cfio%attIntCnts, intAtts=cfio%attInts )
       end if

!      write user defined integer attributes
       if ( cfio%nAttInt .gt. 0 ) then
          do i = 1, cfio%nAttInt
             if ( cfio%attIntCnts(i) .gt. size(cfio%attInts(i,:)) )  then
                rtcode=err("FileCreate: Num of int elements and Cnt differ"  &
                            ,-3,-3)
                if ( present(rc) ) rc = rtcode
                return
             end if

             call CFIO_PutIntAtt(cfio%fid, cfio%attIntNames(i),              &
                                 cfio%attIntCnts(i), cfio%attInts(i,:),      &
                                 cfio%prec, rtcode )
             if (err("error in CFIO_PutIntAtt",rtcode,rtcode) .lt. 0) then
                if ( present(rc) ) rc = rtcode
                return
             end if

          end do
       end if

!      get real attributes from rList
       if ( associated(cfio%rList) ) then
!@@          call getMaxLenCnt(maxLen, cfio%nAttReal, rList=cfio%rList)
!@@          allocate(cfio%attRealNames(cfio%nAttReal),                       &
!@@                   cfio%attRealCnts(cfio%nAttReal),                        &
!@@                   cfio%attReals(cfio%nAttReal,maxLen), stat=rtcode)
!@@          if (err("can't allocate mem: attRealNames",rtcode,-2) .lt. 0) then
!@@             if ( present(rc) ) rc = rtcode
!@@             return
!@@          end if

          call getList(rList=cfio%rList, realAttNames=cfio%attRealNames,   &
                       realAttCnts=cfio%attRealCnts, realAtts=cfio%attReals )
          do i = 1, cfio%nAttReal
          end do
       end if

!      write user defined real attributes
       if ( cfio%nAttReal .gt. 0 ) then
          do i = 1, cfio%nAttReal
             if ( cfio%attRealCnts(i) .gt. size(cfio%attReals(i,:)) )  then
                rtcode=err("FileCreate: Num of real elements and Cnt differ" &
                            ,-3,-3)
                if ( present(rc) ) rc = rtcode
                return
             end if
             call CFIO_PutRealAtt(cfio%fid, cfio%attRealNames(i),            &
                                 cfio%attRealCnts(i),                        &
                                 cfio%attReals(i,1:cfio%attRealCnts(i)),     &
                                 cfio%prec, rtcode )
             if (err("error in CFIO_PutRealAtt",rtcode,rtcode) .lt. 0) then
                if ( present(rc) ) rc = rtcode
                return
             end if
          end do
       end if

!      get char attributes from cList
       if ( associated(cfio%cList) ) then
!@@          call getMaxLenCnt(maxLen, cfio%nAttChar, cList=cfio%cList)
!@@          allocate(cfio%attCharNames(cfio%nAttChar),                      &
!@@                   cfio%attCharCnts(cfio%nAttChar),                       &
!@@                   cfio%attChars(cfio%nAttChar), stat=rtcode)
!@@          if (err("can't allocate mem: attCharNames",rtcode,-2) .lt. 0) then
!@@             if ( present(rc) ) rc = rtcode
!@@             return
!@@          end if
          call getList(cList=cfio%cList, charAttNames=cfio%attCharNames,  &
                       charAttCnts=cfio%attCharCnts, charAtts=cfio%attChars )
       end if

!      write user defined char attributes
       if ( cfio%nAttChar .gt. 0 ) then
          do i = 1, cfio%nAttChar
             call CFIO_PutCharAtt(cfio%fid, cfio%attCharNames(i),       &
                                 cfio%attCharCnts(i), cfio%attChars(i), &
                                 rtcode )
             if (err("error in CFIO_PutCharAtt",rtcode,rtcode) .lt. 0) then
                if ( present(rc) ) rc = rtcode
                return
             end if
          end do
       end if

       cfio%isOpen = .true.

       rtcode = 0
       if ( present(rc) ) rc = rtcode

      end subroutine ESMF_CFIOSdfFileCreate