m_read_icemod.f90 2.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117
  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_read_icemod
  10. ! Francois Massonnet, UCL, 2013
  11. ! Reads data from icemod file (instead of classically restart files).
  12. ! This is required when doing data assimilation of OSISAF sea ice drift
  13. ! computed over several hours/days. Indeed, the restart only gives a
  14. ! snapshot of the state of the system while the icemod records the time
  15. ! average. The icemod file should have one time slice.
  16. USE NETCDF
  17. use qmpi
  18. CONTAINS
  19. SUBROUTINE read_icemod(fld,k,enslist,cfld,nx,ny)
  20. IMPLICIT NONE
  21. real,dimension(nx,ny),intent(inout):: fld ! output fl
  22. character(len=*), intent(in) :: cfld ! name of fld
  23. integer, intent(in) :: k ! Index to enslist
  24. integer,dimension(:), intent(in) :: enslist! List of existing ensemble members
  25. integer, intent(in) :: nx,ny ! Grid dimension
  26. integer :: iens
  27. integer :: error, ncid,varID
  28. character(len=3) :: cmem
  29. character(len=99) :: cfile
  30. logical :: exf
  31. iens = enslist(k)
  32. write(cmem,'(i3.3)') 100+iens ! iens=1 gives cmem = 101
  33. cfile='icemod_'//cmem//'.nc'
  34. inquire(file=cfile, exist=exf)
  35. if (.not.exf) then
  36. if (master) print *, '(read_icemod): Icemod file '//cfile//' missing!'
  37. call stop_mpi()
  38. end if
  39. error = nf90_open(trim(cfile),nf90_Write,ncid); if (error.ne.nf90_noerr) call handle_err(error, "opening")
  40. error = nf90_inq_varid(ncid, trim(cfld), varID); if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  41. error = nf90_get_var(ncid, varID, fld); if (error.ne.nf90_noerr) call handle_err(error, "getting 2D variable")
  42. END SUBROUTINE read_icemod
  43. subroutine handle_err(status, infomsg)
  44. integer, intent ( in) :: status
  45. character(len = *), intent ( in), optional :: infomsg
  46. if(status /= nf90_noerr) then
  47. if (master) then
  48. if (present(infomsg)) then
  49. print *, 'Error while '//infomsg//' - '//trim(nf90_strerror(status))
  50. else
  51. print *, trim(nf90_strerror(status))
  52. endif ! opt arg
  53. print *,'(io_mod_fld)'
  54. endif ! only master outputs
  55. call stop_mpi()
  56. end if ! check error status
  57. end subroutine handle_err
  58. END MODULE m_read_icemod