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 12182 for NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/IOM/iom.F90 – NEMO

Ignore:
Timestamp:
2019-12-11T12:38:43+01:00 (4 years ago)
Author:
davestorkey
Message:

2019/dev_r11943_MERGE_2019: Merge in dev_ASINTER-01-05_merge.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/IOM/iom.F90

    r12150 r12182  
    2929   USE lib_mpp           ! MPP library 
    3030#if defined key_iomput 
    31    USE sbc_oce  , ONLY :   nn_fsbc         ! ocean space and time domain 
     31   USE sbc_oce  , ONLY :   nn_fsbc, ght_abl, ghw_abl, e3t_abl, e3w_abl, jpka, jpkam1 
    3232   USE icb_oce  , ONLY :   nclasses, class_num       !  !: iceberg classes 
    3333#if defined key_si3 
     
    111111      ! 
    112112      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zt_bnds, zw_bnds 
     113      REAL(wp), DIMENSION(2,jpkam1)         :: za_bnds   ! ABL vertical boundaries 
    113114      LOGICAL ::   ll_tmppatch = .TRUE.    !: seb: patch before we remove periodicity 
    114115      INTEGER ::   nldi_save, nlei_save    !:      and close boundaries in output files 
     
    194195      ! vertical grid definition 
    195196      IF(.NOT.llrst_context) THEN 
    196           CALL iom_set_axis_attr( "deptht",  paxis = gdept_1d ) 
    197           CALL iom_set_axis_attr( "depthu",  paxis = gdept_1d ) 
    198           CALL iom_set_axis_attr( "depthv",  paxis = gdept_1d ) 
    199           CALL iom_set_axis_attr( "depthw",  paxis = gdepw_1d ) 
    200  
     197          CALL iom_set_axis_attr(  "deptht", paxis = gdept_1d ) 
     198          CALL iom_set_axis_attr(  "depthu", paxis = gdept_1d ) 
     199          CALL iom_set_axis_attr(  "depthv", paxis = gdept_1d ) 
     200          CALL iom_set_axis_attr(  "depthw", paxis = gdepw_1d ) 
     201 
     202          ! ABL 
     203          IF( .NOT. ALLOCATED(ght_abl) ) THEN   ! force definition for xml files (xios)  
     204             ALLOCATE( ght_abl(jpka), ghw_abl(jpka), e3t_abl(jpka), e3w_abl(jpka) )   ! default allocation needed by iom 
     205             ght_abl(:) = -1._wp   ;   ghw_abl(:) = -1._wp 
     206             e3t_abl(:) = -1._wp   ;   e3w_abl(:) = -1._wp 
     207          ENDIF 
     208          CALL iom_set_axis_attr( "ght_abl", ght_abl(2:jpka) ) 
     209          CALL iom_set_axis_attr( "ghw_abl", ghw_abl(2:jpka) ) 
     210           
    201211          ! Add vertical grid bounds 
    202212          jkmin = MIN(2,jpk)  ! in case jpk=1 (i.e. sas2D) 
     
    207217          zw_bnds(2,1:jpkm1  ) = gdepw_1d(jkmin:jpk) 
    208218          zw_bnds(2,jpk:     ) = gdepw_1d(jpk) + e3t_1d(jpk) 
    209           CALL iom_set_axis_attr( "deptht", bounds=zw_bnds ) 
    210           CALL iom_set_axis_attr( "depthu", bounds=zw_bnds ) 
    211           CALL iom_set_axis_attr( "depthv", bounds=zw_bnds ) 
    212           CALL iom_set_axis_attr( "depthw", bounds=zt_bnds ) 
     219          CALL iom_set_axis_attr(  "deptht", bounds=zw_bnds ) 
     220          CALL iom_set_axis_attr(  "depthu", bounds=zw_bnds ) 
     221          CALL iom_set_axis_attr(  "depthv", bounds=zw_bnds ) 
     222          CALL iom_set_axis_attr(  "depthw", bounds=zt_bnds ) 
     223 
     224          ! ABL 
     225          za_bnds(1,:) = ghw_abl(1:jpkam1) 
     226          za_bnds(2,:) = ghw_abl(2:jpka  ) 
     227          CALL iom_set_axis_attr( "ght_abl", bounds=za_bnds ) 
     228          za_bnds(1,:) = ght_abl(2:jpka  ) 
     229          za_bnds(2,:) = ght_abl(2:jpka  ) + e3w_abl(2:jpka) 
     230          CALL iom_set_axis_attr( "ghw_abl", bounds=za_bnds ) 
     231 
    213232          CALL iom_set_axis_attr( "nfloat", (/ (REAL(ji,wp), ji=1,jpnfl) /) ) 
    214233# if defined key_si3 
     
    682701      clname   = trim(cdname) 
    683702      IF ( .NOT. Agrif_Root() .AND. .NOT. lliof ) THEN 
    684 !FUS         iln    = INDEX(clname,'/')  
    685          iln    = INDEX(clname,'/',BACK=.true.)  ! FUS: to insert the nest index at the right location within the string, the last / has to be found (search from the right to left) 
     703         iln    = INDEX(clname,'/')  
    686704         cltmpn = clname(1:iln) 
    687705         clname = clname(iln+1:LEN_TRIM(clname)) 
     
    11281146            WRITE(cldmspc , fmt='(i1)') idmspc 
    11291147            ! 
    1130             IF(     idmspc <  irankpv ) THEN  
    1131                CALL ctl_stop( TRIM(clinfo), 'The file has only '//cldmspc//' spatial dimension',   & 
    1132                   &                         'it is impossible to read a '//clrankpv//'D array from this file...' ) 
    1133             ELSEIF( idmspc == irankpv ) THEN 
     1148            !!GS: we consider 2D data as 3D data with vertical dim size = 1 
     1149            !IF(     idmspc <  irankpv ) THEN  
     1150            !   CALL ctl_stop( TRIM(clinfo), 'The file has only '//cldmspc//' spatial dimension',   & 
     1151            !      &                         'it is impossible to read a '//clrankpv//'D array from this file...' ) 
     1152            !ELSEIF( idmspc == irankpv ) THEN 
     1153            IF( idmspc == irankpv ) THEN 
    11341154               IF( PRESENT(pv_r1d) .AND. idom /= jpdom_unknown )   & 
    11351155                  &   CALL ctl_stop( TRIM(clinfo), 'case not coded...You must use jpdom_unknown' ) 
     
    19291949      ! 
    19301950      INTEGER :: ji, jj, jn, ni, nj 
    1931       INTEGER :: icnr, jcnr                                    ! Offset such that the vertex coordinate (i+icnr,j+jcnr) 
    1932       !                                                        ! represents the bottom-left corner of cell (i,j) 
     1951      INTEGER :: icnr, jcnr                             ! Offset such that the vertex coordinate (i+icnr,j+jcnr) 
     1952      !                                                 ! represents the bottom-left corner of cell (i,j) 
    19331953      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: z_bnds      ! Lat/lon coordinates of the vertices of cell (i,j) 
    19341954      REAL(wp), ALLOCATABLE, DIMENSION(:,:)     :: z_fld       ! Working array to determine where to rotate cells 
     
    21012121      f_op%timestep = nn_fsbc  ;  f_of%timestep =  0  ; CALL iom_set_field_attr('SBC'             , freq_op=f_op, freq_offset=f_of) 
    21022122      f_op%timestep = nn_fsbc  ;  f_of%timestep =  0  ; CALL iom_set_field_attr('SBC_scalar'      , freq_op=f_op, freq_offset=f_of) 
    2103       f_op%timestep = 1        ;  f_of%timestep =  0  ; CALL iom_set_field_attr('ptrc_T'          , freq_op=f_op, freq_offset=f_of) 
    2104       f_op%timestep = 1        ;  f_of%timestep =  0  ; CALL iom_set_field_attr('diad_T'          , freq_op=f_op, freq_offset=f_of) 
     2123      f_op%timestep = nn_fsbc  ;  f_of%timestep =  0  ; CALL iom_set_field_attr('ABL'             , freq_op=f_op, freq_offset=f_of) 
    21052124 
    21062125      ! output file names (attribut: name) 
     
    22272246      CHARACTER(LEN=20)  ::   clfreq 
    22282247      CHARACTER(LEN=20)  ::   cldate 
    2229       CHARACTER(LEN=256) ::   cltmpn                 !FUS needed for correct path with AGRIF 
    2230       INTEGER            ::   iln                    !FUS needed for correct path with AGRIF 
    22312248      INTEGER            ::   idx 
    22322249      INTEGER            ::   jn 
     
    23112328            END DO 
    23122329            ! 
    2313 !FUS            IF( jn == 1 .AND. TRIM(Agrif_CFixed()) /= '0' )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname) 
    2314 !FUS see comment line 700  
    2315             IF( jn == 1 .AND. TRIM(Agrif_CFixed()) /= '0' ) THEN 
    2316              iln    = INDEX(clname,'/',BACK=.true.) 
    2317              cltmpn = clname(1:iln) 
    2318              clname = clname(iln+1:LEN_TRIM(clname)) 
    2319              clname = TRIM(cltmpn)//TRIM(Agrif_CFixed())//'_'//TRIM(clname) 
    2320             ENDIF 
    2321 !FUS  
     2330            IF( jn == 1 .AND. TRIM(Agrif_CFixed()) /= '0' )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname) 
    23222331            IF( jn == 1 )   CALL iom_set_file_attr( cdid, name        = clname ) 
    23232332            IF( jn == 2 )   CALL iom_set_file_attr( cdid, name_suffix = clname ) 
Note: See TracChangeset for help on using the changeset viewer.