Changeset 10966
- Timestamp:
- 2019-05-10T18:43:09+02:00 (6 years ago)
- Location:
- NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src
- Files:
-
- 25 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/TRD/trdtra.F90
r10946 r10966 172 172 END SELECT 173 173 ! ! send trend to trd_trc 174 CALL trd_trc( ztrds, ktra, ktrd, kt )174 CALL trd_trc( ztrds, ktra, ktrd, kt, Kmm ) 175 175 ! 176 176 ENDIF -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/TRD/trdtrc.F90
r10068 r10966 9 9 CONTAINS 10 10 11 SUBROUTINE trd_trc( ptrtrd, kjn, ktrd, kt )11 SUBROUTINE trd_trc( ptrtrd, kjn, ktrd, kt, Kmm ) 12 12 INTEGER :: kt, kjn, ktrd 13 INTEGER :: Kmm ! time level index 13 14 REAL :: ptrtrd(:,:,:) 14 15 WRITE(*,*) 'trd_trc : You should not have seen this print! error?', ptrtrd(1,1,1) -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/AGE/trcsms_age.F90
r10070 r10966 37 37 CONTAINS 38 38 39 SUBROUTINE trc_sms_age( kt )39 SUBROUTINE trc_sms_age( kt, Kmm ) 40 40 !!---------------------------------------------------------------------- 41 41 !! *** trc_sms_age *** … … 46 46 !!---------------------------------------------------------------------- 47 47 INTEGER, INTENT(in) :: kt ! ocean time-step index 48 INTEGER, INTENT(in) :: Kmm ! ocean time level 48 49 INTEGER :: jn, jk ! dummy loop index 49 50 !!---------------------------------------------------------------------- … … 67 68 END DO 68 69 ! 69 IF( l_trdtrc ) CALL trd_trc( tra(:,:,:,jp_age), jn, jptra_sms, kt ) ! save trends70 IF( l_trdtrc ) CALL trd_trc( tra(:,:,:,jp_age), jn, jptra_sms, kt, Kmm ) ! save trends 70 71 ! 71 72 IF( ln_timing ) CALL timing_stop('trc_sms_age') -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/C14/trcsms_c14.F90
r10069 r10966 33 33 CONTAINS 34 34 35 SUBROUTINE trc_sms_c14( kt )35 SUBROUTINE trc_sms_c14( kt, Kmm ) 36 36 !!---------------------------------------------------------------------- 37 37 !! *** ROUTINE trc_sms_c14 *** … … 51 51 ! 52 52 INTEGER, INTENT(in) :: kt ! ocean time-step index 53 INTEGER, INTENT(in) :: Kmm ! ocean time level 53 54 ! 54 55 INTEGER :: ji, jj, jk ! dummy loop indices … … 157 158 ENDIF 158 159 159 IF( l_trdtrc ) CALL trd_trc( tra(:,:,:,jp_c14), 1, jptra_sms, kt ) ! save trends160 IF( l_trdtrc ) CALL trd_trc( tra(:,:,:,jp_c14), 1, jptra_sms, kt, Kmm ) ! save trends 160 161 ! 161 162 IF( ln_timing ) CALL timing_stop('trc_sms_c14') -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/CFC/trcsms_cfc.F90
r10425 r10966 54 54 CONTAINS 55 55 56 SUBROUTINE trc_sms_cfc( kt )56 SUBROUTINE trc_sms_cfc( kt, Kmm ) 57 57 !!---------------------------------------------------------------------- 58 58 !! *** ROUTINE trc_sms_cfc *** … … 71 71 !!---------------------------------------------------------------------- 72 72 INTEGER, INTENT(in) :: kt ! ocean time-step index 73 INTEGER, INTENT(in) :: Kmm ! ocean time level 73 74 ! 74 75 INTEGER :: ji, jj, jn, jl, jm … … 191 192 IF( l_trdtrc ) THEN 192 193 DO jn = jp_cfc0, jp_cfc1 193 CALL trd_trc( tra(:,:,:,jn), jn, jptra_sms, kt ) ! save trends194 CALL trd_trc( tra(:,:,:,jn), jn, jptra_sms, kt, Kmm ) ! save trends 194 195 END DO 195 196 END IF -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/MY_TRC/trcsms_my_trc.F90
r10963 r10966 63 63 DO jn = jp_myt0, jp_myt1 64 64 ztrmyt(:,:,:) = tra(:,:,:,jn) 65 CALL trd_trc( ztrmyt, jn, jptra_sms, kt ) ! save trends65 CALL trd_trc( ztrmyt, jn, jptra_sms, kt, Kmm ) ! save trends 66 66 END DO 67 67 DEALLOCATE( ztrmyt ) -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/PISCES/P2Z/p2zsms.F90
r10068 r10966 35 35 CONTAINS 36 36 37 SUBROUTINE p2z_sms( kt )37 SUBROUTINE p2z_sms( kt, Kmm ) 38 38 !!--------------------------------------------------------------------- 39 39 !! *** ROUTINE p2z_sms *** … … 45 45 !! -------------------------------------------------------------------- 46 46 INTEGER, INTENT( in ) :: kt ! ocean time-step index 47 INTEGER, INTENT( in ) :: Kmm ! ocean time level index 47 48 ! 48 49 INTEGER :: jn ! dummy loop index … … 58 59 IF( l_trdtrc ) THEN 59 60 DO jn = jp_pcs0, jp_pcs1 60 CALL trd_trc( tra(:,:,:,jn), jn, jptra_sms, kt ) ! save trends61 CALL trd_trc( tra(:,:,:,jn), jn, jptra_sms, kt, Kmm ) ! save trends 61 62 END DO 62 63 END IF -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/PISCES/P4Z/p4zbio.F90
r10227 r10966 45 45 CONTAINS 46 46 47 SUBROUTINE p4z_bio ( kt, knt )47 SUBROUTINE p4z_bio ( kt, knt, Kbb, Kmm ) 48 48 !!--------------------------------------------------------------------- 49 49 !! *** ROUTINE p4z_bio *** … … 56 56 !!--------------------------------------------------------------------- 57 57 INTEGER, INTENT(in) :: kt, knt 58 INTEGER, INTENT(in) :: Kbb, Kmm ! time level indices 58 59 ! 59 60 INTEGER :: ji, jj, jk, jn … … 78 79 79 80 CALL p4z_opt ( kt, knt ) ! Optic: PAR in the water column 80 CALL p4z_sink ( kt, knt ) ! vertical flux of particulate organic matter81 CALL p4z_sink ( kt, knt, Kbb, Kmm ) ! vertical flux of particulate organic matter 81 82 CALL p4z_fechem ( kt, knt ) ! Iron chemistry/scavenging 82 83 ! -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/PISCES/P4Z/p4zsink.F90
r10425 r10966 49 49 !!---------------------------------------------------------------------- 50 50 51 SUBROUTINE p4z_sink ( kt, knt )51 SUBROUTINE p4z_sink ( kt, knt, Kbb, Kmm ) 52 52 !!--------------------------------------------------------------------- 53 53 !! *** ROUTINE p4z_sink *** … … 59 59 !!--------------------------------------------------------------------- 60 60 INTEGER, INTENT(in) :: kt, knt 61 INTEGER, INTENT(in) :: Kbb, Kmm ! time level indices 61 62 INTEGER :: ji, jj, jk 62 63 CHARACTER (len=25) :: charout … … 104 105 ! Compute the sedimentation term using p4zsink2 for all the sinking particles 105 106 ! ----------------------------------------------------- 106 CALL trc_sink( kt, wsbio3, sinking , jppoc, rfact2 )107 CALL trc_sink( kt, wsbio3, sinkfer , jpsfe, rfact2 )108 CALL trc_sink( kt, wsbio4, sinking2, jpgoc, rfact2 )109 CALL trc_sink( kt, wsbio4, sinkfer2, jpbfe, rfact2 )110 CALL trc_sink( kt, wsbio4, sinksil , jpgsi, rfact2 )111 CALL trc_sink( kt, wsbio4, sinkcal , jpcal, rfact2 )107 CALL trc_sink( kt, Kbb, Kmm, wsbio3, sinking , jppoc, rfact2 ) 108 CALL trc_sink( kt, Kbb, Kmm, wsbio3, sinkfer , jpsfe, rfact2 ) 109 CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinking2, jpgoc, rfact2 ) 110 CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinkfer2, jpbfe, rfact2 ) 111 CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinksil , jpgsi, rfact2 ) 112 CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinkcal , jpcal, rfact2 ) 112 113 113 114 IF( ln_p5z ) THEN … … 119 120 ! Compute the sedimentation term using p4zsink2 for all the sinking particles 120 121 ! ----------------------------------------------------- 121 CALL trc_sink( kt, wsbio3, sinkingn , jppon, rfact2 )122 CALL trc_sink( kt, wsbio3, sinkingp , jppop, rfact2 )123 CALL trc_sink( kt, wsbio4, sinking2n, jpgon, rfact2 )124 CALL trc_sink( kt, wsbio4, sinking2p, jpgop, rfact2 )122 CALL trc_sink( kt, Kbb, Kmm, wsbio3, sinkingn , jppon, rfact2 ) 123 CALL trc_sink( kt, Kbb, Kmm, wsbio3, sinkingp , jppop, rfact2 ) 124 CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinking2n, jpgon, rfact2 ) 125 CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinking2p, jpgop, rfact2 ) 125 126 ENDIF 126 127 -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/PISCES/P4Z/p4zsms.F90
r10963 r10966 46 46 CONTAINS 47 47 48 SUBROUTINE p4z_sms( kt, K mm )48 SUBROUTINE p4z_sms( kt, Kbb, Kmm ) 49 49 !!--------------------------------------------------------------------- 50 50 !! *** ROUTINE p4z_sms *** … … 58 58 !!--------------------------------------------------------------------- 59 59 ! 60 INTEGER, INTENT( in ) :: kt ! ocean time-step index61 INTEGER, INTENT( in ) :: K mm ! time level index60 INTEGER, INTENT( in ) :: kt ! ocean time-step index 61 INTEGER, INTENT( in ) :: Kbb, Kmm ! time level index 62 62 !! 63 63 INTEGER :: ji, jj, jk, jnt, jn, jl … … 111 111 DO jnt = 1, nrdttrc ! Potential time splitting if requested 112 112 ! 113 CALL p4z_bio( kt, jnt ) ! Biology113 CALL p4z_bio( kt, jnt, Kbb, Kmm ) ! Biology 114 114 CALL p4z_lys( kt, jnt ) ! Compute CaCO3 saturation 115 115 CALL p4z_sed( kt, jnt ) ! Surface and Bottom boundary conditions … … 149 149 IF( l_trdtrc ) THEN 150 150 DO jn = jp_pcs0, jp_pcs1 151 CALL trd_trc( tra(:,:,:,jn), jn, jptra_sms, kt ) ! save trends151 CALL trd_trc( tra(:,:,:,jn), jn, jptra_sms, kt, Kmm ) ! save trends 152 152 END DO 153 153 END IF -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/PISCES/trcsms_pisces.F90
r10963 r10966 25 25 CONTAINS 26 26 27 SUBROUTINE trc_sms_pisces( kt, K mm )27 SUBROUTINE trc_sms_pisces( kt, Kbb, Kmm ) 28 28 !!--------------------------------------------------------------------- 29 29 !! *** ROUTINE trc_sms_pisces *** … … 34 34 !!--------------------------------------------------------------------- 35 35 ! 36 INTEGER, INTENT( in ) :: kt ! ocean time-step index37 INTEGER, INTENT( in ) :: K mm ! time level index36 INTEGER, INTENT( in ) :: kt ! ocean time-step index 37 INTEGER, INTENT( in ) :: Kbb, Kmm ! time level index 38 38 !!--------------------------------------------------------------------- 39 39 ! 40 IF( ln_p4z .OR. ln_p5z ) THEN ; CALL p4z_sms( kt, K mm ) ! PISCES41 ELSE ; CALL p2z_sms( kt ) ! LOBSTER40 IF( ln_p4z .OR. ln_p5z ) THEN ; CALL p4z_sms( kt, Kbb, Kmm ) ! PISCES 41 ELSE ; CALL p2z_sms( kt, Kmm ) ! LOBSTER 42 42 ENDIF 43 43 -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcadv.F90
r10954 r10966 74 74 !! ** Purpose : compute the ocean tracer advection trend. 75 75 !! 76 !! ** Method : - Update after tracers (tr a) with the advection term following nadv76 !! ** Method : - Update after tracers (tr(Krhs)) with the advection term following nadv 77 77 !!---------------------------------------------------------------------- 78 78 INTEGER , INTENT(in) :: kt ! ocean time-step index … … 82 82 INTEGER :: jk ! dummy loop index 83 83 CHARACTER (len=22) :: charout 84 REAL(wp), DIMENSION(jpi,jpj,jpk) :: zu n, zvn, zwn! effective velocity84 REAL(wp), DIMENSION(jpi,jpj,jpk) :: zuu, zvv, zww ! effective velocity 85 85 !!---------------------------------------------------------------------- 86 86 ! … … 89 89 ! !== effective transport ==! 90 90 IF( l_offline ) THEN 91 zu n(:,:,:) = un(:,:,:) ! already in (un,vn,wn)92 zv n(:,:,:) = vn(:,:,:)93 zw n(:,:,:) = wn(:,:,:)91 zuu(:,:,:) = uu(:,:,:,Kmm) ! already in (uu(Kmm),vv(Kmm),ww) 92 zvv(:,:,:) = vv(:,:,:,Kmm) 93 zww(:,:,:) = ww(:,:,:) 94 94 ELSE ! build the effective transport 95 zu n(:,:,jpk) = 0._wp96 zv n(:,:,jpk) = 0._wp97 zw n(:,:,jpk) = 0._wp95 zuu(:,:,jpk) = 0._wp 96 zvv(:,:,jpk) = 0._wp 97 zww(:,:,jpk) = 0._wp 98 98 IF( ln_wave .AND. ln_sdw ) THEN 99 99 DO jk = 1, jpkm1 ! eulerian transport + Stokes Drift 100 zu n(:,:,jk) = e2u (:,:) * e3u_n(:,:,jk) * ( un(:,:,jk) + usd(:,:,jk) )101 zv n(:,:,jk) = e1v (:,:) * e3v_n(:,:,jk) * ( vn(:,:,jk) + vsd(:,:,jk) )102 zw n(:,:,jk) = e1e2t(:,:) * ( wn(:,:,jk) + wsd(:,:,jk) )100 zuu(:,:,jk) = e2u (:,:) * e3u(:,:,jk,Kmm) * ( uu(:,:,jk,Kmm) + usd(:,:,jk) ) 101 zvv(:,:,jk) = e1v (:,:) * e3v(:,:,jk,Kmm) * ( vv(:,:,jk,Kmm) + vsd(:,:,jk) ) 102 zww(:,:,jk) = e1e2t(:,:) * ( ww(:,:,jk) + wsd(:,:,jk) ) 103 103 END DO 104 104 ELSE 105 105 DO jk = 1, jpkm1 106 zu n(:,:,jk) = e2u (:,:) * e3u_n(:,:,jk) * un(:,:,jk) ! eulerian transport107 zv n(:,:,jk) = e1v (:,:) * e3v_n(:,:,jk) * vn(:,:,jk)108 zw n(:,:,jk) = e1e2t(:,:) * wn(:,:,jk)106 zuu(:,:,jk) = e2u (:,:) * e3u(:,:,jk,Kmm) * uu(:,:,jk,Kmm) ! eulerian transport 107 zvv(:,:,jk) = e1v (:,:) * e3v(:,:,jk,Kmm) * vv(:,:,jk,Kmm) 108 zww(:,:,jk) = e1e2t(:,:) * ww(:,:,jk) 109 109 END DO 110 110 ENDIF 111 111 ! 112 112 IF( ln_vvl_ztilde .OR. ln_vvl_layer ) THEN ! add z-tilde and/or vvl corrections 113 zu n(:,:,:) = zun(:,:,:) + un_td(:,:,:)114 zv n(:,:,:) = zvn(:,:,:) + vn_td(:,:,:)113 zuu(:,:,:) = zuu(:,:,:) + un_td(:,:,:) 114 zvv(:,:,:) = zvv(:,:,:) + vn_td(:,:,:) 115 115 ENDIF 116 116 ! 117 117 IF( ln_ldfeiv .AND. .NOT. ln_traldf_triad ) & 118 & CALL ldf_eiv_trp( kt, nittrc000, zu n, zvn, zwn, 'TRC', Kmm, Krhs ) ! add the eiv transport119 ! 120 IF( ln_mle ) CALL tra_mle_trp( kt, nittrc000, zu n, zvn, zwn, 'TRC', Kmm ) ! add the mle transport118 & CALL ldf_eiv_trp( kt, nittrc000, zuu, zvv, zww, 'TRC', Kmm, Krhs ) ! add the eiv transport 119 ! 120 IF( ln_mle ) CALL tra_mle_trp( kt, nittrc000, zuu, zvv, zww, 'TRC', Kmm ) ! add the mle transport 121 121 ! 122 122 ENDIF … … 125 125 ! 126 126 CASE ( np_CEN ) ! Centered : 2nd / 4th order 127 CALL tra_adv_cen( kt, nittrc000,'TRC', zu n, zvn, zwn, Kmm, ptr, jptra, Krhs, nn_cen_h, nn_cen_v )127 CALL tra_adv_cen( kt, nittrc000,'TRC', zuu, zvv, zww, Kmm, ptr, jptra, Krhs, nn_cen_h, nn_cen_v ) 128 128 CASE ( np_FCT ) ! FCT : 2nd / 4th order 129 CALL tra_adv_fct( kt, nittrc000,'TRC', r2dttrc, zu n, zvn, zwn, Kbb, Kmm, ptr, jptra, Krhs, nn_fct_h, nn_fct_v )129 CALL tra_adv_fct( kt, nittrc000,'TRC', r2dttrc, zuu, zvv, zww, Kbb, Kmm, ptr, jptra, Krhs, nn_fct_h, nn_fct_v ) 130 130 CASE ( np_MUS ) ! MUSCL 131 CALL tra_adv_mus( kt, nittrc000,'TRC', r2dttrc, zu n, zvn, zwn, Kbb, Kmm, ptr, jptra, Krhs, ln_mus_ups )131 CALL tra_adv_mus( kt, nittrc000,'TRC', r2dttrc, zuu, zvv, zww, Kbb, Kmm, ptr, jptra, Krhs, ln_mus_ups ) 132 132 CASE ( np_UBS ) ! UBS 133 CALL tra_adv_ubs( kt, nittrc000,'TRC', r2dttrc, zu n, zvn, zwn, Kbb, Kmm, ptr, jptra, Krhs, nn_ubs_v )133 CALL tra_adv_ubs( kt, nittrc000,'TRC', r2dttrc, zuu, zvv, zww, Kbb, Kmm, ptr, jptra, Krhs, nn_ubs_v ) 134 134 CASE ( np_QCK ) ! QUICKEST 135 CALL tra_adv_qck( kt, nittrc000,'TRC', r2dttrc, zu n, zvn, zwn, Kbb, Kmm, ptr, jptra, Krhs )135 CALL tra_adv_qck( kt, nittrc000,'TRC', r2dttrc, zuu, zvv, zww, Kbb, Kmm, ptr, jptra, Krhs ) 136 136 ! 137 137 END SELECT … … 140 140 WRITE(charout, FMT="('adv ')") 141 141 CALL prt_ctl_trc_info(charout) 142 CALL prt_ctl_trc( tab4d=tr a, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )142 CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 143 143 END IF 144 144 ! -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcbbl.F90
r10954 r10966 61 61 IF( l_trdtrc ) THEN 62 62 ALLOCATE( ztrtrd(jpi,jpj,jpk,jptra) ) ! temporary save of trends 63 ztrtrd(:,:,:,:) = tr a(:,:,:,:)63 ztrtrd(:,:,:,:) = tr(:,:,:,:,Krhs) 64 64 ENDIF 65 65 … … 67 67 IF( nn_bbl_ldf == 1 ) THEN 68 68 ! 69 CALL tra_bbl_dif( tr b, tra, jptra, Kmm )69 CALL tra_bbl_dif( tr(:,:,:,:,Kbb), tr(:,:,:,:,Krhs), jptra, Kmm ) 70 70 IF( ln_ctl ) THEN 71 71 WRITE(charout, FMT="(' bbl_dif')") ; CALL prt_ctl_trc_info(charout) 72 CALL prt_ctl_trc( tab4d=tr a, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )72 CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 73 73 ENDIF 74 74 ! … … 78 78 IF( nn_bbl_adv /= 0 ) THEN 79 79 ! 80 CALL tra_bbl_adv( tr b, tra, jptra, Kmm )80 CALL tra_bbl_adv( tr(:,:,:,:,Kbb), tr(:,:,:,:,Krhs), jptra, Kmm ) 81 81 IF( ln_ctl ) THEN 82 82 WRITE(charout, FMT="(' bbl_adv')") ; CALL prt_ctl_trc_info(charout) 83 CALL prt_ctl_trc( tab4d=tr a, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )83 CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 84 84 ENDIF 85 85 ! … … 88 88 IF( l_trdtrc ) THEN ! save the horizontal diffusive trends for further diagnostics 89 89 DO jn = 1, jptra 90 ztrtrd(:,:,:,jn) = tr a(:,:,:,jn) - ztrtrd(:,:,:,jn)90 ztrtrd(:,:,:,jn) = tr(:,:,:,jn,Krhs) - ztrtrd(:,:,:,jn) 91 91 CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_bbl, ztrtrd(:,:,:,jn) ) 92 92 END DO -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcdmp.F90
r10963 r10966 63 63 64 64 65 SUBROUTINE trc_dmp( kt, K mm, Krhs )65 SUBROUTINE trc_dmp( kt, Kbb, Kmm, Krhs ) 66 66 !!---------------------------------------------------------------------- 67 67 !! *** ROUTINE trc_dmp *** … … 73 73 !! ** Method : Newtonian damping towards trdta computed 74 74 !! and add to the general tracer trends: 75 !! tr n = tra + restotr * (trdta - trb)75 !! tr(Kmm) = tr(Krhs) + restotr * (trdta - tr(Kbb)) 76 76 !! The trend is computed either throughout the water column 77 77 !! (nlmdmptr=0) or in area of weak vertical mixing (nlmdmptr=1) or 78 78 !! below the well mixed layer (nlmdmptr=2) 79 79 !! 80 !! ** Action : - update the tracer trends tr awith the newtonian80 !! ** Action : - update the tracer trends tr(:,:,:,:,Krhs) with the newtonian 81 81 !! damping trends. 82 82 !! - save the trends ('key_trdmxl_trc') 83 83 !!---------------------------------------------------------------------- 84 INTEGER, INTENT(in) :: kt ! ocean time-step index85 INTEGER, INTENT(in) :: K mm, Krhs ! time level indices84 INTEGER, INTENT(in) :: kt ! ocean time-step index 85 INTEGER, INTENT(in) :: Kbb, Kmm, Krhs ! time level indices 86 86 ! 87 87 INTEGER :: ji, jj, jk, jn, jl ! dummy loop indices … … 101 101 DO jn = 1, jptra ! tracer loop 102 102 ! ! =========== 103 IF( l_trdtrc ) ztrtrd(:,:,:) = tr a(:,:,:,jn) ! save trends103 IF( l_trdtrc ) ztrtrd(:,:,:) = tr(:,:,:,jn,Krhs) ! save trends 104 104 ! 105 105 IF( ln_trc_ini(jn) ) THEN ! update passive tracers arrays with input data read from file … … 114 114 DO jj = 2, jpjm1 115 115 DO ji = fs_2, fs_jpim1 ! vector opt. 116 tr a(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - trb(ji,jj,jk,jn) )116 tr(ji,jj,jk,jn,Krhs) = tr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - tr(ji,jj,jk,jn,Kbb) ) 117 117 END DO 118 118 END DO … … 124 124 DO ji = fs_2, fs_jpim1 ! vector opt. 125 125 IF( avt(ji,jj,jk) <= avt_c ) THEN 126 tr a(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - trb(ji,jj,jk,jn) )126 tr(ji,jj,jk,jn,Krhs) = tr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - tr(ji,jj,jk,jn,Kbb) ) 127 127 ENDIF 128 128 END DO … … 134 134 DO jj = 2, jpjm1 135 135 DO ji = fs_2, fs_jpim1 ! vector opt. 136 IF( gdept _n(ji,jj,jk) >= hmlp (ji,jj) ) THEN137 tr a(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - trb(ji,jj,jk,jn) )136 IF( gdept(ji,jj,jk,Kmm) >= hmlp (ji,jj) ) THEN 137 tr(ji,jj,jk,jn,Krhs) = tr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - tr(ji,jj,jk,jn,Kbb) ) 138 138 END IF 139 139 END DO … … 146 146 ! 147 147 IF( l_trdtrc ) THEN 148 ztrtrd(:,:,:) = tr a(:,:,:,jn) - ztrtrd(:,:,:)148 ztrtrd(:,:,:) = tr(:,:,:,jn,Krhs) - ztrtrd(:,:,:) 149 149 CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_dmp, ztrtrd ) 150 150 END IF … … 160 160 WRITE(charout, FMT="('dmp ')") 161 161 CALL prt_ctl_trc_info(charout) 162 CALL prt_ctl_trc( tab4d=tr a, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )162 CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 163 163 ENDIF 164 164 ! … … 225 225 226 226 227 SUBROUTINE trc_dmp_clo( kt, K mm )227 SUBROUTINE trc_dmp_clo( kt, Kbb, Kmm ) 228 228 !!--------------------------------------------------------------------- 229 229 !! *** ROUTINE trc_dmp_clo *** … … 237 237 !! nctsi2(), nctsj2() : north-east Closed sea limits (i,j) 238 238 !!---------------------------------------------------------------------- 239 INTEGER, INTENT( in ) :: kt ! ocean time-step index240 INTEGER, INTENT( in ) :: K mm ! time level indices239 INTEGER, INTENT( in ) :: kt ! ocean time-step index 240 INTEGER, INTENT( in ) :: Kbb, Kmm ! time level indices 241 241 ! 242 242 INTEGER :: ji , jj, jk, jn, jl, jc ! dummy loop indicesa … … 361 361 DO jj = nctsj1(jc), nctsj2(jc) 362 362 DO ji = nctsi1(jc), nctsi2(jc) 363 tr n(ji,jj,jk,jn) = ztrcdta(ji,jj,jk)364 tr b(ji,jj,jk,jn) = trn(ji,jj,jk,jn)363 tr(ji,jj,jk,jn,Kmm) = ztrcdta(ji,jj,jk) 364 tr(ji,jj,jk,jn,Kbb) = tr(ji,jj,jk,jn,Kmm) 365 365 END DO 366 366 END DO -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcldf.F90
r10954 r10966 51 51 CONTAINS 52 52 53 SUBROUTINE trc_ldf( kt, K mm, Krhs )53 SUBROUTINE trc_ldf( kt, Kbb, Kmm, Krhs ) 54 54 !!---------------------------------------------------------------------- 55 55 !! *** ROUTINE tra_ldf *** … … 58 58 !! 59 59 !!---------------------------------------------------------------------- 60 INTEGER, INTENT( in ) :: kt ! ocean time-step index61 INTEGER, INTENT( in ) :: K mm, Krhs ! ocean time-level index60 INTEGER, INTENT( in ) :: kt ! ocean time-step index 61 INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs ! ocean time-level index 62 62 ! 63 63 INTEGER :: ji, jj, jk, jn … … 74 74 IF( l_trdtrc ) THEN 75 75 ALLOCATE( ztrtrd(jpi,jpj,jpk,jptra) ) 76 ztrtrd(:,:,:,:) = tr a(:,:,:,:)76 ztrtrd(:,:,:,:) = tr(:,:,:,:,Krhs) 77 77 ENDIF 78 78 ! !* set the lateral diffusivity coef. for passive tracer … … 83 83 DO jj = 1, jpj 84 84 DO ji = 1, jpi 85 IF( gdept _n(ji,jj,jk) > 200. .AND. gphit(ji,jj) < 5. .AND. gphit(ji,jj) > -5. ) THEN86 zdep = MAX( gdept _n(ji,jj,jk) - 1000., 0. ) / 1000.85 IF( gdept(ji,jj,jk,Kmm) > 200. .AND. gphit(ji,jj) < 5. .AND. gphit(ji,jj) > -5. ) THEN 86 zdep = MAX( gdept(ji,jj,jk,Kmm) - 1000., 0. ) / 1000. 87 87 zahu(ji,jj,jk) = zahu(ji,jj,jk) * MAX( 1., rn_fact_lap * EXP( -zdep ) ) 88 88 ENDIF … … 93 93 SELECT CASE ( nldf_trc ) !* compute lateral mixing trend and add it to the general trend 94 94 ! 95 CASE ( np_lap ) ! iso-level laplacian 96 CALL tra_ldf_lap ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, tra, jptra, 1 , Kmm ) 97 CASE ( np_lap_i ) ! laplacian : standard iso-neutral operator (Madec) 98 CALL tra_ldf_iso ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra, 1 , Kmm ) 99 CASE ( np_lap_it ) ! laplacian : triad iso-neutral operator (griffies) 100 CALL tra_ldf_triad( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra, 1 , Kmm ) 101 CASE ( np_blp , np_blp_i , np_blp_it ) ! bilaplacian: all operator (iso-level, -neutral) 102 CALL tra_ldf_blp ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb , tra, jptra, nldf_trc, Kmm ) 95 CASE ( np_lap ) ! iso-level laplacian 96 CALL tra_ldf_lap ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, & 97 & tr(:,:,:,:,Kbb), tr(:,:,:,:,Krhs), jptra, 1 , Kmm ) 98 CASE ( np_lap_i ) ! laplacian : standard iso-neutral operator (Madec) 99 CALL tra_ldf_iso ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, & 100 & tr(:,:,:,:,Kbb), tr(:,:,:,:,Kbb), tr(:,:,:,:,Krhs), jptra, 1 , Kmm ) 101 CASE ( np_lap_it ) ! laplacian : triad iso-neutral operator (griffies) 102 CALL tra_ldf_triad( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, & 103 & tr(:,:,:,:,Kbb), tr(:,:,:,:,Kbb), tr(:,:,:,:,Krhs), jptra, 1 , Kmm ) 104 CASE ( np_blp , np_blp_i , np_blp_it ) ! bilaplacian: all operator (iso-level, -neutral) 105 CALL tra_ldf_blp ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, & 106 & tr(:,:,:,:,Kbb) , tr(:,:,:,:,Krhs), jptra, nldf_trc, Kmm ) 103 107 END SELECT 104 108 ! 105 109 IF( l_trdtrc ) THEN ! send the trends for further diagnostics 106 110 DO jn = 1, jptra 107 ztrtrd(:,:,:,jn) = tr a(:,:,:,jn) - ztrtrd(:,:,:,jn)111 ztrtrd(:,:,:,jn) = tr(:,:,:,jn,Krhs) - ztrtrd(:,:,:,jn) 108 112 CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_ldf, ztrtrd(:,:,:,jn) ) 109 113 END DO … … 114 118 WRITE(charout, FMT="('ldf ')") 115 119 CALL prt_ctl_trc_info(charout) 116 CALL prt_ctl_trc( tab4d=tr a, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )120 CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 117 121 ENDIF 118 122 ! … … 168 172 IF( ln_trcldf_OFF ) THEN ; nldf_trc = np_no_ldf ; ioptio = ioptio + 1 ; ENDIF 169 173 IF( ln_trcldf_tra ) THEN ; nldf_trc = nldf_tra ; ioptio = ioptio + 1 ; ENDIF 170 IF( ioptio /= 1 ) CALL ctl_stop( 'trc_ldf_ini: use ONE of the 2 operator options ( NONE/tra)' )174 IF( ioptio /= 1 ) CALL ctl_stop( 'trc_ldf_ini: use ONE of the 2 operator options (OFF/tra)' ) 171 175 172 176 ! ! multiplier : passive/active tracers ration -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcnxt.F90
r10963 r10966 61 61 !! next time-step from their temporal trends and swap the fields. 62 62 !! 63 !! ** Method : Apply lateral boundary conditions on (u a,va) through63 !! ** Method : Apply lateral boundary conditions on (uu(Krhs),vv(Krhs)) through 64 64 !! call to lbc_lnk routine 65 65 !! default: 66 66 !! arrays swap 67 !! (tr n) = (tra) ; (tra) = (0,0)68 !! (tr b) = (trn)67 !! (tr(Kmm)) = (tr(Krhs)) ; (tr(Krhs)) = (0,0) 68 !! (tr(Kbb)) = (tr(Kmm)) 69 69 !! 70 70 !! For Arakawa or TVD Scheme : 71 !! A Asselin time filter applied on now tracers (tr n) to avoid71 !! A Asselin time filter applied on now tracers (tr(:,:,:,:,Kmm)) to avoid 72 72 !! the divergence of two consecutive time-steps and tr arrays 73 73 !! to prepare the next time_step: 74 !! (tr b) = (trn) + atfp [ (trb) + (tra) - 2 (trn) ]75 !! (tr n) = (tra) ; (tra) = (0,0)76 !! 77 !! 78 !! ** Action : - update tr b, trn74 !! (tr(Kbb)) = (tr(Kmm)) + atfp [ (tr(Kbb)) + (tr(Krhs)) - 2 (tr(Kmm)) ] 75 !! (tr(Kmm)) = (tr(Krhs)) ; (tr(Krhs)) = (0,0) 76 !! 77 !! 78 !! ** Action : - update tr(Kbb), tr(Kmm) 79 79 !!---------------------------------------------------------------------- 80 80 INTEGER, INTENT( in ) :: kt ! ocean time-step index … … 98 98 #endif 99 99 ! Update after tracer on domain lateral boundaries 100 CALL lbc_lnk( 'trcnxt', tr a(:,:,:,:), 'T', 1. )100 CALL lbc_lnk( 'trcnxt', tr(:,:,:,:,Krhs), 'T', 1. ) 101 101 102 102 IF( ln_bdy ) CALL trc_bdy( kt, Kbb, Kmm, Krhs ) … … 113 113 ! total trend for the non-time-filtered variables. 114 114 zfact = 1.0 / rdttrc 115 ! G Nurser 23 Mar 2017. Recalculate trend as Delta(e3t*T)/e3tn; e3tn cancel from ts nterms115 ! G Nurser 23 Mar 2017. Recalculate trend as Delta(e3t*T)/e3tn; e3tn cancel from ts(Kmm) terms 116 116 IF( ln_linssh ) THEN ! linear sea surface height only 117 117 DO jn = 1, jptra 118 118 DO jk = 1, jpkm1 119 ztrdt(:,:,jk,jn) = ( tr a(:,:,jk,jn)*e3t_a(:,:,jk) / e3t_n(:,:,jk) - trn(:,:,jk,jn)) * zfact119 ztrdt(:,:,jk,jn) = ( tr(:,:,jk,jn,Krhs)*e3t(:,:,jk,Krhs) / e3t(:,:,jk,Kmm) - tr(:,:,jk,jn,Kmm)) * zfact 120 120 END DO 121 121 END DO … … 123 123 DO jn = 1, jptra 124 124 DO jk = 1, jpkm1 125 ztrdt(:,:,jk,jn) = ( tr a(:,:,jk,jn) - trn(:,:,jk,jn) ) * zfact125 ztrdt(:,:,jk,jn) = ( tr(:,:,jk,jn,Krhs) - tr(:,:,jk,jn,Kmm) ) * zfact 126 126 END DO 127 127 END DO … … 135 135 ! Store now fields before applying the Asselin filter 136 136 ! in order to calculate Asselin filter trend later. 137 ztrdt(:,:,:,:) = tr n(:,:,:,:)137 ztrdt(:,:,:,:) = tr(:,:,:,:,Kmm) 138 138 ENDIF 139 139 … … 143 143 DO jn = 1, jptra 144 144 DO jk = 1, jpkm1 145 tr n(:,:,jk,jn) = tra(:,:,jk,jn)146 tr b(:,:,jk,jn) = trn(:,:,jk,jn)145 tr(:,:,jk,jn,Kmm) = tr(:,:,jk,jn,Krhs) 146 tr(:,:,jk,jn,Kbb) = tr(:,:,jk,jn,Kmm) 147 147 END DO 148 148 END DO … … 157 157 ELSE 158 158 IF( .NOT. l_offline ) THEN ! Leap-Frog + Asselin filter time stepping 159 IF( ln_linssh ) THEN ; CALL tra_nxt_fix( kt, Kmm, nittrc000, 'TRC', trb, trn, tra, jptra ) ! linear ssh 160 ELSE ; CALL tra_nxt_vvl( kt, Kbb, Kmm, Krhs, nittrc000, rdttrc, 'TRC', trb, trn, tra, & 161 & sbc_trc, sbc_trc_b, jptra ) ! non-linear ssh 159 IF( ln_linssh ) THEN ; CALL tra_nxt_fix( kt, Kmm, nittrc000, 'TRC', & 160 & tr(:,:,:,:,Kbb), tr(:,:,:,:,Kmm), tr(:,:,:,:,Krhs), jptra ) ! linear ssh 161 ELSE ; CALL tra_nxt_vvl( kt, Kbb, Kmm, Krhs, nittrc000, rdttrc, 'TRC', & 162 & tr(:,:,:,:,Kbb), tr(:,:,:,:,Kmm), tr(:,:,:,:,Krhs), & 163 & sbc_trc, sbc_trc_b, jptra ) ! non-linear ssh 162 164 ENDIF 163 165 ELSE 164 CALL trc_nxt_off( kt ) ! offline165 ENDIF 166 ! 167 CALL lbc_lnk_multi( 'trcnxt', tr b(:,:,:,:), 'T', 1._wp, trn(:,:,:,:), 'T', 1._wp, tra(:,:,:,:), 'T', 1._wp )166 CALL trc_nxt_off( kt, Kbb, Kmm, Krhs ) ! offline 167 ENDIF 168 ! 169 CALL lbc_lnk_multi( 'trcnxt', tr(:,:,:,:,Kbb), 'T', 1._wp, tr(:,:,:,:,Kmm), 'T', 1._wp, tr(:,:,:,:,Krhs), 'T', 1._wp ) 168 170 ENDIF 169 171 ! … … 172 174 DO jk = 1, jpkm1 173 175 zfact = 1._wp / r2dttrc 174 ztrdt(:,:,jk,jn) = ( tr b(:,:,jk,jn) - ztrdt(:,:,jk,jn) ) * zfact176 ztrdt(:,:,jk,jn) = ( tr(:,:,jk,jn,Kbb) - ztrdt(:,:,jk,jn) ) * zfact 175 177 END DO 176 178 CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_atf, ztrdt(:,:,:,jn) ) … … 182 184 WRITE(charout, FMT="('nxt')") 183 185 CALL prt_ctl_trc_info(charout) 184 CALL prt_ctl_trc(tab4d=tr n, mask=tmask, clinfo=ctrcnm)186 CALL prt_ctl_trc(tab4d=tr(:,:,:,:,Kmm), mask=tmask, clinfo=ctrcnm) 185 187 ENDIF 186 188 ! … … 190 192 191 193 192 SUBROUTINE trc_nxt_off( kt )194 SUBROUTINE trc_nxt_off( kt, Kbb, Kmm, Krhs ) 193 195 !!---------------------------------------------------------------------- 194 196 !! *** ROUTINE tra_nxt_vvl *** … … 204 206 !! This can be summurized for tempearture as: 205 207 !! ztm = ( e3t_n*tn + rbcp*[ e3t_b*tb - 2 e3t_n*tn + e3t_a*ta ] ) ln_dynhpg_imp = T 206 !! /( e3t _n + rbcp*[ e3t_b - 2 e3t_n + e3t_a] )208 !! /( e3t(:,:,:,Kmm) + rbcp*[ e3t(:,:,:,Kbb) - 2 e3t(:,:,:,Kmm) + e3t(:,:,:,Krhs) ] ) 207 209 !! ztm = 0 otherwise 208 210 !! tb = ( e3t_n*tn + atfp*[ e3t_b*tb - 2 e3t_n*tn + e3t_a*ta ] ) 209 !! /( e3t _n + atfp*[ e3t_b - 2 e3t_n + e3t_a] )211 !! /( e3t(:,:,:,Kmm) + atfp*[ e3t(:,:,:,Kbb) - 2 e3t(:,:,:,Kmm) + e3t(:,:,:,Krhs) ] ) 210 212 !! tn = ta 211 213 !! ta = zt (NB: reset to 0 after eos_bn2 call) … … 214 216 !! - (ta,sa) time averaged (t,s) (ln_dynhpg_imp = T) 215 217 !!---------------------------------------------------------------------- 216 INTEGER , INTENT(in ) :: kt ! ocean time-step index 218 INTEGER, INTENT(in ) :: kt ! ocean time-step index 219 INTEGER, INTENT(in ) :: Kbb, Kmm, Krhs ! time level indices 217 220 !! 218 221 INTEGER :: ji, jj, jk, jn ! dummy loop indices … … 236 239 DO jj = 1, jpj 237 240 DO ji = 1, jpi 238 ze3t_b = e3t _b(ji,jj,jk)239 ze3t_n = e3t _n(ji,jj,jk)240 ze3t_a = e3t _a(ji,jj,jk)241 ze3t_b = e3t(ji,jj,jk,Kbb) 242 ze3t_n = e3t(ji,jj,jk,Kmm) 243 ze3t_a = e3t(ji,jj,jk,Krhs) 241 244 ! ! tracer content at Before, now and after 242 ztc_b = tr b(ji,jj,jk,jn)* ze3t_b243 ztc_n = tr n(ji,jj,jk,jn)* ze3t_n244 ztc_a = tr a(ji,jj,jk,jn) * ze3t_a245 ztc_b = tr(ji,jj,jk,jn,Kbb) * ze3t_b 246 ztc_n = tr(ji,jj,jk,jn,Kmm) * ze3t_n 247 ztc_a = tr(ji,jj,jk,jn,Krhs) * ze3t_a 245 248 ! 246 249 ze3t_d = ze3t_a - 2. * ze3t_n + ze3t_b … … 256 259 257 260 ze3t_f = 1.e0 / ze3t_f 258 tr b(ji,jj,jk,jn) = ztc_f * ze3t_f ! ptb <-- ptnfiltered259 tr n(ji,jj,jk,jn) = tra(ji,jj,jk,jn) ! ptn <-- pta261 tr(ji,jj,jk,jn,Kbb) = ztc_f * ze3t_f ! pt(:,:,:,:,Kbb) <-- pt(:,:,:,:,Kmm) filtered 262 tr(ji,jj,jk,jn,Kmm) = tr(ji,jj,jk,jn,Krhs) ! pt(:,:,:,:,Kmm) <-- pt(:,:,:,:,Krhs) 260 263 ! 261 264 END DO … … 272 275 !!---------------------------------------------------------------------- 273 276 CONTAINS 274 SUBROUTINE trc_nxt( kt )277 SUBROUTINE trc_nxt( kt, Kbb, Kmm, Krhs ) 275 278 INTEGER, INTENT(in) :: kt 279 INTEGER, INTENT(in) :: Kbb, Kmm, Krhs ! time level indices 276 280 WRITE(*,*) 'trc_nxt: You should not have seen this print! error?', kt 277 281 END SUBROUTINE trc_nxt -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcrad.F90
r10946 r10966 37 37 CONTAINS 38 38 39 SUBROUTINE trc_rad( kt, K mm, Krhs )39 SUBROUTINE trc_rad( kt, Kbb, Kmm, Krhs ) 40 40 !!---------------------------------------------------------------------- 41 41 !! *** ROUTINE trc_rad *** … … 52 52 !! (the total CFC content is not strictly preserved) 53 53 !!---------------------------------------------------------------------- 54 INTEGER, INTENT(in) :: kt ! ocean time-step index55 INTEGER, INTENT(in) :: K mm, Krhs ! time level indices54 INTEGER, INTENT(in) :: kt ! ocean time-step index 55 INTEGER, INTENT(in) :: Kbb, Kmm, Krhs ! time level indices 56 56 ! 57 57 CHARACTER (len=22) :: charout … … 60 60 IF( ln_timing ) CALL timing_start('trc_rad') 61 61 ! 62 IF( ln_age ) CALL trc_rad_sms( kt, Kmm, Krhs, tr b, trn, jp_age , jp_age ) ! AGE63 IF( ll_cfc ) CALL trc_rad_sms( kt, Kmm, Krhs, tr b, trn, jp_cfc0, jp_cfc1 ) ! CFC model64 IF( ln_c14 ) CALL trc_rad_sms( kt, Kmm, Krhs, tr b, trn, jp_c14 , jp_c14 ) ! C1465 IF( ln_pisces ) CALL trc_rad_sms( kt, Kmm, Krhs, tr b, trn, jp_pcs0, jp_pcs1, cpreserv='Y' ) ! PISCES model66 IF( ln_my_trc ) CALL trc_rad_sms( kt, Kmm, Krhs, tr b, trn, jp_myt0, jp_myt1 ) ! MY_TRC model62 IF( ln_age ) CALL trc_rad_sms( kt, Kmm, Krhs, tr(:,:,:,:,Kbb), tr(:,:,:,:,Kmm), jp_age , jp_age ) ! AGE 63 IF( ll_cfc ) CALL trc_rad_sms( kt, Kmm, Krhs, tr(:,:,:,:,Kbb), tr(:,:,:,:,Kmm), jp_cfc0, jp_cfc1 ) ! CFC model 64 IF( ln_c14 ) CALL trc_rad_sms( kt, Kmm, Krhs, tr(:,:,:,:,Kbb), tr(:,:,:,:,Kmm), jp_c14 , jp_c14 ) ! C14 65 IF( ln_pisces ) CALL trc_rad_sms( kt, Kmm, Krhs, tr(:,:,:,:,Kbb), tr(:,:,:,:,Kmm), jp_pcs0, jp_pcs1, cpreserv='Y' ) ! PISCES model 66 IF( ln_my_trc ) CALL trc_rad_sms( kt, Kmm, Krhs, tr(:,:,:,:,Kbb), tr(:,:,:,:,Kmm), jp_myt0, jp_myt1 ) ! MY_TRC model 67 67 ! 68 68 IF(ln_ctl) THEN ! print mean trends (used for debugging) 69 69 WRITE(charout, FMT="('rad')") 70 70 CALL prt_ctl_trc_info( charout ) 71 CALL prt_ctl_trc( tab4d=tr n, mask=tmask, clinfo=ctrcnm )71 CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Kmm), mask=tmask, clinfo=ctrcnm ) 72 72 ENDIF 73 73 ! … … 160 160 DO jn = jp_sms0, jp_sms1 161 161 ! 162 IF( l_trdtrc ) ztrtrd(:,:,:) = ptrb(:,:,:,jn) ! save input tr bfor trend computation162 IF( l_trdtrc ) ztrtrd(:,:,:) = ptrb(:,:,:,jn) ! save input tr(:,:,:,:,Kbb) for trend computation 163 163 ! 164 164 DO jk = 1, jpkm1 … … 210 210 DO jn = jp_sms0, jp_sms1 211 211 ! 212 IF( l_trdtrc ) ztrtrd(:,:,:) = ptrn(:,:,:,jn) ! save input tr bfor trend computation212 IF( l_trdtrc ) ztrtrd(:,:,:) = ptrn(:,:,:,jn) ! save input tr for trend computation 213 213 ! 214 214 DO jk = 1, jpkm1 … … 257 257 DO jn = jp_sms0, jp_sms1 258 258 ! 259 IF( l_trdtrc ) ztrtrd(:,:,:) = ptrb(:,:,:,jn) ! save input tr bfor trend computation259 IF( l_trdtrc ) ztrtrd(:,:,:) = ptrb(:,:,:,jn) ! save input tr for trend computation 260 260 ! 261 261 WHERE( ptrb(:,:,:,jn) < 0. ) ptrb(:,:,:,jn) = 0. … … 266 266 ENDIF 267 267 ! 268 IF( l_trdtrc ) ztrtrd(:,:,:) = ptrn(:,:,:,jn) ! save input tr nfor trend computation268 IF( l_trdtrc ) ztrtrd(:,:,:) = ptrn(:,:,:,jn) ! save input tr for trend computation 269 269 ! 270 270 WHERE( ptrn(:,:,:,jn) < 0. ) ptrn(:,:,:,jn) = 0. … … 288 288 !!---------------------------------------------------------------------- 289 289 CONTAINS 290 SUBROUTINE trc_rad( kt ) ! Empty routine290 SUBROUTINE trc_rad( kt, Kbb, Kmm, Krhs ) ! Empty routine 291 291 INTEGER, INTENT(in) :: kt 292 INTEGER, INTENT(in) :: Kbb, Kmm, Krhs ! time level indices 292 293 WRITE(*,*) 'trc_rad: You should not have seen this print! error?', kt 293 294 END SUBROUTINE trc_rad -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcsbc.F90
r10946 r10966 49 49 !! The surface freshwater flux modify the ocean volume 50 50 !! and thus the concentration of a tracer as : 51 !! tr a = tra + emp * trn/ e3t for k=151 !! tr(Krhs) = tr(Krhs) + emp * tr(Kmm) / e3t for k=1 52 52 !! where emp, the surface freshwater budget (evaporation minus 53 53 !! precipitation ) given in kg/m2/s is divided 54 54 !! by 1035 kg/m3 (density of ocean water) to obtain m/s. 55 55 !! 56 !! ** Action : - Update the 1st level of tr awith the trend associated56 !! ** Action : - Update the 1st level of tr(:,:,:,:,Krhs) with the trend associated 57 57 !! with the tracer surface boundary condition 58 58 !! … … 103 103 ENDIF 104 104 105 ! Coupling online : river runoff is added to the horizontal divergence (hdiv n) in the subroutine sbc_rnf_div105 ! Coupling online : river runoff is added to the horizontal divergence (hdiv) in the subroutine sbc_rnf_div 106 106 ! one only consider the concentration/dilution effect due to evaporation minus precipitation + freezing/melting of sea-ice 107 107 ! Coupling offline : runoff are in emp which contains E-P-R … … 119 119 DO jj = 2, jpj 120 120 DO ji = fs_2, fs_jpim1 ! vector opt. 121 sbc_trc(ji,jj,jn) = zsfx(ji,jj) * r1_rau0 * tr n(ji,jj,1,jn)121 sbc_trc(ji,jj,jn) = zsfx(ji,jj) * r1_rau0 * tr(ji,jj,1,jn,Kmm) 122 122 END DO 123 123 END DO … … 129 129 DO jj = 2, jpj 130 130 DO ji = fs_2, fs_jpim1 ! vector opt. 131 zse3t = 1. / e3t _n(ji,jj,1)131 zse3t = 1. / e3t(ji,jj,1,Kmm) 132 132 ! tracer flux at the ice/ocean interface (tracer/m2/s) 133 133 zftra = - trc_i(ji,jj,jn) * fmmflx(ji,jj) ! uptake of tracer in the sea ice … … 138 138 ztfx = zftra ! net tracer flux 139 139 ! 140 zdtra = r1_rau0 * ( ztfx + zsfx(ji,jj) * tr n(ji,jj,1,jn) )140 zdtra = r1_rau0 * ( ztfx + zsfx(ji,jj) * tr(ji,jj,1,jn,Kmm) ) 141 141 IF ( zdtra < 0. ) THEN 142 zratio = -zdtra * zse3t * r2dttrc / ( tr n(ji,jj,1,jn) + zrtrn )142 zratio = -zdtra * zse3t * r2dttrc / ( tr(ji,jj,1,jn,Kmm) + zrtrn ) 143 143 zdtra = MIN(1.0, zratio) * zdtra ! avoid negative concentrations to arise 144 144 ENDIF … … 153 153 DO jn = 1, jptra 154 154 ! 155 IF( l_trdtrc ) ztrtrd(:,:,:) = tr a(:,:,:,jn) ! save trends155 IF( l_trdtrc ) ztrtrd(:,:,:) = tr(:,:,:,jn,Krhs) ! save trends 156 156 ! 157 157 DO jj = 2, jpj 158 158 DO ji = fs_2, fs_jpim1 ! vector opt. 159 zse3t = zfact / e3t _n(ji,jj,1)160 tr a(ji,jj,1,jn) = tra(ji,jj,1,jn) + ( sbc_trc_b(ji,jj,jn) + sbc_trc(ji,jj,jn) ) * zse3t159 zse3t = zfact / e3t(ji,jj,1,Kmm) 160 tr(ji,jj,1,jn,Krhs) = tr(ji,jj,1,jn,Krhs) + ( sbc_trc_b(ji,jj,jn) + sbc_trc(ji,jj,jn) ) * zse3t 161 161 END DO 162 162 END DO 163 163 ! 164 164 IF( l_trdtrc ) THEN 165 ztrtrd(:,:,:) = tr a(:,:,:,jn) - ztrtrd(:,:,:)165 ztrtrd(:,:,:) = tr(:,:,:,jn,Krhs) - ztrtrd(:,:,:) 166 166 CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_nsr, ztrtrd ) 167 167 END IF … … 184 184 IF( ln_ctl ) THEN 185 185 WRITE(charout, FMT="('sbc ')") ; CALL prt_ctl_trc_info(charout) 186 CALL prt_ctl_trc( tab4d=tr a, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )186 CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 187 187 ENDIF 188 188 IF( l_trdtrc ) DEALLOCATE( ztrtrd ) -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcsink.F90
r10376 r10966 35 35 !!---------------------------------------------------------------------- 36 36 37 SUBROUTINE trc_sink ( kt, pwsink, psinkflx, jp_tra, rsfact )37 SUBROUTINE trc_sink ( kt, Kbb, Kmm, pwsink, psinkflx, jp_tra, rsfact ) 38 38 !!--------------------------------------------------------------------- 39 39 !! *** ROUTINE trc_sink *** … … 45 45 !!--------------------------------------------------------------------- 46 46 INTEGER , INTENT(in) :: kt 47 INTEGER , INTENT(in) :: Kbb, Kmm 47 48 INTEGER , INTENT(in) :: jp_tra ! tracer index index 48 49 REAL(wp), INTENT(in) :: rsfact ! time step duration … … 75 76 DO jk = 1, jpkm1 76 77 IF( tmask(ji,jj,jk) == 1.0 ) THEN 77 zwsmax = 0.5 * e3t _n(ji,jj,jk) * rday / rsfact78 zwsmax = 0.5 * e3t(ji,jj,jk,Kmm) * rday / rsfact 78 79 iiter(ji,jj) = MAX( iiter(ji,jj), INT( pwsink(ji,jj,jk) / zwsmax ) ) 79 80 ENDIF … … 88 89 DO ji = 1, jpi 89 90 IF( tmask(ji,jj,jk) == 1 ) THEN 90 zwsmax = 0.5 * e3t _n(ji,jj,jk) * rday / rsfact91 zwsmax = 0.5 * e3t(ji,jj,jk,Kmm) * rday / rsfact 91 92 zwsink(ji,jj,jk) = MIN( pwsink(ji,jj,jk), zwsmax * REAL( iiter(ji,jj), wp ) ) 92 93 ENDIF … … 101 102 ! Compute the sedimentation term using trc_sink2 for the considered sinking particle 102 103 ! ----------------------------------------------------- 103 CALL trc_sink2( zwsink, psinkflx, jp_tra, iiter, rsfact )104 CALL trc_sink2( Kbb, Kmm, zwsink, psinkflx, jp_tra, iiter, rsfact ) 104 105 ! 105 106 IF( ln_timing ) CALL timing_stop('trc_sink') … … 107 108 END SUBROUTINE trc_sink 108 109 109 SUBROUTINE trc_sink2( pwsink, psinkflx, jp_tra, kiter, rsfact )110 SUBROUTINE trc_sink2( Kbb, Kmm, pwsink, psinkflx, jp_tra, kiter, rsfact ) 110 111 !!--------------------------------------------------------------------- 111 112 !! *** ROUTINE trc_sink2 *** … … 118 119 !! transport term, i.e. div(u*tra). 119 120 !!--------------------------------------------------------------------- 121 INTEGER, INTENT(in ) :: Kbb, Kmm ! time level indices 120 122 INTEGER, INTENT(in ) :: jp_tra ! tracer index index 121 123 REAL(wp), INTENT(in ) :: rsfact ! duration of time step … … 133 135 ztraz(:,:,:) = 0.e0 134 136 zakz (:,:,:) = 0.e0 135 ztrb (:,:,:) = tr b(:,:,:,jp_tra)137 ztrb (:,:,:) = tr(:,:,:,jp_tra,Kbb) 136 138 137 139 DO jk = 1, jpkm1 … … 150 152 ! 151 153 DO jk = 2, jpkm1 152 ztraz(ji,jj,jk) = ( tr b(ji,jj,jk-1,jp_tra) - trb(ji,jj,jk,jp_tra) ) * tmask(ji,jj,jk)154 ztraz(ji,jj,jk) = ( tr(ji,jj,jk-1,jp_tra,Kbb) - tr(ji,jj,jk,jp_tra,Kbb) ) * tmask(ji,jj,jk) 153 155 END DO 154 156 ztraz(ji,jj,1 ) = 0.0 … … 169 171 ! vertical advective flux 170 172 DO jk = 1, jpkm1 171 zigma = zwsink2(ji,jj,jk+1) * zstep / e3w _n(ji,jj,jk+1)173 zigma = zwsink2(ji,jj,jk+1) * zstep / e3w(ji,jj,jk+1,Kmm) 172 174 zew = zwsink2(ji,jj,jk+1) 173 psinkflx(ji,jj,jk+1) = -zew * ( tr b(ji,jj,jk,jp_tra) - 0.5 * ( 1 + zigma ) * zakz(ji,jj,jk) ) * zstep175 psinkflx(ji,jj,jk+1) = -zew * ( tr(ji,jj,jk,jp_tra,Kbb) - 0.5 * ( 1 + zigma ) * zakz(ji,jj,jk) ) * zstep 174 176 END DO 175 177 ! … … 179 181 180 182 DO jk=1,jpkm1 181 zflx = ( psinkflx(ji,jj,jk) - psinkflx(ji,jj,jk+1) ) / e3t _n(ji,jj,jk)182 tr b(ji,jj,jk,jp_tra) = trb(ji,jj,jk,jp_tra) + zflx183 zflx = ( psinkflx(ji,jj,jk) - psinkflx(ji,jj,jk+1) ) / e3t(ji,jj,jk,Kmm) 184 tr(ji,jj,jk,jp_tra,Kbb) = tr(ji,jj,jk,jp_tra,Kbb) + zflx 183 185 END DO 184 186 END DO … … 189 191 DO jj = 1,jpj 190 192 DO ji = 1, jpi 191 zflx = ( psinkflx(ji,jj,jk) - psinkflx(ji,jj,jk+1) ) / e3t _n(ji,jj,jk)193 zflx = ( psinkflx(ji,jj,jk) - psinkflx(ji,jj,jk+1) ) / e3t(ji,jj,jk,Kmm) 192 194 ztrb(ji,jj,jk) = ztrb(ji,jj,jk) + 2. * zflx 193 195 END DO … … 195 197 END DO 196 198 197 tr b(:,:,:,jp_tra) = ztrb(:,:,:)199 tr(:,:,:,jp_tra,Kbb) = ztrb(:,:,:) 198 200 psinkflx(:,:,:) = 2. * psinkflx(:,:,:) 199 201 ! -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trctrp.F90
r10963 r10966 61 61 IF( .NOT. lk_c1d ) THEN 62 62 ! 63 CALL trc_sbc ( kt, Kmm, Krhs ) ! surface boundary condition64 IF( ln_trabbl ) CALL trc_bbl ( kt, Kbb, Kmm, Krhs ) ! advective (and/or diffusive) bottom boundary layer scheme65 IF( ln_trcdmp ) CALL trc_dmp ( kt, K mm, Krhs ) ! internal damping trends66 IF( ln_bdy ) CALL trc_bdy_dmp( kt, Kbb, Krhs ) ! BDY damping trends67 CALL trc_adv ( kt, Kbb, Kmm, tr, Krhs ) 68 ! ! Partial top/bottom cell: GRADh( tr b)63 CALL trc_sbc ( kt, Kmm, Krhs ) ! surface boundary condition 64 IF( ln_trabbl ) CALL trc_bbl ( kt, Kbb, Kmm, Krhs ) ! advective (and/or diffusive) bottom boundary layer scheme 65 IF( ln_trcdmp ) CALL trc_dmp ( kt, Kbb, Kmm, Krhs ) ! internal damping trends 66 IF( ln_bdy ) CALL trc_bdy_dmp( kt, Kbb, Krhs ) ! BDY damping trends 67 CALL trc_adv ( kt, Kbb, Kmm, tr, Krhs ) ! horizontal & vertical advection 68 ! ! Partial top/bottom cell: GRADh( tr(Kbb) ) 69 69 IF( ln_zps ) THEN 70 IF( ln_isfcav ) THEN ; CALL zps_hde_isf( kt, Kmm, jptra, tr b, pgtu=gtru, pgtv=gtrv, pgtui=gtrui, pgtvi=gtrvi ) ! both top & bottom71 ELSE ; CALL zps_hde ( kt, Kmm, jptra, tr b, gtru, gtrv ) ! only bottom70 IF( ln_isfcav ) THEN ; CALL zps_hde_isf( kt, Kmm, jptra, tr(:,:,:,:,Kbb), pgtu=gtru, pgtv=gtrv, pgtui=gtrui, pgtvi=gtrvi ) ! both top & bottom 71 ELSE ; CALL zps_hde ( kt, Kmm, jptra, tr(:,:,:,:,Kbb), gtru, gtrv ) ! only bottom 72 72 ENDIF 73 73 ENDIF 74 74 ! 75 CALL trc_ldf ( kt, K mm, Krhs )! lateral mixing75 CALL trc_ldf ( kt, Kbb, Kmm, Krhs ) ! lateral mixing 76 76 #if defined key_agrif 77 77 IF(.NOT. Agrif_Root()) CALL Agrif_Sponge_trc ! tracers sponge 78 78 #endif 79 CALL trc_zdf ( kt, Kbb, Kmm, Krhs, tr, Kaa ) ! vert. mixing & after tracer ==> after80 CALL trc_nxt ( kt, Kbb, Kmm, Krhs ) ! tracer fields at next time step81 IF( ln_trcrad ) CALL trc_rad ( kt, K mm, Krhs )! Correct artificial negative concentrations82 IF( ln_trcdmp_clo ) CALL trc_dmp_clo( kt, K mm )! internal damping trends on closed seas only79 CALL trc_zdf ( kt, Kbb, Kmm, Krhs, tr, Kaa ) ! vert. mixing & after tracer ==> after 80 CALL trc_nxt ( kt, Kbb, Kmm, Krhs ) ! tracer fields at next time step 81 IF( ln_trcrad ) CALL trc_rad ( kt, Kbb, Kmm, Krhs ) ! Correct artificial negative concentrations 82 IF( ln_trcdmp_clo ) CALL trc_dmp_clo( kt, Kbb, Kmm ) ! internal damping trends on closed seas only 83 83 84 84 ! 85 85 ELSE ! 1D vertical configuration 86 CALL trc_sbc( kt, Kmm, Krhs ) ! surface boundary condition87 IF( ln_trcdmp ) CALL trc_dmp( kt, K mm, Krhs ) ! internal damping trends86 CALL trc_sbc( kt, Kmm, Krhs ) ! surface boundary condition 87 IF( ln_trcdmp ) CALL trc_dmp( kt, Kbb, Kmm, Krhs ) ! internal damping trends 88 88 CALL trc_zdf( kt, Kbb, Kmm, Krhs, tr, Kaa ) ! vert. mixing & after tracer ==> after 89 CALL trc_nxt( kt, Kbb, Kmm, Krhs ) ! tracer fields at next time step90 IF( ln_trcrad ) CALL trc_rad( kt, K mm, Krhs ) ! Correct artificial negative concentrations89 CALL trc_nxt( kt, Kbb, Kmm, Krhs ) ! tracer fields at next time step 90 IF( ln_trcrad ) CALL trc_rad( kt, Kbb, Kmm, Krhs ) ! Correct artificial negative concentrations 91 91 ! 92 92 END IF -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trczdf.F90
r10946 r10966 70 70 WRITE(charout, FMT="('zdf ')") 71 71 CALL prt_ctl_trc_info(charout) 72 CALL prt_ctl_trc( tab4d=tr a, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )72 CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Kaa), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 73 73 END IF 74 74 ! -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trdmxl_trc.F90
r10425 r10966 16 16 !! trd_mxl_trc_init : initialization step 17 17 !!---------------------------------------------------------------------- 18 USE trc ! tracer definitions (tr n, trb, tra,etc.)18 USE trc ! tracer definitions (tr etc.) 19 19 USE trc_oce, ONLY : nn_dttrc ! frequency of step on passive tracers 20 20 USE dom_oce ! domain definition … … 70 70 71 71 72 SUBROUTINE trd_mxl_trc_zint( ptrc_trdmxl, ktrd, ctype, kjn )72 SUBROUTINE trd_mxl_trc_zint( ptrc_trdmxl, ktrd, ctype, kjn, Kmm ) 73 73 !!---------------------------------------------------------------------- 74 74 !! *** ROUTINE trd_mxl_trc_zint *** … … 92 92 !! 93 93 INTEGER, INTENT( in ) :: ktrd, kjn ! ocean trend index and passive tracer rank 94 INTEGER, INTENT( in ) :: Kmm ! time level index 94 95 CHARACTER(len=2), INTENT( in ) :: ctype ! surface/bottom (2D) or interior (3D) physics 95 96 REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( in ) :: ptrc_trdmxl ! passive tracer trend … … 150 151 DO jj = 1, jpj 151 152 DO ji = 1, jpi 152 IF( jk - nmld_trc(ji,jj) < 0 ) wkx_trc(ji,jj,jk) = e3t _n(ji,jj,jk) * tmask(ji,jj,jk)153 IF( jk - nmld_trc(ji,jj) < 0 ) wkx_trc(ji,jj,jk) = e3t(ji,jj,jk,Kmm) * tmask(ji,jj,jk) 153 154 END DO 154 155 END DO … … 183 184 184 185 185 SUBROUTINE trd_mxl_trc( kt )186 SUBROUTINE trd_mxl_trc( kt, Kmm ) 186 187 !!---------------------------------------------------------------------- 187 188 !! *** ROUTINE trd_mxl_trc *** … … 232 233 ! 233 234 INTEGER, INTENT(in) :: kt ! ocean time-step index 235 INTEGER, INTENT(in) :: Kmm ! time level index 234 236 ! 235 237 INTEGER :: ji, jj, jk, jl, ik, it, itmod, jn … … 267 269 ik = nmld_trc(ji,jj) 268 270 IF( ln_trdtrc(jn) ) & 269 tmltrd_trc(ji,jj,jpmxl_trc_zdf,jn) = - avs(ji,jj,ik) / e3w _n(ji,jj,ik) * tmask(ji,jj,ik) &270 & * ( tr n(ji,jj,ik-1,jn) - trn(ji,jj,ik,jn) ) &271 tmltrd_trc(ji,jj,jpmxl_trc_zdf,jn) = - avs(ji,jj,ik) / e3w(ji,jj,ik,Kmm) * tmask(ji,jj,ik) & 272 & * ( tr(ji,jj,ik-1,jn,Kmm) - tr(ji,jj,ik,jn,Kmm) ) & 271 273 & / MAX( 1., rmld_trc(ji,jj) ) * tmask(ji,jj,1) 272 274 END DO … … 322 324 DO jn = 1, jptra 323 325 IF( ln_trdtrc(jn) ) & 324 tml_trc(:,:,jn) = tml_trc(:,:,jn) + wkx_trc(:,:,jk) * tr n(:,:,jk,jn)326 tml_trc(:,:,jn) = tml_trc(:,:,jn) + wkx_trc(:,:,jk) * tr(:,:,jk,jn,Kmm) 325 327 END DO 326 328 END DO … … 970 972 !!---------------------------------------------------------------------- 971 973 CONTAINS 972 SUBROUTINE trd_mxl_trc( kt ) ! Empty routine974 SUBROUTINE trd_mxl_trc( kt, Kmm ) ! Empty routine 973 975 INTEGER, INTENT( in) :: kt 976 INTEGER, INTENT( in) :: Kmm ! time level index 974 977 WRITE(*,*) 'trd_mxl_trc: You should not have seen this print! error?', kt 975 978 END SUBROUTINE trd_mxl_trc 976 SUBROUTINE trd_mxl_trc_zint( ptrc_trdmxl, ktrd, ctype, kjn )979 SUBROUTINE trd_mxl_trc_zint( ptrc_trdmxl, ktrd, ctype, kjn, Kmm ) 977 980 INTEGER , INTENT( in ) :: ktrd, kjn ! ocean trend index and passive tracer rank 981 INTEGER , INTENT( in ) :: Kmm ! time level index 978 982 CHARACTER(len=2) , INTENT( in ) :: ctype ! surface/bottom (2D) or interior (3D) physics 979 983 REAL, DIMENSION(:,:,:), INTENT( in ) :: ptrc_trdmxl ! passive trc trend -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trdtrc.F90
r10096 r10966 13 13 !! trdtrc : passive tracer trends 14 14 !!---------------------------------------------------------------------- 15 USE trc ! tracer definitions (tr n, trb, tra, etc.)15 USE trc ! tracer definitions (tr(:,:,:,:,Kmm), tr(:,:,:,:,Kbb), tr(:,:,:,:,Krhs), etc.) 16 16 USE trd_oce 17 17 USE trdtrc_oce ! definition of main arrays used for trends computations … … 32 32 CONTAINS 33 33 34 SUBROUTINE trd_trc( ptrtrd, kjn, ktrd, kt )34 SUBROUTINE trd_trc( ptrtrd, kjn, ktrd, kt, Kmm ) 35 35 !!---------------------------------------------------------------------- 36 36 !! *** ROUTINE trd_trc *** 37 37 !!---------------------------------------------------------------------- 38 38 INTEGER, INTENT( in ) :: kt ! time step 39 INTEGER, INTENT( in ) :: Kmm ! time level index 39 40 INTEGER, INTENT( in ) :: kjn ! tracer index 40 41 INTEGER, INTENT( in ) :: ktrd ! tracer trend index … … 56 57 ! 57 58 SELECT CASE ( ktrd ) 58 CASE ( jptra_xad ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_xad, '3D', kjn )59 CASE ( jptra_yad ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_yad, '3D', kjn )60 CASE ( jptra_zad ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_zad, '3D', kjn )61 CASE ( jptra_ldf ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_ldf, '3D', kjn )62 CASE ( jptra_bbl ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_bbl, '3D', kjn )59 CASE ( jptra_xad ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_xad, '3D', kjn, Kmm ) 60 CASE ( jptra_yad ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_yad, '3D', kjn, Kmm ) 61 CASE ( jptra_zad ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_zad, '3D', kjn, Kmm ) 62 CASE ( jptra_ldf ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_ldf, '3D', kjn, Kmm ) 63 CASE ( jptra_bbl ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_bbl, '3D', kjn, Kmm ) 63 64 CASE ( jptra_zdf ) 64 65 IF( ln_trcldf_iso ) THEN 65 CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_ldf, '3D', kjn )66 CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_ldf, '3D', kjn, Kmm ) 66 67 ELSE 67 CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_zdf, '3D', kjn )68 CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_zdf, '3D', kjn, Kmm ) 68 69 ENDIF 69 CASE ( jptra_dmp ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_dmp , '3D', kjn )70 CASE ( jptra_nsr ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_sbc , '2D', kjn )71 CASE ( jptra_sms ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_sms , '3D', kjn )72 CASE ( jptra_radb ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_radb, '3D', kjn )73 CASE ( jptra_radn ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_radn, '3D', kjn )74 CASE ( jptra_atf ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_atf , '3D', kjn )70 CASE ( jptra_dmp ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_dmp , '3D', kjn, Kmm ) 71 CASE ( jptra_nsr ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_sbc , '2D', kjn, Kmm ) 72 CASE ( jptra_sms ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_sms , '3D', kjn, Kmm ) 73 CASE ( jptra_radb ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_radb, '3D', kjn, Kmm ) 74 CASE ( jptra_radn ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_radn, '3D', kjn, Kmm ) 75 CASE ( jptra_atf ) ; CALL trd_mxl_trc_zint( ptrtrd, jpmxl_trc_atf , '3D', kjn, Kmm ) 75 76 END SELECT 76 77 ! … … 110 111 CONTAINS 111 112 112 SUBROUTINE trd_trc( ptrtrd, kjn, ktrd, kt )113 SUBROUTINE trd_trc( ptrtrd, kjn, ktrd, kt, Kmm ) 113 114 INTEGER , INTENT( in ) :: kt ! time step 115 INTEGER , INTENT( in ) :: Kmm ! time level index 114 116 INTEGER , INTENT( in ) :: kjn ! tracer index 115 117 INTEGER , INTENT( in ) :: ktrd ! tracer trend index -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/trcsms.F90
r10963 r10966 34 34 CONTAINS 35 35 36 SUBROUTINE trc_sms( kt, K mm , Krhs )36 SUBROUTINE trc_sms( kt, Kbb, Kmm , Krhs ) 37 37 !!--------------------------------------------------------------------- 38 38 !! *** ROUTINE trc_sms *** … … 43 43 !! ------------------------------------------------------------------------------------- 44 44 INTEGER, INTENT( in ) :: kt ! ocean time-step index 45 INTEGER, INTENT( in ) :: K mm, Krhs ! time level indices45 INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs ! time level indices 46 46 !! 47 47 CHARACTER (len=25) :: charout … … 50 50 IF( ln_timing ) CALL timing_start('trc_sms') 51 51 ! 52 IF( ln_pisces ) CALL trc_sms_pisces ( kt, K mm )! main program of PISCES53 IF( ll_cfc ) CALL trc_sms_cfc ( kt )! surface fluxes of CFC54 IF( ln_c14 ) CALL trc_sms_c14 ( kt )! surface fluxes of C1455 IF( ln_age ) CALL trc_sms_age ( kt )! Age tracer56 IF( ln_my_trc ) CALL trc_sms_my_trc ( kt, Kmm, Krhs ) ! MY_TRC tracers52 IF( ln_pisces ) CALL trc_sms_pisces ( kt, Kbb, Kmm ) ! main program of PISCES 53 IF( ll_cfc ) CALL trc_sms_cfc ( kt, Kmm ) ! surface fluxes of CFC 54 IF( ln_c14 ) CALL trc_sms_c14 ( kt, Kmm ) ! surface fluxes of C14 55 IF( ln_age ) CALL trc_sms_age ( kt, Kmm ) ! Age tracer 56 IF( ln_my_trc ) CALL trc_sms_my_trc ( kt, Kmm, Krhs ) ! MY_TRC tracers 57 57 58 58 IF(ln_ctl) THEN ! print mean trends (used for debugging) -
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/trcstp.F90
r10963 r10966 101 101 IF( lrst_trc ) CALL trc_rst_cal ( kt, 'WRITE' ) ! calendar 102 102 CALL trc_wri ( kt ) ! output of passive tracers with iom I/O manager 103 CALL trc_sms ( kt, 103 CALL trc_sms ( kt, Kbb, Kmm, Krhs ) ! tracers: sinks and sources 104 104 CALL trc_trp ( kt, Kbb, Kmm, Krhs, Kaa ) ! transport of passive tracers 105 105 IF( kt == nittrc000 ) THEN … … 108 108 ENDIF 109 109 IF( lrst_trc ) CALL trc_rst_wri ( kt, Kbb, Kmm, Krhs ) ! write tracer restart file 110 IF( lk_trdmxl_trc ) CALL trd_mxl_trc ( kt )! trends: Mixed-layer110 IF( lk_trdmxl_trc ) CALL trd_mxl_trc ( kt, Kmm ) ! trends: Mixed-layer 111 111 ! 112 112 IF( nn_dttrc /= 1 ) CALL trc_sub_reset( kt, Kbb, Kmm, Krhs ) ! resetting physical variables when sub-stepping
Note: See TracChangeset
for help on using the changeset viewer.