MODULE traqsr !!====================================================================== !! *** MODULE traqsr *** !! Ocean physics: solar radiation penetration in the top ocean levels !!====================================================================== !! History : 6.0 ! 90-10 (B. Blanke) Original code !! 7.0 ! 91-11 (G. Madec) !! ! 96-01 (G. Madec) s-coordinates !! 8.5 ! 02-06 (G. Madec) F90: Free form and module !! 9.0 ! 05-11 (G. Madec) zco, zps, sco coordinate !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! tra_qsr : trend due to the solar radiation penetration !! tra_qsr_init : solar radiation penetration initialization !!---------------------------------------------------------------------- USE oce ! ocean dynamics and active tracers USE dom_oce ! ocean space and time domain USE trdmod ! ocean active tracers trends USE trdmod_oce ! ocean variables trends USE in_out_manager ! I/O manager USE trc_oce ! share SMS/Ocean variables USE ocesbc ! thermohaline fluxes USE phycst ! physical constants USE prtctl ! Print control IMPLICIT NONE PRIVATE PUBLIC tra_qsr ! routine called by step.F90 (ln_traqsr=T) PUBLIC tra_qsr_init ! routine called by opa.F90 !!* Namelist namqsr: penetrative solar radiation LOGICAL , PUBLIC :: ln_traqsr = .TRUE. !: qsr flag (Default=T) REAL(wp), PUBLIC :: rabs = 0.58_wp ! fraction associated with xsi1 REAL(wp), PUBLIC :: xsi1 = 0.35_wp ! first depth of extinction REAL(wp), PUBLIC :: xsi2 = 23.0_wp ! second depth of extinction (default values: water type Ib) LOGICAL , PUBLIC :: ln_qsr_sms = .false. ! flag to use or not the biological fluxes for light INTEGER :: nksr ! number of levels REAL(wp), DIMENSION(jpk) :: gdsr ! profile of the solar flux penetration !! * Substitutions # include "domzgr_substitute.h90" # include "vectopt_loop_substitute.h90" !!---------------------------------------------------------------------- !! OPA 9.0 , LOCEAN-IPSL (2005) !! $Header$ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE tra_qsr( kt ) !!---------------------------------------------------------------------- !! *** ROUTINE tra_qsr *** !! !! ** Purpose : Compute the temperature trend due to the solar radiation !! penetration and add it to the general temperature trend. !! !! ** Method : The profile of the solar radiation within the ocean is !! defined through two penetration length scale (xsr1,xsr2) and a !! ratio (rabs) as : !! I(k) = Qsr*( rabs*EXP(z(k)/xsr1) + (1.-rabs)*EXP(z(k)/xsr2) ) !! The temperature trend associated with the solar radiation !! penetration is given by : !! zta = 1/e3t dk[ I ] / (rau0*Cp) !! At the bottom, boudary condition for the radiation is no flux : !! all heat which has not been absorbed in the above levels is put !! in the last ocean level. !! In z-coordinate case, the computation is only done down to the !! level where I(k) < 1.e-15 W/m2. In addition, the coefficients !! used for the computation are calculated one for once as they !! depends on k only. !! !! ** Action : - update ta with the penetrative solar radiation trend !! - save the trend in ttrd ('key_trdtra') !!---------------------------------------------------------------------- USE oce, ONLY : ztrdt => ua ! use ua as 3D workspace USE oce, ONLY : ztrds => va ! use va as 3D workspace !! INTEGER, INTENT(in) :: kt ! ocean time-step !! INTEGER :: ji, jj, jk ! dummy loop indexes REAL(wp) :: zc0 , zta ! temporary scalars !!---------------------------------------------------------------------- IF( kt == nit000 ) THEN IF(lwp) WRITE(numout,*) IF(lwp) WRITE(numout,*) 'tra_qsr : penetration of the surface solar radiation' IF(lwp) WRITE(numout,*) '~~~~~~~' CALL tra_qsr_init ENDIF IF( l_trdtra ) THEN ! Save ta and sa trends ztrdt(:,:,:) = ta(:,:,:) ztrds(:,:,:) = 0.e0 ENDIF ! ---------------------------------------------- ! ! Biological fluxes : all vertical coordinate ! ! ---------------------------------------------- ! IF( lk_qsr_sms .AND. ln_qsr_sms ) THEN ! ! =============== DO jk = 1, jpkm1 ! Horizontal slab ! ! =============== DO jj = 2, jpjm1 DO ji = fs_2, fs_jpim1 ! vector opt. zc0 = ro0cpr / fse3t(ji,jj,jk) ! compute the qsr trend zta = zc0 * ( etot3(ji,jj,jk ) * tmask(ji,jj,jk) & & - etot3(ji,jj,jk+1) * tmask(ji,jj,jk+1) ) ta(ji,jj,jk) = ta(ji,jj,jk) + zta ! add qsr trend to the temperature trend END DO END DO ! ! =============== END DO ! End of slab ! ! =============== ! ---------------------------------------------- ! ! Ocean alone : ! ---------------------------------------------- ! ELSE ! ! =================== ! IF( ln_sco ) THEN ! s-coordinate ! ! ! =================== ! DO jk = 1, jpkm1 ta(:,:,jk) = ta(:,:,jk) + etot3(:,:,jk) * qsr(:,:) END DO ENDIF ! ! =================== ! IF( ln_zps ) THEN ! partial steps ! ! ! =================== ! DO jk = 1, nksr DO jj = 2, jpjm1 DO ji = fs_2, fs_jpim1 ! vector opt. ! qsr trend from gdsr zc0 = qsr(ji,jj) / fse3t(ji,jj,jk) zta = zc0 * ( gdsr(jk) * tmask(ji,jj,jk) - gdsr(jk+1) * tmask(ji,jj,jk+1) ) ! add qsr trend to the temperature trend ta(ji,jj,jk) = ta(ji,jj,jk) + zta END DO END DO END DO ENDIF ! ! =================== ! IF( ln_zco ) THEN ! z-coordinate ! ! ! =================== ! DO jk = 1, nksr zc0 = 1. / e3t_0(jk) DO jj = 2, jpjm1 DO ji = fs_2, fs_jpim1 ! vector opt. ! qsr trend zta = qsr(ji,jj) * zc0 * ( gdsr(jk)*tmask(ji,jj,jk) - gdsr(jk+1)*tmask(ji,jj,jk+1) ) ! add qsr trend to the temperature trend ta(ji,jj,jk) = ta(ji,jj,jk) + zta END DO END DO END DO ENDIF ! ENDIF IF( l_trdtra ) THEN ! qsr tracers trends saved for diagnostics ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:) CALL trd_mod( ztrdt, ztrds, jptra_trd_qsr, 'TRA', kt ) ENDIF ! ! print mean trends (used for debugging) IF(ln_ctl) CALL prt_ctl( tab3d_1=ta, clinfo1=' qsr - Ta: ', mask1=tmask, clinfo3='tra-ta' ) ! END SUBROUTINE tra_qsr SUBROUTINE tra_qsr_init !!---------------------------------------------------------------------- !! *** ROUTINE tra_qsr_init *** !! !! ** Purpose : Initialization for the penetrative solar radiation !! !! ** Method : The profile of solar radiation within the ocean is set !! from two length scale of penetration (xsr1,xsr2) and a ratio !! (rabs). These parameters are read in the namqsr namelist. The !! default values correspond to clear water (type I in Jerlov' !! (1968) classification. !! called by tra_qsr at the first timestep (nit000) !! !! ** Action : - initialize xsr1, xsr2 and rabs !! !! Reference : Jerlov, N. G., 1968 Optical Oceanography, Elsevier, 194pp. !!---------------------------------------------------------------------- INTEGER :: ji, jj, jk ! dummy loop index INTEGER :: indic ! temporary integer REAL(wp) :: zc0 , zc1 , zc2 ! temporary scalars REAL(wp) :: zcst, zdp1, zdp2 ! " " NAMELIST/namqsr/ ln_traqsr, rabs, xsi1, xsi2, ln_qsr_sms !!---------------------------------------------------------------------- REWIND ( numnam ) ! Read Namelist namqsr : ratio and length of penetration READ ( numnam, namqsr ) IF( ln_traqsr ) THEN ! Parameter control and print IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) 'tra_qsr_init : penetration of the surface solar radiation' WRITE(numout,*) '~~~~~~~~~~~~' WRITE(numout,*) ' Namelist namqsr : set the parameter of penetration' WRITE(numout,*) ' fraction associated with xsi rabs = ',rabs WRITE(numout,*) ' first depth of extinction xsi1 = ',xsi1 WRITE(numout,*) ' second depth of extinction xsi2 = ',xsi2 IF( lk_qsr_sms ) THEN WRITE(numout,*) ' Biological fluxes for light(Y/N) ln_qsr_sms = ',ln_qsr_sms ENDIF ENDIF ELSE IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) 'tra_qsr_init : NO solar flux penetration' WRITE(numout,*) '~~~~~~~~~~~~' ENDIF ENDIF IF( rabs > 1.e0 .OR. rabs < 0.e0 .OR. xsi1 < 0.e0 .OR. xsi2 < 0.e0 ) & CALL ctl_stop( ' 0