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

Ignore:
Timestamp:
2019-12-10T15:44:23+01:00 (4 years ago)
Author:
cetlod
Message:

commit

File:
1 edited

Legend:

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

    r12109 r12154  
    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 trc_oce  , ONLY :   nn_dttrc        !  !: frequency of step on passive tracers 
    3333   USE icb_oce  , ONLY :   nclasses, class_num       !  !: iceberg classes 
     
    113113      ! 
    114114      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zt_bnds, zw_bnds 
     115      REAL(wp), DIMENSION(2,jpkam1)         :: za_bnds   ! ABL vertical boundaries 
    115116      LOGICAL ::   ll_tmppatch = .TRUE.    !: seb: patch before we remove periodicity 
    116117      INTEGER ::   nldi_save, nlei_save    !:      and close boundaries in output files 
     
    200201      ! vertical grid definition 
    201202      IF(.NOT.llrst_context) THEN 
    202           CALL iom_set_axis_attr( "deptht",  paxis = gdept_1d ) 
    203           CALL iom_set_axis_attr( "depthu",  paxis = gdept_1d ) 
    204           CALL iom_set_axis_attr( "depthv",  paxis = gdept_1d ) 
    205           CALL iom_set_axis_attr( "depthw",  paxis = gdepw_1d ) 
    206  
     203          CALL iom_set_axis_attr(  "deptht", paxis = gdept_1d ) 
     204          CALL iom_set_axis_attr(  "depthu", paxis = gdept_1d ) 
     205          CALL iom_set_axis_attr(  "depthv", paxis = gdept_1d ) 
     206          CALL iom_set_axis_attr(  "depthw", paxis = gdepw_1d ) 
     207 
     208          ! ABL 
     209          IF( .NOT. ALLOCATED(ght_abl) ) THEN   ! force definition for xml files (xios)  
     210             ALLOCATE( ght_abl(jpka), ghw_abl(jpka), e3t_abl(jpka), e3w_abl(jpka) )   ! default allocation needed by iom 
     211             ght_abl(:) = -1._wp   ;   ghw_abl(:) = -1._wp 
     212             e3t_abl(:) = -1._wp   ;   e3w_abl(:) = -1._wp 
     213          ENDIF 
     214          CALL iom_set_axis_attr( "ght_abl", ght_abl(2:jpka) ) 
     215          CALL iom_set_axis_attr( "ghw_abl", ghw_abl(2:jpka) ) 
     216           
    207217          ! Add vertical grid bounds 
    208218          jkmin = MIN(2,jpk)  ! in case jpk=1 (i.e. sas2D) 
     
    213223          zw_bnds(2,1:jpkm1  ) = gdepw_1d(jkmin:jpk) 
    214224          zw_bnds(2,jpk:     ) = gdepw_1d(jpk) + e3t_1d(jpk) 
    215           CALL iom_set_axis_attr( "deptht", bounds=zw_bnds ) 
    216           CALL iom_set_axis_attr( "depthu", bounds=zw_bnds ) 
    217           CALL iom_set_axis_attr( "depthv", bounds=zw_bnds ) 
    218           CALL iom_set_axis_attr( "depthw", bounds=zt_bnds ) 
     225          CALL iom_set_axis_attr(  "deptht", bounds=zw_bnds ) 
     226          CALL iom_set_axis_attr(  "depthu", bounds=zw_bnds ) 
     227          CALL iom_set_axis_attr(  "depthv", bounds=zw_bnds ) 
     228          CALL iom_set_axis_attr(  "depthw", bounds=zt_bnds ) 
     229 
     230          ! ABL 
     231          za_bnds(1,:) = ghw_abl(1:jpkam1) 
     232          za_bnds(2,:) = ghw_abl(2:jpka  ) 
     233          CALL iom_set_axis_attr( "ght_abl", bounds=za_bnds ) 
     234          za_bnds(1,:) = ght_abl(2:jpka  ) 
     235          za_bnds(2,:) = ght_abl(2:jpka  ) + e3w_abl(2:jpka) 
     236          CALL iom_set_axis_attr( "ghw_abl", bounds=za_bnds ) 
     237 
    219238          CALL iom_set_axis_attr( "nfloat", (/ (REAL(ji,wp), ji=1,jpnfl) /) ) 
    220239# if defined key_si3 
     
    11471166            WRITE(cldmspc , fmt='(i1)') idmspc 
    11481167            ! 
    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 
     1168            !!GS: we consider 2D data as 3D data with vertical dim size = 1 
     1169            !IF(     idmspc <  irankpv ) THEN  
     1170            !   CALL ctl_stop( TRIM(clinfo), 'The file has only '//cldmspc//' spatial dimension',   & 
     1171            !      &                         'it is impossible to read a '//clrankpv//'D array from this file...' ) 
     1172            !ELSEIF( idmspc == irankpv ) THEN 
     1173            IF( idmspc == irankpv ) THEN 
    11531174               IF( PRESENT(pv_r1d) .AND. idom /= jpdom_unknown )   & 
    11541175                  &   CALL ctl_stop( TRIM(clinfo), 'case not coded...You must use jpdom_unknown' ) 
     
    19721993      ! 
    19731994      INTEGER :: ji, jj, jn, ni, nj 
    1974       INTEGER :: icnr, jcnr                                    ! Offset such that the vertex coordinate (i+icnr,j+jcnr) 
    1975       !                                                        ! represents the bottom-left corner of cell (i,j) 
     1995      INTEGER :: icnr, jcnr                             ! Offset such that the vertex coordinate (i+icnr,j+jcnr) 
     1996      !                                                 ! represents the bottom-left corner of cell (i,j) 
    19761997      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: z_bnds      ! Lat/lon coordinates of the vertices of cell (i,j) 
    19771998      REAL(wp), ALLOCATABLE, DIMENSION(:,:)     :: z_fld       ! Working array to determine where to rotate cells 
     
    21432164      f_op%timestep = nn_fsbc  ;  f_of%timestep =  0  ; CALL iom_set_field_attr('SBC'             , freq_op=f_op, freq_offset=f_of) 
    21442165      f_op%timestep = nn_fsbc  ;  f_of%timestep =  0  ; CALL iom_set_field_attr('SBC_scalar'      , freq_op=f_op, freq_offset=f_of) 
     2166      f_op%timestep = nn_fsbc  ;  f_of%timestep =  0  ; CALL iom_set_field_attr('ABL'             , freq_op=f_op, freq_offset=f_of) 
    21452167      f_op%timestep = nn_dttrc ;  f_of%timestep =  0  ; CALL iom_set_field_attr('ptrc_T'          , freq_op=f_op, freq_offset=f_of) 
    21462168      f_op%timestep = nn_dttrc ;  f_of%timestep =  0  ; CALL iom_set_field_attr('diad_T'          , freq_op=f_op, freq_offset=f_of) 
Note: See TracChangeset for help on using the changeset viewer.