Changeset 15394 for NEMO/trunk/src/TOP/TRP/trcsbc.F90
- Timestamp:
- 2021-10-18T12:55:29+02:00 (3 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/trunk/src/TOP/TRP/trcsbc.F90
r14215 r15394 51 51 !! The surface freshwater flux modify the ocean volume 52 52 !! and thus the concentration of a tracer as : 53 !! tr(Krhs) = tr(Krhs) + emp * tr(Kmm) / e3t_ for k=1 54 !! where emp, the surface freshwater budget (evaporation minus 55 !! precipitation ) given in kg/m2/s is divided 56 !! by 1035 kg/m3 (density of ocean water) to obtain m/s. 53 !! tr(Krhs) = tr(Krhs) + emp * tr(Kmm) / e3t_ + fmmflx * tri / e3t for k=1 54 !! - tr(Kmm) , the concentration of tracer in the ocean 55 !! - tri, the concentration of tracer in the sea-ice 56 !! - emp, the surface freshwater budget (evaporation minus precipitation + fmmflx) 57 !! given in kg/m2/s is divided by 1035 kg/m3 (density of ocean water) to obtain m/s. 58 !! - fmmflx, the flux asscociated to freezing-melting of sea-ice 59 !! In linear free surface case (ln_linssh=T), the volume of the 60 !! ocean does not change with the water exchanges at the (air+ice)-sea 57 61 !! 58 62 !! ** Action : - Update the 1st level of tr(:,:,:,:,Krhs) with the trend associated … … 66 70 INTEGER :: ji, jj, jn ! dummy loop indices 67 71 REAL(wp) :: zse3t, zrtrn, zfact ! local scalars 68 REAL(wp) :: z ftra, zdtra, ztfx, ztra! - -72 REAL(wp) :: zdtra ! - - 69 73 CHARACTER (len=22) :: charout 70 REAL(wp), DIMENSION(jpi,jpj) :: zsfx71 74 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: ztrtrd 72 75 !!--------------------------------------------------------------------- … … 106 109 ENDIF 107 110 108 ! Coupling online : river runoff is added to the horizontal divergence (hdiv) in the subroutine sbc_rnf_div109 ! one only consider the concentration/dilution effect due to evaporation minus precipitation + freezing/melting of sea-ice110 ! Coupling offline : runoff are in emp which contains E-P-R111 !112 IF( .NOT.ln_linssh ) THEN ! online coupling with vvl113 zsfx(:,:) = 0._wp114 ELSE ! online coupling free surface or offline with free surface115 zsfx(:,:) = emp(:,:)116 ENDIF117 118 111 ! 0. initialization 119 112 SELECT CASE ( nn_ice_tr ) 120 113 121 CASE ( -1 ) ! No tracers in sea ice (null concentration in sea ice) 122 ! 123 DO jn = 1, jptra 124 DO_2D( 0, 0, 0, 1 ) 125 sbc_trc(ji,jj,jn) = zsfx(ji,jj) * r1_rho0 * ptr(ji,jj,1,jn,Kmm) 126 END_2D 127 END DO 128 ! 129 CASE ( 0 ) ! Same concentration in sea ice and in the ocean 130 ! 131 DO jn = 1, jptra 132 DO_2D( 0, 0, 0, 1 ) 133 sbc_trc(ji,jj,jn) = ( zsfx(ji,jj) + fmmflx(ji,jj) ) * r1_rho0 * ptr(ji,jj,1,jn,Kmm) 134 END_2D 135 END DO 114 CASE ( -1 ) ! ! No tracers in sea ice ( trc_i = 0 ) 115 ! 116 DO jn = 1, jptra 117 DO_2D( 0, 0, 0, 1 ) 118 sbc_trc(ji,jj,jn) = 0._wp 119 END_2D 120 END DO 121 ! 122 IF( ln_linssh ) THEN !* linear free surface 123 DO jn = 1, jptra 124 DO_2D( 0, 0, 0, 1 ) 125 sbc_trc(ji,jj,jn) = sbc_trc(ji,jj,jn) + r1_rho0 * emp(ji,jj) * ptr(ji,jj,1,jn,Kmm) !==>> add concentration/dilution effect due to constant volume cell 126 END_2D 127 END DO 128 ENDIF 129 ! 130 CASE ( 0 ) ! Same concentration in sea ice and in the ocean ( trc_i = ptr(...,Kmm) ) 131 ! 132 DO jn = 1, jptra 133 DO_2D( 0, 0, 0, 1 ) 134 sbc_trc(ji,jj,jn) = - fmmflx(ji,jj) * r1_rho0 * ptr(ji,jj,1,jn,Kmm) 135 END_2D 136 END DO 137 ! 138 IF( ln_linssh ) THEN !* linear free surface 139 DO jn = 1, jptra 140 DO_2D( 0, 0, 0, 1 ) 141 sbc_trc(ji,jj,jn) = sbc_trc(ji,jj,jn) + r1_rho0 * emp(ji,jj) * ptr(ji,jj,1,jn,Kmm) !==>> add concentration/dilution effect due to constant volume cell 142 END_2D 143 END DO 144 ENDIF 136 145 ! 137 146 CASE ( 1 ) ! Specific treatment of sea ice fluxes with an imposed concentration in sea ice … … 139 148 DO jn = 1, jptra 140 149 DO_2D( 0, 0, 0, 1 ) 141 zse3t = 1. / e3t(ji,jj,1,Kmm) 142 ! tracer flux at the ice/ocean interface (tracer/m2/s) 143 zftra = - trc_i(ji,jj,jn) * fmmflx(ji,jj) ! uptake of tracer in the sea ice 144 ! ! only used in the levitating sea ice case 145 ! tracer flux only : add concentration dilution term in net tracer flux, no F-M in volume flux 146 ! tracer and mass fluxes : no concentration dilution term in net tracer flux, F-M term in volume flux 147 ztfx = zftra ! net tracer flux 148 ! 149 zdtra = r1_rho0 * ( ztfx + ( zsfx(ji,jj) + fmmflx(ji,jj) ) * ptr(ji,jj,1,jn,Kmm) ) 150 IF ( zdtra < 0. ) THEN 151 zdtra = MAX(zdtra, -ptr(ji,jj,1,jn,Kmm) * e3t(ji,jj,1,Kmm) / rDt_trc ) ! avoid negative concentrations to arise 152 ENDIF 153 sbc_trc(ji,jj,jn) = zdtra 154 END_2D 155 END DO 150 sbc_trc(ji,jj,jn) = - fmmflx(ji,jj) * r1_rho0 * trc_i(ji,jj,jn) 151 END_2D 152 END DO 153 ! 154 IF( ln_linssh ) THEN !* linear free surface 155 DO jn = 1, jptra 156 DO_2D( 0, 0, 0, 1 ) 157 sbc_trc(ji,jj,jn) = sbc_trc(ji,jj,jn) + r1_rho0 * emp(ji,jj) * ptr(ji,jj,1,jn,Kmm) !==>> add concentration/dilution effect due to constant volume cell 158 END_2D 159 END DO 160 ENDIF 161 ! 162 DO jn = 1, jptra 163 DO_2D( 0, 0, 0, 1 ) 164 zse3t = rDt_trc / e3t(ji,jj,1,Kmm) 165 zdtra = ptr(ji,jj,1,jn,Kmm) + sbc_trc(ji,jj,jn) * zse3t 166 IF( zdtra < 0. ) sbc_trc(ji,jj,jn) = MAX( zdtra, -ptr(ji,jj,1,jn,Kmm) / zse3t ) ! avoid negative concentration that can occurs if trc_i > ptr 167 END_2D 168 END DO 169 ! 156 170 END SELECT 157 171 !
Note: See TracChangeset
for help on using the changeset viewer.