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 11275 for NEMO/branches/2019/dev_r11265_ASINTER-01_Guillaume_ABL1D/src/OCE/IOM/iom.F90 – NEMO

Ignore:
Timestamp:
2019-07-17T15:05:13+02:00 (5 years ago)
Author:
smasson
Message:

dev_r11265_ABL : add ABL interface, see #2131

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11265_ASINTER-01_Guillaume_ABL1D/src/OCE/IOM/iom.F90

    r11223 r11275  
    2929   USE lib_mpp           ! MPP library 
    3030#if defined key_iomput 
    31    USE sbc_oce  , ONLY :   nn_fsbc         ! ocean space and time domain 
    32    USE trc_oce  , ONLY :   nn_dttrc        !  !: frequency of step on passive tracers 
    33    USE icb_oce  , ONLY :   nclasses, class_num       !  !: iceberg classes 
     31   USE sbc_oce  , ONLY :   nn_fsbc, ght_abl, ghw_abl, e3w_abl, jpka, jpkam1 
     32   USE trc_oce  , ONLY :   nn_dttrc                  ! frequency of step on passive tracers 
     33   USE icb_oce  , ONLY :   nclasses, class_num       ! iceberg classes 
    3434#if defined key_si3 
    3535   USE ice      , ONLY :   jpl 
     
    112112      ! 
    113113      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zt_bnds, zw_bnds 
     114      REAL(wp), DIMENSION(2   ,jpkam1)      ::   za_bnds     ! ABL vertical boundaries 
    114115      LOGICAL ::   ll_tmppatch = .TRUE.    !: seb: patch before we remove periodicity 
    115116      INTEGER ::   nldi_save, nlei_save    !:      and close boundaries in output files 
     
    195196      ! vertical grid definition 
    196197      IF(.NOT.llrst_context) THEN 
    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  
     198          CALL iom_set_axis_attr(  "deptht", paxis = gdept_1d ) 
     199          CALL iom_set_axis_attr(  "depthu", paxis = gdept_1d ) 
     200          CALL iom_set_axis_attr(  "depthv", paxis = gdept_1d ) 
     201          CALL iom_set_axis_attr(  "depthw", paxis = gdepw_1d ) 
     202 
     203          ! ABL 
     204          IF( .NOT. ALLOCATED(ght_abl) ) THEN   ! force definition for xml files (xios)  
     205             ALLOCATE( ght_abl(jpka), ghw_abl(jpka), e3t_abl(jpka), e3w_abl(jpka) )   ! default allocation needed by iom 
     206             ght_abl(:) = -1._wp   ;   ghw_abl(:) = -1._wp 
     207             e3t_abl(:) = -1._wp   ;   e3w_abl(:) = -1._wp 
     208          ENDIF 
     209          CALL iom_set_axis_attr( "ght_abl", ght_abl(2:jpka) ) 
     210          CALL iom_set_axis_attr( "ghw_abl", ghw_abl(2:jpka) ) 
     211           
    202212          ! Add vertical grid bounds 
    203213          jkmin = MIN(2,jpk)  ! in case jpk=1 (i.e. sas2D) 
     
    208218          zw_bnds(2,1:jpkm1  ) = gdepw_1d(jkmin:jpk) 
    209219          zw_bnds(2,jpk:     ) = gdepw_1d(jpk) + e3t_1d(jpk) 
    210           CALL iom_set_axis_attr( "deptht", bounds=zw_bnds ) 
    211           CALL iom_set_axis_attr( "depthu", bounds=zw_bnds ) 
    212           CALL iom_set_axis_attr( "depthv", bounds=zw_bnds ) 
    213           CALL iom_set_axis_attr( "depthw", bounds=zt_bnds ) 
     220          CALL iom_set_axis_attr(  "deptht", bounds=zw_bnds ) 
     221          CALL iom_set_axis_attr(  "depthu", bounds=zw_bnds ) 
     222          CALL iom_set_axis_attr(  "depthv", bounds=zw_bnds ) 
     223          CALL iom_set_axis_attr(  "depthw", bounds=zt_bnds ) 
     224 
     225          ! ABL 
     226          za_bnds(1,:) = ghw_abl(1:jpkam1) 
     227          za_bnds(2,:) = ghw_abl(2:jpka  ) 
     228          CALL iom_set_axis_attr( "ght_abl", bounds=za_bnds ) 
     229          za_bnds(1,:) = ght_abl(2:jpka  ) 
     230          za_bnds(2,:) = ght_abl(2:jpka  ) + e3w_abl(2:jpka) 
     231          CALL iom_set_axis_attr( "ghw_abl", bounds=za_bnds ) 
    214232          ! 
    215233# if defined key_floats 
     
    19431961      ! 
    19441962      INTEGER :: ji, jj, jn, ni, nj 
    1945       INTEGER :: icnr, jcnr                                    ! Offset such that the vertex coordinate (i+icnr,j+jcnr) 
    1946       !                                                        ! represents the bottom-left corner of cell (i,j) 
    1947       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: z_bnds      ! Lat/lon coordinates of the vertices of cell (i,j) 
    1948       REAL(wp), ALLOCATABLE, DIMENSION(:,:)     :: z_fld       ! Working array to determine where to rotate cells 
    1949       REAL(wp), ALLOCATABLE, DIMENSION(:,:)     :: z_rot       ! Lat/lon working array for rotation of cells 
    1950       !!---------------------------------------------------------------------- 
    1951       ! 
    1952       ALLOCATE( z_bnds(4,jpi,jpj,2), z_fld(jpi,jpj), z_rot(4,2)  ) 
     1963      INTEGER :: icnr, jcnr                             ! Offset such that the vertex coordinate (i+icnr,j+jcnr) 
     1964      !                                                 ! represents the bottom-left corner of cell (i,j) 
     1965      REAL(wp), DIMENSION(4,jpi,jpj,2) ::   z_bnds      ! Lat/lon coordinates of the vertices of cell (i,j) 
     1966      REAL(wp), DIMENSION(  jpi,jpj  ) ::   z_fld       ! Working array to determine where to rotate cells 
     1967      REAL(wp), DIMENSION(4        ,2) ::   z_rot       ! Lat/lon working array for rotation of cells 
     1968      !!---------------------------------------------------------------------- 
    19531969      ! 
    19541970      ! Offset of coordinate representing bottom-left corner 
     
    20312047          &                                    bounds_lon = RESHAPE(z_bnds(:,nldi:nlei,nldj:nlej,2),(/ 4,ni*nj /)), nvertex=4 ) 
    20322048      ! 
    2033       DEALLOCATE( z_bnds, z_fld, z_rot )  
    2034       ! 
    20352049   END SUBROUTINE set_grid_bounds 
    20362050 
     
    21152129      f_op%timestep = nn_fsbc  ;  f_of%timestep =  0  ; CALL iom_set_field_attr('SBC'             , freq_op=f_op, freq_offset=f_of) 
    21162130      f_op%timestep = nn_fsbc  ;  f_of%timestep =  0  ; CALL iom_set_field_attr('SBC_scalar'      , freq_op=f_op, freq_offset=f_of) 
     2131      f_op%timestep = nn_fsbc  ;  f_of%timestep =  0  ; CALL iom_set_field_attr('ABL'             , freq_op=f_op, freq_offset=f_of) 
    21172132      f_op%timestep = nn_dttrc ;  f_of%timestep =  0  ; CALL iom_set_field_attr('ptrc_T'          , freq_op=f_op, freq_offset=f_of) 
    21182133      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.