New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 13727 for NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS – NEMO

Ignore:
Timestamp:
2020-11-05T15:18:53+01:00 (4 years ago)
Author:
andmirek
Message:

Ticket #2462: Upate to trunk rev 13688

Location:
NEMO/branches/2020/dev_12905_xios_restart
Files:
15 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_12905_xios_restart

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
        88 
        99# SETTE 
        10 ^/utils/CI/sette@HEAD         sette 
         10^/utils/CI/sette@13559        sette 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/ddatetoymdhms.h90

    r10068 r13727  
    2121 
    2222      !! * Arguments 
    23       real(wp), INTENT(IN) :: ddate 
     23      real(dp), INTENT(IN) :: ddate 
    2424      INTEGER, INTENT(OUT) :: kyea 
    2525      INTEGER, INTENT(OUT) :: kmon 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/diaobs.F90

    r12489 r13727  
    9494   TYPE(obs_prof), PUBLIC, POINTER, DIMENSION(:) ::   profdataqc   !: Profile data after quality control 
    9595 
    96    CHARACTER(len=6), PUBLIC, DIMENSION(:), ALLOCATABLE ::   cobstypesprof, cobstypessurf   !: Profile & surface obs types 
     96   CHARACTER(len=lca), PUBLIC, DIMENSION(:), ALLOCATABLE ::   cobstypesprof, cobstypessurf   !: Profile & surface obs types 
    9797 
    9898   !!---------------------------------------------------------------------- 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/find_obs_proc.h90

    r10068 r13727  
    4141      ! first and last indoor i- and j-indexes      kldi, klei,   kldj, klej 
    4242      ! exclude any obs in the bottom-left overlap region 
    43       ! also any obs outside to whole region (defined by nlci and nlcj) 
     43      ! also any obs outside to whole region (defined by jpi and jpj) 
    4444      ! I am assuming that kobsp does not need to be the correct processor  
    4545      ! number 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/grt_cir_dis.h90

    r10068 r13727  
    2828      REAL(KIND=wp) :: pc2   !  cos(lat2) * sin(lon2) 
    2929 
     30      REAL(KIND=wp) :: cosdist ! cosine of great circle distance 
     31 
     32      ! Compute cosine of great circle distance, constraining it to be between 
     33      ! -1 and 1 (rounding errors can take it slightly outside this range 
     34      cosdist = MAX( MIN( pa1 * pa2 + pb1 * pb2 + pc1 * pc2, 1.0_wp), -1.0_wp ) 
     35 
    3036      grt_cir_dis = & 
    31          &  ASIN( SQRT( 1.0 - ( pa1 * pa2 + pb1 * pb2 + pc1 * pc2 )**2 ) ) 
     37         &  ASIN( SQRT( 1.0_wp - cosdist**2.0_wp ) ) 
    3238       
    3339   END FUNCTION grt_cir_dis 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/mpp_map.F90

    r10068 r13727  
    1111   !!---------------------------------------------------------------------- 
    1212   USE par_kind, ONLY :   wp            ! Precision variables 
    13    USE par_oce , ONLY :   jpi, jpj      ! Ocean parameters 
    14    USE dom_oce , ONLY :   mig, mjg, nldi, nlei, nldj, nlej, nlci, nlcj, narea   ! Ocean space and time domain variables 
     13   USE par_oce , ONLY :   jpi, jpj, Nis0, Nie0, Njs0, Nje0   ! Ocean parameters 
     14   USE dom_oce , ONLY :   mig, mjg, narea                    ! Ocean space and time domain variables 
    1515#if defined key_mpp_mpi 
    16    USE lib_mpp, ONLY :   mpi_comm_oce   ! MPP library 
     16   USE lib_mpp , ONLY :   mpi_comm_oce   ! MPP library 
    1717#endif 
    1818   USE in_out_manager   ! I/O manager 
     
    6565 
    6666!      ! Setup local grid points 
    67       imppmap(mig(1):mig(nlci),mjg(1):mjg(nlcj)) = narea 
     67      imppmap(mig(1):mig(jpi),mjg(1):mjg(jpj)) = narea 
    6868       
    6969      ! Get global data 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/obs_grid.F90

    r10068 r13727  
    129129            IF ( cdgrid == 'T' ) THEN 
    130130               CALL obs_grd_bruteforce( jpi, jpj, jpiglo, jpjglo, & 
    131                   &                             1, nlci, 1, nlcj,         & 
     131                  &                             1, jpi, 1, jpj,           & 
    132132                  &                             nproc, jpnij,             & 
    133133                  &                             glamt, gphit, tmask,      & 
     
    136136            ELSEIF ( cdgrid == 'U' ) THEN 
    137137               CALL obs_grd_bruteforce( jpi, jpj, jpiglo, jpjglo, & 
    138                   &                             1, nlci, 1, nlcj,         & 
     138                  &                             1, jpi, 1, jpj,           & 
    139139                  &                             nproc, jpnij,             & 
    140140                  &                             glamu, gphiu, umask,      & 
     
    143143            ELSEIF ( cdgrid == 'V' ) THEN 
    144144               CALL obs_grd_bruteforce( jpi, jpj, jpiglo, jpjglo, & 
    145                   &                             1, nlci, 1, nlcj,         & 
     145                  &                             1, jpi, 1, jpj,           & 
    146146                  &                             nproc, jpnij,             & 
    147147                  &                             glamv, gphiv, vmask,      & 
     
    150150            ELSEIF ( cdgrid == 'F' ) THEN 
    151151               CALL obs_grd_bruteforce( jpi, jpj, jpiglo, jpjglo, & 
    152                   &                             1, nlci, 1, nlcj,         & 
     152                  &                             1, jpi, 1, jpj,           & 
    153153                  &                             nproc, jpnij,             & 
    154154                  &                             glamf, gphif, fmask,      & 
     
    279279         zmskg(:,:) = -1.e+10 
    280280         ! Add various grids here. 
    281          DO jj = 1, nlcj 
    282             DO ji = 1, nlci 
     281         DO jj = 1, jpj 
     282            DO ji = 1, jpi 
    283283               zlamg(mig(ji),mjg(jj)) = glamt(ji,jj) 
    284284               zphig(mig(ji),mjg(jj)) = gphit(ji,jj) 
     
    684684         & fhistx1, fhistx2, fhisty1, fhisty2 
    685685      REAL(wp) :: histtol 
    686        
     686      CHARACTER(LEN=26) :: clfmt            ! writing format 
     687      INTEGER           :: idg              ! number of digits 
     688  
    687689      IF (ln_grid_search_lookup) THEN 
    688690          
     
    709711 
    710712         IF ( ln_grid_global ) THEN 
    711             WRITE(cfname, FMT="(A,'_',A)") & 
    712                &          TRIM(cn_gridsearchfile), 'global.nc' 
     713            WRITE(cfname, FMT="(A,'_',A)") TRIM(cn_gridsearchfile), 'global.nc' 
    713714         ELSE 
    714             WRITE(cfname, FMT="(A,'_',I4.4,'of',I4.4,'by',I4.4,'.nc')") & 
    715                &          TRIM(cn_gridsearchfile), nproc, jpni, jpnj 
     715            idg = MAX( INT(LOG10(REAL(jpnij,wp))) + 1, 4 )        ! how many digits to we need to write? min=4, max=9 
     716            ! define the following format: "(a,a,ix.x,a,ix.x,a,ix.x,a)" 
     717            WRITE(clfmt, "('(a,a,i', i1, '.', i1',a,i', i1, '.', i1',a,i', i1, '.', i1',a)')") idg, idg, idg, idg, idg, idg 
     718            WRITE(cfname,      clfmt     ) TRIM(cn_gridsearchfile),'_', nproc,'of', jpni,'by', jpnj,'.nc' 
    716719         ENDIF 
    717720 
     
    816819             
    817820            CALL obs_grd_bruteforce( jpi, jpj, jpiglo, jpjglo,  & 
    818                &                     1, nlci, 1, nlcj,          & 
     821               &                     1, jpi, 1, jpj,            & 
    819822               &                     nproc, jpnij,              & 
    820823               &                     glamt, gphit, tmask,       & 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/obs_oper.F90

    r12377 r13727  
    189189         ! Initialize daily mean for first timestep of the day 
    190190         IF ( idayend == 1 .OR. kt == 0 ) THEN 
    191             DO_3D_11_11( 1, jpk ) 
     191            DO_3D( 1, 1, 1, 1, 1, jpk ) 
    192192               prodatqc%vdmean(ji,jj,jk,1) = 0.0 
    193193               prodatqc%vdmean(ji,jj,jk,2) = 0.0 
     
    195195         ENDIF 
    196196 
    197          DO_3D_11_11( 1, jpk ) 
     197         DO_3D( 1, 1, 1, 1, 1, jpk ) 
    198198            ! Increment field 1 for computing daily mean 
    199199            prodatqc%vdmean(ji,jj,jk,1) = prodatqc%vdmean(ji,jj,jk,1) & 
     
    209209            IF (lwp) WRITE(numout,*) 'Calculating prodatqc%vdmean on time-step: ',kt 
    210210            CALL FLUSH(numout) 
    211             DO_3D_11_11( 1, jpk ) 
     211            DO_3D( 1, 1, 1, 1, 1, jpk ) 
    212212               prodatqc%vdmean(ji,jj,jk,1) = prodatqc%vdmean(ji,jj,jk,1) & 
    213213                  &                        * zdaystp 
     
    750750         ! Initialize night-time mean for first timestep of the day 
    751751         IF ( idayend == 1 .OR. kt == 0 ) THEN 
    752             DO_2D_11_11 
     752            DO_2D( 1, 1, 1, 1 ) 
    753753               surfdataqc%vdmean(ji,jj) = 0.0 
    754754               zmeanday(ji,jj) = 0.0 
     
    761761         imask_night(:,:) = INT( zouttmp(:,:) ) 
    762762 
    763          DO_2D_11_11 
     763         DO_2D( 1, 1, 1, 1 ) 
    764764            ! Increment the temperature field for computing night mean and counter 
    765765            surfdataqc%vdmean(ji,jj) = surfdataqc%vdmean(ji,jj)  & 
     
    773773         IF ( idayend == 0 ) THEN 
    774774            IF (lwp) WRITE(numout,*) 'Calculating surfdataqc%vdmean on time-step: ',kt 
    775             DO_2D_11_11 
     775            DO_2D( 1, 1, 1, 1 ) 
    776776               ! Test if "no night" point 
    777777               IF ( icount_night(ji,jj) > 0 ) THEN 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/obs_read_altbias.F90

    r12377 r13727  
    125125         ! Get the Alt bias data 
    126126          
    127          CALL iom_get( numaltbias, jpdom_data, 'altbias', z_altbias(:,:), 1 ) 
     127         CALL iom_get( numaltbias, jpdom_global, 'altbias', z_altbias(:,:) ) 
    128128          
    129129         ! Close the file 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/obs_read_prof.F90

    r10068 r13727  
    140140         & zphi, & 
    141141         & zlam 
    142       REAL(wp), DIMENSION(:), ALLOCATABLE :: & 
     142      REAL(dp), DIMENSION(:), ALLOCATABLE :: & 
    143143         & zdat 
    144       REAL(wp), DIMENSION(knumfiles) :: & 
     144      REAL(dp), DIMENSION(knumfiles) :: & 
    145145         & djulini, & 
    146146         & djulend 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/obs_read_surf.F90

    r10069 r13727  
    112112         & zphi, & 
    113113         & zlam 
    114       REAL(wp), DIMENSION(:), ALLOCATABLE :: & 
     114      REAL(dp), DIMENSION(:), ALLOCATABLE :: & 
    115115         & zdat 
    116       REAL(wp), DIMENSION(knumfiles) :: & 
     116      REAL(dp), DIMENSION(knumfiles) :: & 
    117117         & djulini, & 
    118118         & djulend 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/obs_readmdt.F90

    r12377 r13727  
    9090      CALL iom_open( mdtname, nummdt )       ! Open the file 
    9191      !                                      ! Get the MDT data 
    92       CALL iom_get ( nummdt, jpdom_data, 'sossheig', z_mdt(:,:), 1 ) 
     92      CALL iom_get ( nummdt, jpdom_global, 'sossheig', z_mdt(:,:) ) 
    9393      CALL iom_close(nummdt)                 ! Close the file 
    9494       
     
    215215      zeta2 = 0.0 
    216216 
    217       DO_2D_11_11 
     217      DO_2D( 1, 1, 1, 1 ) 
    218218       zdxdy = e1e2t(ji,jj) * zpromsk(ji,jj) 
    219219       zarea = zarea + zdxdy 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/obs_sstbias.F90

    r12377 r13727  
    139139               cl_bias_files(jtype) ) 
    140140            ! Get the SST bias data 
    141             CALL iom_get( numsstbias, jpdom_data, 'tn', z_sstbias_2d(:,:), 1 ) 
     141            CALL iom_get( numsstbias, jpdom_global, 'tn', z_sstbias_2d(:,:), 1 ) 
    142142            z_sstbias(:,:,jtype) = z_sstbias_2d(:,:)        
    143143            ! Close the file 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/obs_write.F90

    r12377 r13727  
    8686      CHARACTER(LEN=40) :: clfname 
    8787      CHARACTER(LEN=10) :: clfiletype 
     88      CHARACTER(LEN=12) :: clfmt            ! writing format 
     89      INTEGER :: idg                        ! number of digits 
    8890      INTEGER :: ilevel 
    8991      INTEGER :: jvar 
     
    181183      fbdata%caddname(1)   = 'Hx' 
    182184 
    183       WRITE(clfname, FMT="(A,'_fdbk_',I4.4,'.nc')") TRIM(clfiletype), nproc 
     185      idg = MAX( INT(LOG10(REAL(jpnij,wp))) + 1, 4 )            ! how many digits to we need to write? min=4, max=9 
     186      WRITE(clfmt, "('(a,a,i', i1, '.', i1, ',a)')") idg, idg   ! '(a,a,ix.x,a)' 
     187      WRITE(clfname,clfmt) TRIM(clfiletype), '_fdbk_', nproc, '.nc' 
    184188 
    185189      IF(lwp) THEN 
     
    326330      CHARACTER(LEN=10) :: clfiletype 
    327331      CHARACTER(LEN=12), PARAMETER :: cpname = 'obs_wri_surf' 
     332      CHARACTER(LEN=12) :: clfmt           ! writing format 
     333      INTEGER :: idg                       ! number of digits 
    328334      INTEGER :: jo 
    329335      INTEGER :: ja 
     
    453459      fbdata%caddname(1)   = 'Hx' 
    454460 
    455       WRITE(clfname, FMT="(A,'_fdbk_',I4.4,'.nc')") TRIM(clfiletype), nproc 
     461      idg = MAX( INT(LOG10(REAL(jpnij,wp))) + 1, 4 )            ! how many digits to we need to write? min=4, max=9 
     462      WRITE(clfmt, "('(a,a,i', i1, '.', i1, ',a)')") idg, idg   ! '(a,a,ix.x,a)' 
     463      WRITE(clfname,clfmt) TRIM(clfiletype), '_fdbk_', nproc, '.nc' 
    456464 
    457465      IF(lwp) THEN 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/OBS/obsinter_z1d.h90

    r10068 r13727  
    6262         z1dm = ( pdep(kkco(jdep)) - pobsdep(jdep)      ) 
    6363         z1dp = ( pobsdep(jdep)    - pdep(kkco(jdep)-1) ) 
    64          IF ( pobsmask(kkco(jdep)) == 0.0_wp ) z1dp = 0.0_wp 
     64          
     65         ! If kkco(jdep) is masked then set pobs(jdep) to the lowest value located above bathymetry 
     66         IF ( pobsmask(kkco(jdep)) == 0.0_wp ) THEN 
     67            pobs(jdep) = pobsk(kkco(jdep)-1) 
     68         ELSE 
     69            zsum = z1dm + z1dp 
    6570 
    66          zsum = z1dm + z1dp 
    67           
    68          IF ( k1dint == 0 ) THEN 
     71            IF ( k1dint == 0 ) THEN 
    6972 
    70             !----------------------------------------------------------------- 
    71             !  Linear interpolation 
    72             !----------------------------------------------------------------- 
    73             pobs(jdep) = (   z1dm * pobsk(kkco(jdep)-1) & 
    74                &           + z1dp * pobsk(kkco(jdep)  ) ) / zsum 
     73               !----------------------------------------------------------------- 
     74               !  Linear interpolation 
     75               !----------------------------------------------------------------- 
     76               pobs(jdep) = (   z1dm * pobsk(kkco(jdep)-1) & 
     77                  &           + z1dp * pobsk(kkco(jdep)  ) ) / zsum 
    7578 
    76          ELSEIF ( k1dint == 1 ) THEN 
     79            ELSEIF ( k1dint == 1 ) THEN 
    7780 
    78             !----------------------------------------------------------------- 
    79             ! Cubic spline interpolation 
    80             !----------------------------------------------------------------- 
    81             zsum2 = zsum * zsum 
    82             pobs(jdep)  = (  z1dm                             * pobsk (kkco(jdep)-1) & 
    83                &           + z1dp                             * pobsk (kkco(jdep)  ) & 
    84                &           + ( z1dm * ( z1dm * z1dm - zsum2 ) * pobs2k(kkco(jdep)-1) & 
    85                &           +   z1dp * ( z1dp * z1dp - zsum2 ) * pobs2k(kkco(jdep)  ) & 
    86                &             ) / 6.0_wp                                              & 
    87                &          ) / zsum 
     81               !----------------------------------------------------------------- 
     82               ! Cubic spline interpolation 
     83               !----------------------------------------------------------------- 
     84               zsum2 = zsum * zsum 
     85               pobs(jdep)  = (  z1dm                             * pobsk (kkco(jdep)-1) & 
     86                  &           + z1dp                             * pobsk (kkco(jdep)  ) & 
     87                  &           + ( z1dm * ( z1dm * z1dm - zsum2 ) * pobs2k(kkco(jdep)-1) & 
     88                  &           +   z1dp * ( z1dp * z1dp - zsum2 ) * pobs2k(kkco(jdep)  ) & 
     89                  &             ) / 6.0_wp                                              & 
     90                  &          ) / zsum 
    8891 
     92            ENDIF 
    8993         ENDIF 
    9094      END DO 
Note: See TracChangeset for help on using the changeset viewer.