m_io_mod_fld.f90 7.8 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249
  1. # 0 "<stdin>"
  2. # 0 "<built-in>"
  3. # 0 "<command-line>"
  4. # 1 "/usr/include/stdc-predef.h" 1 3 4
  5. # 17 "/usr/include/stdc-predef.h" 3 4
  6. # 2 "<command-line>" 2
  7. # 1 "<stdin>"
  8. # 10 "<stdin>"
  9. module m_io_mod_fld
  10. ! Get or put one of the fields of a restart file, specified by
  11. ! ensemble number, field name and type, and vertical level. The
  12. ! time level is currently not used (restart files have only one)
  13. ! but who knows. Grid dimension is also needed, as well as if you
  14. ! want to 'get' or 'put'.
  15. !
  16. ! This replaces the two routines 'm_get_mod_fld.F90' and m_put_mod_fld.F90'.
  17. ! There was so much overlap that it became easier to merge the two. I think.
  18. !
  19. ! (c) July 2009, Christof.KonigBeatty@uclouvain.be
  20. use netcdf
  21. use qmpi
  22. private handle_err
  23. contains
  24. subroutine io_mod_fld(fld,k,enslist,cfld,type,vlevel,tlevel,nx,ny,gorp,rdate_obs)
  25. implicit none
  26. ! In/out
  27. real,dimension(nx,ny),intent(inout):: fld ! output fl
  28. integer, intent(in) :: k ! Index to enslist
  29. integer,dimension(:), intent(in) :: enslist! List of existing ensemble members
  30. character(len=*), intent(in) :: cfld ! name of fld
  31. integer, intent(in) :: type ! which file to use
  32. integer, intent(in) :: vlevel ! vertical level (ignored)
  33. integer, intent(in) :: tlevel ! time level (ignored)
  34. integer, intent(in) :: nx,ny ! Grid dimension
  35. character(len=3), intent(in) :: gorp ! 'get' or 'put' (sorry, couldn't come up with anything better)
  36. real(kind=8), intent(in) :: rdate_obs
  37. ! NetCDF vars
  38. integer :: iens ! Ensemble member to read
  39. character(len=99) :: fcfile, anafile, cfile
  40. integer :: ncid, varID, error
  41. logical :: exfc, exan
  42. ! Other
  43. character(len=3) :: cmem
  44. integer :: zvlevel ! for i/o ocean variable
  45. ! [AD] and ice category as a dimension in SI3 2024
  46. real(kind=8) :: rdate_mod
  47. ! Find iens withing enslist
  48. iens = enslist(k)
  49. ! Create filename dep. on type of variable/parameter requested
  50. write(cmem,'(i3.3)') 100+iens ! iens=1 gives cmem = 101
  51. select case( type )
  52. case(1) ! ice variable [AD] Case with ice category as dimension (considered as "vertical" level here)
  53. fcfile ='forecast_ice_'//cmem//'.nc'
  54. anafile='analysis_ice_'//cmem//'.nc'
  55. if (vlevel>0) then
  56. zvlevel = max(vlevel,1) ! consider 3rd dimension
  57. else
  58. zvlevel = 0 ! No third dimension
  59. endif
  60. case(2) ! ocean variable
  61. fcfile ='forecast_oce_'//cmem//'.nc'
  62. anafile='analysis_oce_'//cmem//'.nc'
  63. zvlevel = max(vlevel,1)
  64. case(3) ! ice namelist parameter
  65. if (master) print *, '(io_mod_fld): ice parameter writing not implemented yet!'
  66. call stop_mpi()
  67. case(4) ! ocean namelist parameter
  68. if (master) print *, '(io_mod_fld): ocean parameter writing not implemented yet!'
  69. call stop_mpi()
  70. case default
  71. if (master) print *, '(io_mod_fld): variable type not understood!'
  72. call stop_mpi()
  73. end select
  74. ! If the fc file exists we turn it into the analysis file (unless that's already there).
  75. inquire(file=fcfile, exist=exfc)
  76. inquire(file=anafile, exist=exan)
  77. if ((.not.exfc).and.(.not.exan)) then ! Neither file is there
  78. if (master) print *, '(io_mod_fld): Restart file '//cmem//' missing!'
  79. call stop_mpi()
  80. elseif (exfc.and.(.not.exan)) then ! fcfile here but no anafile
  81. ! call system('mv '//trim(fcfile)//' '//trim(anafile) ) ! "operational" to save space
  82. call system('cp '//trim(fcfile)//' '//trim(anafile) ) ! for debugging
  83. end if
  84. ! Decide on which file to use
  85. if (gorp=='get') cfile=fcfile
  86. if (gorp=='put') cfile=anafile
  87. ! ckb prefers only one file at the time, so take care of this special case
  88. inquire(file=fcfile, exist=exfc)
  89. if (.not.exfc) cfile=anafile
  90. !!$ !XXX:
  91. !!$ write(*,*) "XXX: "
  92. !!$ write(*,*) "XXX: iens : ", iens
  93. !!$ write(*,*) "XXX: cfld : ", cfld
  94. !!$ write(*,*) "XXX: type : ", type
  95. !!$ write(*,*) "XXX: nx, ny, zvlevel: ", nx, ny, zvlevel
  96. !!$ write(*,*) "XXX: fcfile : ", trim(fcfile)
  97. !!$ write(*,*) "XXX: anafile : ", trim(anafile)
  98. !!$ write(*,*) "XXX: shape(fldIO) : ", shape(fldIO)
  99. !!$ write(*,*) "XXX: "
  100. !!$ !:XXX
  101. ! open the netCDF file
  102. error = nf90_open(trim(cfile),nf90_Write,ncid); if (error.ne.nf90_noerr) call handle_err(error, "opening")
  103. ! Find VarID of cfld
  104. error = nf90_inq_varid(ncid, trim(cfld), varID); if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  105. ! Put/Get
  106. select case( type )
  107. case(3, 4) ! 2D
  108. if (gorp=='get') then
  109. error = nf90_get_var(ncid, varID, fld); if (error.ne.nf90_noerr) call handle_err(error, "getting 2D variable")
  110. elseif (gorp=='put') then
  111. error = nf90_put_var(ncid, varID, fld); if (error.ne.nf90_noerr) call handle_err(error, "putting 2D variable")
  112. else
  113. if (master) print *, "(io_mod_fld): Either 'put' or 'get'!"
  114. call stop_mpi()
  115. endif
  116. case(1) ! 2D ice varibale [AD] with possibility of 3D (ice category as a dimension // vertical dimensioni)
  117. if (zvlevel > 0) then ! 3D ice variables
  118. if (gorp=='get') then
  119. error = nf90_get_var(ncid, varID, fld,start=(/1,1,zvlevel/), count=(/nx,ny,1/))
  120. if (error.ne.nf90_noerr) call handle_err(error, "getting 3D ice variable")
  121. elseif (gorp=='put') then
  122. error = nf90_put_var(ncid, varID, fld,start=(/1,1,zvlevel/), count=(/nx,ny,1/))
  123. if (error.ne.nf90_noerr) call handle_err(error, "putting 3D ice variable")
  124. else
  125. if (master) print *, "(io_mod_fld): Either 'put' or 'get'!"
  126. call stop_mpi()
  127. endif
  128. else ! 2D ice variables
  129. if (gorp=='get') then
  130. error = nf90_get_var(ncid, varID, fld); if (error.ne.nf90_noerr) call handle_err(error, "getting 2D variable")
  131. elseif (gorp=='put') then
  132. error = nf90_put_var(ncid, varID, fld); if (error.ne.nf90_noerr) call handle_err(error, "putting 2D variable")
  133. else
  134. if (master) print *, "(io_mod_fld): Either 'put' or 'get'!"
  135. call stop_mpi()
  136. endif
  137. endif
  138. case(2) ! 3D ocean variable
  139. if (gorp=='get') then
  140. error = nf90_get_var(ncid, varID, fld, start=(/1,1,zvlevel/), count=(/nx,ny,1/))
  141. if (error.ne.nf90_noerr) call handle_err(error, "getting ocean variable")
  142. elseif (gorp=='put') then
  143. error = nf90_put_var(ncid, varID, fld, start=(/1,1,zvlevel/), count=(/nx,ny,1/))
  144. if (error.ne.nf90_noerr) call handle_err(error, "putting ocean variable")
  145. else
  146. if (master) print *, "(io_mod_fld): Either 'put' or 'get'!"
  147. call stop_mpi()
  148. endif
  149. end select
  150. !if (master) PRINT *, " Find VarID of cfld "
  151. error = nf90_inq_varid(ncid, 'time_counter', varID); if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  152. error = nf90_get_var(ncid, varID, rdate_mod); if (error.ne.nf90_noerr) call handle_err(error, "getting ocean variable")
  153. ! Close file
  154. error = nf90_close(ncid); if (error.ne.nf90_noerr) call handle_err(error, "closing")
  155. ! Check date mode and date obs
  156. IF (INT(rdate_mod) .NE. INT(rdate_obs)) THEN
  157. !PRINT *, 'date mod not egal to date obs, stop, (',INT(rdate_mod),' ',INT(rdate_obs),')'
  158. !STOP 1
  159. END IF
  160. end subroutine io_mod_fld
  161. subroutine handle_err(status, infomsg)
  162. integer, intent ( in) :: status
  163. character(len = *), intent ( in), optional :: infomsg
  164. if(status /= nf90_noerr) then
  165. if (master) then
  166. if (present(infomsg)) then
  167. print *, 'Error while '//infomsg//' - '//trim(nf90_strerror(status))
  168. else
  169. print *, trim(nf90_strerror(status))
  170. endif ! opt arg
  171. print *,'(io_mod_fld)'
  172. endif ! only master outputs
  173. call stop_mpi()
  174. end if ! check error status
  175. end subroutine handle_err
  176. end module m_io_mod_fld