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 15410 – NEMO

Changeset 15410


Ignore:
Timestamp:
2021-10-20T11:10:59+02:00 (3 years ago)
Author:
smueller
Message:

Synchronizing with /NEMO/releases/r4.0/r4.0-HEAD@15405 (ticket #2487)

Location:
NEMO/branches/2020/ticket2487
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/ticket2487

    • Property svn:externals
      •  

        old new  
        44^/utils/tools_r4.0-HEAD@14974   tools 
        55^/vendors/AGRIF/stable@14105    ext/AGRIF 
        6 ^/vendors/FCM@10134             ext/FCM 
         6^/vendors/FCM@15268             ext/FCM 
        77^/vendors/IOIPSL@9655           ext/IOIPSL 
        88 
  • NEMO/branches/2020/ticket2487/cfgs/ORCA2_OFF_PISCES/EXPREF/namelist_cfg

    r15264 r15410  
    321321   sn_sal      = 'dyna_grid_T'           ,       120.        , 'vosaline'  ,  .true.   , .true. , 'yearly'  , ''               , ''       , '' 
    322322   sn_mld      = 'dyna_grid_T'           ,       120.        , 'somixhgt'  ,  .true.   , .true. , 'yearly'  , ''               , ''       , '' 
    323    sn_emp      = 'dyna_grid_T'           ,       120.        , 'sowaflup'  ,  .true.   , .true. , 'yearly'  , ''               , ''       , '' 
     323   sn_emp      = 'dyna_grid_T'           ,       120.        , 'sowaflcd'  ,  .true.   , .true. , 'yearly'  , ''               , ''       , '' 
    324324   sn_fmf      = 'dyna_grid_T'           ,       120.        , 'iowaflup'  ,  .true.   , .true. , 'yearly'  , ''               , ''       , '' 
    325325   sn_ice      = 'dyna_grid_T'           ,       120.        , 'soicecov'  ,  .true.   , .true. , 'yearly'  , ''               , ''       , '' 
  • NEMO/branches/2020/ticket2487/cfgs/ORCA2_OFF_TRC/EXPREF/namelist_cfg

    r15264 r15410  
    319319   sn_sal      = 'dyna_grid_T'           ,       120.        , 'vosaline'  ,  .true.   , .true. , 'yearly'  , ''               , ''       , '' 
    320320   sn_mld      = 'dyna_grid_T'           ,       120.        , 'somixhgt'  ,  .true.   , .true. , 'yearly'  , ''               , ''       , '' 
    321    sn_emp      = 'dyna_grid_T'           ,       120.        , 'sowaflup'  ,  .true.   , .true. , 'yearly'  , ''               , ''       , '' 
     321   sn_emp      = 'dyna_grid_T'           ,       120.        , 'sowaflcd'  ,  .true.   , .true. , 'yearly'  , ''               , ''       , '' 
    322322   sn_fmf      = 'dyna_grid_T'           ,       120.        , 'iowaflup'  ,  .true.   , .true. , 'yearly'  , ''               , ''       , '' 
    323323   sn_ice      = 'dyna_grid_T'           ,       120.        , 'soicecov'  ,  .true.   , .true. , 'yearly'  , ''               , ''       , '' 
  • NEMO/branches/2020/ticket2487/src/ICE/iceistate.F90

    r15264 r15410  
    420420            ! 
    421421            DO jk = 1,jpkm1                     ! adjust initial vertical scale factors                 
    422                e3t_n(:,:,jk) = e3t_0(:,:,jk) * z2d(:,:) 
     422               e3t_n(:,:,jk) = e3t_0(:,:,jk) * ( z2d(:,:) * tmask(:,:,jk) - ( tmask(:,:,jk) - 1.0_wp ) ) 
    423423               e3t_b(:,:,jk) = e3t_n(:,:,jk) 
    424424               e3t_a(:,:,jk) = e3t_n(:,:,jk) 
  • NEMO/branches/2020/ticket2487/src/OCE/BDY/bdydta.F90

    r15264 r15410  
    246246         ! If full velocities in boundary data, then split it into barotropic and baroclinic component 
    247247         IF( bf_alias(jp_bdyu3d)%ltotvel ) THEN     ! if we read 3D total velocity (can be true only if u3d was read) 
    248             ! 
    249248            igrd = 2                       ! zonal velocity 
    250249            DO ib = 1, idx_bdy(jbdy)%nblen(igrd) 
     
    260259               END DO 
    261260            END DO 
     261         ENDIF   ! ltotvel 
     262         IF( bf_alias(jp_bdyv3d)%ltotvel ) THEN     ! if we read 3D total velocity (can be true only if u3d was read) 
    262263            igrd = 3                       ! meridional velocity 
    263264            DO ib = 1, idx_bdy(jbdy)%nblen(igrd) 
  • NEMO/branches/2020/ticket2487/src/OCE/ICB/icbini.F90

    r15264 r15410  
    7272      IF( .NOT. ln_icebergs )   RETURN 
    7373 
     74      ALLOCATE( utau_icb(jpi,jpj) , vtau_icb(jpi,jpj) ) 
    7475      !                          ! allocate gridded fields 
    7576      IF( icb_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'icb_alloc : unable to allocate arrays' ) 
  • NEMO/branches/2020/ticket2487/src/OCE/ICB/icbutl.F90

    r15264 r15410  
    7676      ss_e(1:jpi,1:jpj) = sss_m(:,:) 
    7777      fr_e(1:jpi,1:jpj) = fr_i (:,:) 
    78       ua_e(1:jpi,1:jpj) = utau (:,:) * umask(:,:,1) ! maybe mask useless because mask applied in sbcblk 
    79       va_e(1:jpi,1:jpj) = vtau (:,:) * vmask(:,:,1) ! maybe mask useless because mask applied in sbcblk 
     78      ua_e(1:jpi,1:jpj) = utau_icb (:,:) * umask(:,:,1) ! maybe mask useless because mask applied in sbcblk 
     79      va_e(1:jpi,1:jpj) = vtau_icb (:,:) * vmask(:,:,1) ! maybe mask useless because mask applied in sbcblk 
    8080      ! 
    8181      CALL lbc_lnk_icb( 'icbutl', uo_e, 'U', -1._wp, 1, 1 ) 
  • NEMO/branches/2020/ticket2487/src/OCE/SBC/sbc_oce.F90

    r15264 r15410  
    113113   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   utau   , utau_b   !: sea surface i-stress (ocean referential)     [N/m2] 
    114114   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   vtau   , vtau_b   !: sea surface j-stress (ocean referential)     [N/m2] 
     115   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   utau_icb, vtau_icb !: sea surface (i,j)-stress used by icebergs   [N/m2] 
    115116   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   taum              !: module of sea surface stress (at T-point)    [N/m2]  
    116117   !! wndm is used onmpute surface gases exchanges in ice-free ocean or leads 
  • NEMO/branches/2020/ticket2487/src/OCE/SBC/sbcmod.F90

    r15264 r15410  
    449449      IF( ln_mixcpl )          CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice )   ! forced-coupled mixed formulation after forcing 
    450450      ! 
    451       IF ( ln_wave .AND. (ln_tauwoc .OR. ln_tauw) ) CALL sbc_wstress( )      ! Wind stress provided by waves  
     451      IF ( ln_wave .AND. (ln_tauwoc .OR. ln_tauw) ) CALL sbc_wstress( )       ! Wind stress provided by waves  
     452      ! 
     453      IF( ln_icebergs ) THEN  ! save pure wind stresses (with no ice-ocean stress) to be used by icebergs 
     454         utau_icb(:,:) = utau(:,:) ; vtau_icb(:,:) = vtau(:,:) 
     455      ENDIF  
    452456      ! 
    453457      !                                            !==  Misc. Options  ==! 
  • NEMO/branches/2020/ticket2487/src/OCE/lib_fortran.F90

    r10425 r15410  
    3434#if defined key_nosignedzero 
    3535   PUBLIC SIGN 
     36#endif 
     37#if defined key_noisnan 
     38   PUBLIC ISNAN 
    3639#endif 
    3740 
     
    486489#endif 
    487490 
     491#if defined key_noisnan 
     492!$AGRIF_DO_NOT_TREAT 
     493   FUNCTION ISNAN(pa) 
     494      !!----------------------------------------------------------------------- 
     495      !!                  ***  FUNCTION ISNAN  *** 
     496      !! 
     497      !! ** Purpose: provide an alternative to non-standard intrinsic function 
     498      !!             ISNAN 
     499      !!----------------------------------------------------------------------- 
     500      USE, INTRINSIC ::   ieee_arithmetic 
     501      !! 
     502      REAL(wp), INTENT(in) ::   pa 
     503      LOGICAL              ::   ISNAN 
     504      !!----------------------------------------------------------------------- 
     505      ! 
     506      ISNAN = ieee_is_nan(pa) 
     507   END FUNCTION ISNAN 
     508!$AGRIF_END_DO_NOT_TREAT 
     509#endif 
     510 
    488511   !!====================================================================== 
    489512END MODULE lib_fortran 
  • NEMO/branches/2020/ticket2487/src/OCE/stpctl.F90

    r13137 r15410  
    2727   USE wet_dry,   ONLY : ll_wd, ssh_ref    ! reference depth for negative bathy 
    2828 
     29   USE lib_fortran     ! Fortran utilities 
    2930   USE netcdf          ! NetCDF library 
    3031   IMPLICIT NONE 
  • NEMO/branches/2020/ticket2487/src/TOP/TRP/trcsbc.F90

    r10788 r15410  
    4949      !!            The surface freshwater flux modify the ocean volume 
    5050      !!         and thus the concentration of a tracer as : 
    51       !!            tra = tra + emp * trn / e3t   for k=1 
    52       !!         where emp, the surface freshwater budget (evaporation minus 
    53       !!         precipitation ) given in kg/m2/s is divided 
    54       !!         by 1035 kg/m3 (density of ocean water) to obtain m/s. 
     51      !!            tra = tra + emp * trn / e3t + fmmflx * tri / e3t  for k=1 
     52      !!         where : 
     53      !!          - trn, the concentration of tracer in the ocean 
     54      !!          - tri, the concentration of tracer in the sea-ice 
     55      !!          - emp, the surface freshwater budget (evaporation minus precipitation + fmmflx) 
     56      !!            given in kg/m2/s is divided by 1035 kg/m3 (density of ocean water) to obtain m/s. 
     57      !!          - fmmflx, the flux asscociated to freezing-melting of sea-ice  
     58      !!            In linear free surface case (ln_linssh=T), the volume of the 
     59      !!            ocean does not change with the water exchanges at the (air+ice)-sea 
    5560      !! 
    5661      !! ** Action  : - Update the 1st level of tra with the trend associated 
     
    6267      INTEGER  ::   ji, jj, jn                      ! dummy loop indices 
    6368      REAL(wp) ::   zse3t, zrtrn, zfact     ! local scalars 
    64       REAL(wp) ::   zftra, zdtra, ztfx, ztra   !   -      - 
     69      REAL(wp) ::   zdtra          !   -      - 
    6570      CHARACTER (len=22) :: charout 
    66       REAL(wp), DIMENSION(jpi,jpj)   ::   zsfx 
    6771      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrtrd 
    6872      !!--------------------------------------------------------------------- 
     
    102106      ENDIF 
    103107 
    104       ! Coupling online : river runoff is added to the horizontal divergence (hdivn) in the subroutine sbc_rnf_div  
    105       ! one only consider the concentration/dilution effect due to evaporation minus precipitation + freezing/melting of sea-ice 
    106       ! Coupling offline : runoff are in emp which contains E-P-R 
    107       ! 
    108       IF( .NOT.ln_linssh ) THEN  ! online coupling with vvl 
    109          zsfx(:,:) = 0._wp 
    110       ELSE                                      ! online coupling free surface or offline with free surface 
    111          zsfx(:,:) = emp(:,:) 
    112       ENDIF 
    113  
    114108      ! 0. initialization 
    115109      SELECT CASE ( nn_ice_tr ) 
    116110 
    117       CASE ( -1 ) ! No tracers in sea ice (null concentration in sea ice) 
    118          ! 
    119          DO jn = 1, jptra 
    120             DO jj = 2, jpj 
    121                DO ji = fs_2, fs_jpim1   ! vector opt. 
    122                   sbc_trc(ji,jj,jn) = zsfx(ji,jj) * r1_rau0 * trn(ji,jj,1,jn) 
    123                END DO 
    124             END DO 
    125          END DO 
    126          ! 
    127       CASE ( 0 )  ! Same concentration in sea ice and in the ocean 
    128          ! 
    129          DO jn = 1, jptra 
    130             DO jj = 2, jpj 
    131                DO ji = fs_2, fs_jpim1   ! vector opt. 
    132                   sbc_trc(ji,jj,jn) = ( zsfx(ji,jj) + fmmflx(ji,jj) ) * r1_rau0 * trn(ji,jj,1,jn) 
    133                END DO 
    134             END DO 
    135          END DO 
    136          ! 
     111      CASE ( -1 ) ! No tracers in sea ice ( trc_i = 0 ) 
     112         ! 
     113         DO jn = 1, jptra 
     114            DO jj = 2, jpj 
     115               DO ji = fs_2, fs_jpim1   ! vector opt. 
     116                  sbc_trc(ji,jj,jn) = 0._wp 
     117               END DO 
     118            END DO 
     119         END DO 
     120         ! 
     121         IF( ln_linssh ) THEN  !* linear free surface   
     122            DO jn = 1, jptra 
     123               DO jj = 2, jpj 
     124                  DO ji = fs_2, fs_jpim1   ! vector opt. 
     125                     sbc_trc(ji,jj,jn) = sbc_trc(ji,jj,jn) + r1_rau0 * emp(ji,jj) * trn(ji,jj,1,jn) !==>> add concentration/dilution effect due to constant volume cell 
     126                  END DO 
     127               END DO 
     128            END DO 
     129         ENDIF 
     130         ! 
     131      CASE ( 0 )  ! Same concentration in sea ice and in the ocean ( trc_i = trn ) 
     132         ! 
     133         DO jn = 1, jptra 
     134            DO jj = 2, jpj 
     135               DO ji = fs_2, fs_jpim1   ! vector opt. 
     136                  sbc_trc(ji,jj,jn) = - fmmflx(ji,jj) * r1_rau0 * trn(ji,jj,1,jn) 
     137               END DO 
     138            END DO 
     139         END DO 
     140         ! 
     141         IF( ln_linssh ) THEN  !* linear free surface   
     142            DO jn = 1, jptra 
     143               DO jj = 2, jpj 
     144                  DO ji = fs_2, fs_jpim1   ! vector opt. 
     145                     sbc_trc(ji,jj,jn) = sbc_trc(ji,jj,jn) + r1_rau0 * emp(ji,jj) * trn(ji,jj,1,jn) !==>> add concentration/dilution effect due to constant volume cell 
     146                  END DO 
     147               END DO 
     148            END DO 
     149         ENDIF 
     150 
    137151      CASE ( 1 )  ! Specific treatment of sea ice fluxes with an imposed concentration in sea ice  
    138152         ! 
     
    140154            DO jj = 2, jpj 
    141155               DO ji = fs_2, fs_jpim1   ! vector opt. 
    142                   zse3t = 1. / e3t_n(ji,jj,1) 
    143                   ! tracer flux at the ice/ocean interface (tracer/m2/s) 
    144                   zftra = - trc_i(ji,jj,jn) * fmmflx(ji,jj) ! uptake of tracer in the sea ice 
    145                   !                                         ! only used in the levitating sea ice case 
    146                   ! tracer flux only       : add concentration dilution term in net tracer flux, no F-M in volume flux 
    147                   ! tracer and mass fluxes : no concentration dilution term in net tracer flux, F-M term in volume flux 
    148                   ztfx  = zftra                        ! net tracer flux 
    149                   ! 
    150                   zdtra = r1_rau0 * ( ztfx + ( zsfx(ji,jj) + fmmflx(ji,jj) ) * trn(ji,jj,1,jn) )  
    151                   IF ( zdtra < 0. ) THEN 
    152                      zdtra  = MAX(zdtra, -trn(ji,jj,1,jn) * e3t_n(ji,jj,1) / r2dttrc )   ! avoid negative concentrations to arise 
    153                   ENDIF 
    154                   sbc_trc(ji,jj,jn) =  zdtra  
    155                END DO 
    156             END DO 
    157          END DO 
     156                  sbc_trc(ji,jj,jn)  = - fmmflx(ji,jj) * r1_rau0 * trc_i(ji,jj,jn) 
     157               END DO 
     158            END DO 
     159         END DO 
     160         ! 
     161         IF( ln_linssh ) THEN  !* linear free surface   
     162            DO jn = 1, jptra 
     163               DO jj = 2, jpj 
     164                  DO ji = fs_2, fs_jpim1   ! vector opt. 
     165                     sbc_trc(ji,jj,jn) = sbc_trc(ji,jj,jn) + r1_rau0 * emp(ji,jj) * trn(ji,jj,1,jn) !==>> add concentration/dilution effect due to constant volume cell 
     166                  END DO 
     167               END DO 
     168            END DO 
     169         ENDIF 
     170         ! 
     171         DO jn = 1, jptra 
     172            DO jj = 2, jpj 
     173               DO ji = fs_2, fs_jpim1   ! vector opt. 
     174                  zse3t = r2dttrc / e3t_n(ji,jj,1) 
     175                  zdtra = trn(ji,jj,1,jn) + sbc_trc(ji,jj,jn) * zse3t  
     176                  IF( zdtra < 0. ) sbc_trc(ji,jj,jn) = MAX( zdtra, -trn(ji,jj,1,jn) / zse3t  ) ! avoid negative concentration that can occurs if trc_i > trn                    
     177               END DO 
     178            END DO 
     179         END DO 
     180         !                                                       ! =========== 
    158181      END SELECT 
     182 
    159183      ! 
    160184      CALL lbc_lnk( 'trcsbc', sbc_trc(:,:,:), 'T', 1. ) 
     
    175199            CALL trd_tra( kt, 'TRC', jn, jptra_nsr, ztrtrd ) 
    176200         END IF 
    177          !                                                       ! =========== 
     201         ! 
    178202      END DO                                                     ! tracer loop 
    179203      !                                                          ! =========== 
Note: See TracChangeset for help on using the changeset viewer.