Changeset 5325
- Timestamp:
- 2015-06-01T12:00:26+02:00 (9 years ago)
- Location:
- branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC
- Files:
-
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC/PISCES/trcice_pisces.F90
r5195 r5325 20 20 USE phycst ! Ocean physics parameters 21 21 USE sms_pisces ! PISCES Source Minus Sink variables 22 USE p4zsbc23 22 USE in_out_manager 24 23 … … 58 57 !!---------------------------------------------------------------------- 59 58 60 ! --- Variable declarations --- !61 TYPE TRC_I_NML !--- Ice tracer namelist structure62 REAL(wp) :: trc_ratio ! ice-ocean trc ratio63 REAL(wp) :: trc_prescr ! prescribed ice trc cc64 CHARACTER(len=2) :: ctrc_o ! choice of ocean trc cc65 END TYPE66 67 !--- Variables extracted from the68 ! namelist69 REAL(wp), DIMENSION(24) :: trc_ice_ratio, & ! ice-ocean tracer ratio70 trc_ice_prescr ! prescribed ice trc cc71 CHARACTER(len=2), DIMENSION(24) :: cn_trc_o ! choice of ocean tracer cc72 73 59 !--- Dummy variables 74 60 REAL(wp), DIMENSION(jptra,2) & … … 83 69 !!---------------------------------------------------------------------- 84 70 85 ! --- Namelist declarations --- !86 87 ! Tracer structures for individual tracers88 TYPE(TRC_I_NML) :: sn_tri_dic, sn_tri_doc, sn_tri_tal, sn_tri_oxy, &89 sn_tri_cal, sn_tri_po4, sn_tri_poc, sn_tri_goc, &90 sn_tri_bfe, &91 sn_tri_num, &92 sn_tri_sil, sn_tri_dsi, sn_tri_gsi, &93 sn_tri_phy, sn_tri_dia, sn_tri_zoo, sn_tri_mes, &94 sn_tri_fer, sn_tri_sfe, sn_tri_dfe, sn_tri_nfe, &95 sn_tri_nch, sn_tri_dch, sn_tri_no3, sn_tri_nh496 97 98 NAMELIST/nampisice/ sn_tri_dic, sn_tri_doc, sn_tri_tal, sn_tri_oxy, &99 sn_tri_cal, sn_tri_po4, sn_tri_poc, sn_tri_goc, &100 sn_tri_bfe, &101 sn_tri_num, &102 sn_tri_sil, sn_tri_dsi, sn_tri_gsi, &103 sn_tri_phy, sn_tri_dia, sn_tri_zoo, sn_tri_mes, &104 sn_tri_fer, sn_tri_sfe, sn_tri_dfe, sn_tri_nfe, &105 sn_tri_nch, sn_tri_dch, sn_tri_no3, sn_tri_nh4106 107 !!----------------------------------------------------------------------108 109 71 IF(lwp) WRITE(numout,*) 110 72 IF(lwp) WRITE(numout,*) ' trc_ice_ini_pisces: Prescribed sea ice biogeochemistry ' 111 73 IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~' 112 113 !--------------------------------------------114 ! Read namelist115 !--------------------------------------------116 117 REWIND( numnatp_ref )118 READ( numnatp_ref, nampisice )119 120 REWIND( numnatp_cfg )121 READ( numnatp_cfg, nampisice )122 123 ! Assign namelist stuff124 trc_ice_ratio(jpdic) = sn_tri_dic%trc_ratio125 trc_ice_prescr(jpdic) = sn_tri_dic%trc_prescr126 cn_trc_o (jpdic) = sn_tri_dic%ctrc_o127 128 trc_ice_ratio(jpdoc) = sn_tri_doc%trc_ratio129 trc_ice_prescr(jpdoc) = sn_tri_doc%trc_prescr130 cn_trc_o (jpdoc) = sn_tri_doc%ctrc_o131 132 trc_ice_ratio(jptal) = sn_tri_tal%trc_ratio133 trc_ice_prescr(jptal) = sn_tri_tal%trc_prescr134 cn_trc_o (jptal) = sn_tri_tal%ctrc_o135 136 trc_ice_ratio(jpoxy) = sn_tri_oxy%trc_ratio137 trc_ice_prescr(jpoxy) = sn_tri_oxy%trc_prescr138 cn_trc_o (jpoxy) = sn_tri_oxy%ctrc_o139 140 trc_ice_ratio(jpcal) = sn_tri_cal%trc_ratio141 trc_ice_prescr(jpcal) = sn_tri_cal%trc_prescr142 cn_trc_o (jpcal) = sn_tri_cal%ctrc_o143 144 trc_ice_ratio(jppo4) = sn_tri_po4%trc_ratio145 trc_ice_prescr(jppo4) = sn_tri_po4%trc_prescr146 cn_trc_o (jppo4) = sn_tri_po4%ctrc_o147 148 trc_ice_ratio(jppoc) = sn_tri_poc%trc_ratio149 trc_ice_prescr(jppoc) = sn_tri_poc%trc_prescr150 cn_trc_o (jppoc) = sn_tri_poc%ctrc_o151 152 #if ! defined key_kriest153 trc_ice_ratio(jpgoc) = sn_tri_goc%trc_ratio154 trc_ice_prescr(jpgoc) = sn_tri_goc%trc_prescr155 cn_trc_o (jpgoc) = sn_tri_goc%ctrc_o156 157 trc_ice_ratio(jpbfe) = sn_tri_bfe%trc_ratio158 trc_ice_prescr(jpbfe) = sn_tri_bfe%trc_prescr159 cn_trc_o (jpbfe) = sn_tri_bfe%ctrc_o160 #else161 trc_ice_ratio(jpnum) = sn_tri_num%trc_ratio162 trc_ice_prescr(jpnum) = sn_tri_num%trc_prescr163 cn_trc_o (jpnum) = sn_tri_num%ctrc_o164 #endif165 166 trc_ice_ratio(jpsil) = sn_tri_sil%trc_ratio167 trc_ice_prescr(jpsil) = sn_tri_sil%trc_prescr168 cn_trc_o (jpsil) = sn_tri_sil%ctrc_o169 170 trc_ice_ratio(jpdsi) = sn_tri_dsi%trc_ratio171 trc_ice_prescr(jpdsi) = sn_tri_dsi%trc_prescr172 cn_trc_o (jpdsi) = sn_tri_dsi%ctrc_o173 174 trc_ice_ratio(jpgsi) = sn_tri_gsi%trc_ratio175 trc_ice_prescr(jpgsi) = sn_tri_gsi%trc_prescr176 cn_trc_o (jpgsi) = sn_tri_gsi%ctrc_o177 178 trc_ice_ratio(jpphy) = sn_tri_phy%trc_ratio179 trc_ice_prescr(jpphy) = sn_tri_phy%trc_prescr180 cn_trc_o (jpphy) = sn_tri_phy%ctrc_o181 182 trc_ice_ratio(jpdia) = sn_tri_dia%trc_ratio183 trc_ice_prescr(jpdia) = sn_tri_dia%trc_prescr184 cn_trc_o (jpdia) = sn_tri_dia%ctrc_o185 186 trc_ice_ratio(jpzoo) = sn_tri_zoo%trc_ratio187 trc_ice_prescr(jpzoo) = sn_tri_zoo%trc_prescr188 cn_trc_o (jpzoo) = sn_tri_zoo%ctrc_o189 190 trc_ice_ratio(jpmes) = sn_tri_mes%trc_ratio191 trc_ice_prescr(jpmes) = sn_tri_mes%trc_prescr192 cn_trc_o (jpmes) = sn_tri_mes%ctrc_o193 194 trc_ice_ratio(jpfer) = sn_tri_fer%trc_ratio195 trc_ice_prescr(jpfer) = sn_tri_fer%trc_prescr196 cn_trc_o (jpfer) = sn_tri_fer%ctrc_o197 198 trc_ice_ratio(jpsfe) = sn_tri_sfe%trc_ratio199 trc_ice_prescr(jpsfe) = sn_tri_sfe%trc_prescr200 cn_trc_o (jpsfe) = sn_tri_sfe%ctrc_o201 202 trc_ice_ratio(jpdfe) = sn_tri_dfe%trc_ratio203 trc_ice_prescr(jpdfe) = sn_tri_dfe%trc_prescr204 cn_trc_o (jpdfe) = sn_tri_dfe%ctrc_o205 206 trc_ice_ratio(jpnfe) = sn_tri_nfe%trc_ratio207 trc_ice_prescr(jpnfe) = sn_tri_nfe%trc_prescr208 cn_trc_o (jpnfe) = sn_tri_nfe%ctrc_o209 210 trc_ice_ratio(jpnch) = sn_tri_nch%trc_ratio211 trc_ice_prescr(jpnch) = sn_tri_nch%trc_prescr212 cn_trc_o (jpnch) = sn_tri_nch%ctrc_o213 214 trc_ice_ratio(jpdch) = sn_tri_dch%trc_ratio215 trc_ice_prescr(jpdch) = sn_tri_dch%trc_prescr216 cn_trc_o (jpdch) = sn_tri_dch%ctrc_o217 218 trc_ice_ratio(jpno3) = sn_tri_no3%trc_ratio219 trc_ice_prescr(jpno3) = sn_tri_no3%trc_prescr220 cn_trc_o (jpno3) = sn_tri_no3%ctrc_o221 222 trc_ice_ratio(jpnh4) = sn_tri_nh4%trc_ratio223 trc_ice_prescr(jpnh4) = sn_tri_nh4%trc_prescr224 cn_trc_o (jpnh4) = sn_tri_nh4%ctrc_o225 74 226 75 !-------------------------------------------- … … 367 216 zrs(2) = zsice_bal / zsoce_bal !! ice-ocean salinity ratio, Baltic case 368 217 369 DO jn = 1, jptra218 DO jn = jp_pcs0, jp_pcs1 370 219 IF ( trc_ice_ratio(jn) >= 0._wp ) zratio(jn,:) = trc_ice_ratio(jn) 371 220 IF ( trc_ice_ratio(jn) == -1._wp ) zratio(jn,:) = zrs(:) … … 376 225 ! Sea ice tracer concentrations 377 226 !------------------------------- 378 DO jn = 1, jptra227 DO jn = jp_pcs0, jp_pcs1 379 228 !-- Everywhere but in the Baltic 380 229 IF ( trc_ice_ratio(jn) >= -1._wp ) THEN !! no prescribed concentration … … 391 240 WHERE( 14._wp <= glamt(:,:) .AND. glamt(:,:) <= 32._wp .AND. & 392 241 54._wp <= gphit(:,:) .AND. gphit(:,:) <= 66._wp ) 393 trc_i(:,:,jn) = zratio(jn,2) * trc_o(:,:,jn)242 trc_i(:,:,jn) = zratio(jn,2) * trc_o(:,:,jn) 394 243 END WHERE 395 244 ELSE !! prescribed tracer concentration in ice 396 245 WHERE( 14._wp <= glamt(:,:) .AND. glamt(:,:) <= 32._wp .AND. & 397 246 54._wp <= gphit(:,:) .AND. gphit(:,:) <= 66._wp ) 398 trc_i(:,:,jn) = trc_ice_prescr(jn)247 trc_i(:,:,jn) = trc_ice_prescr(jn) 399 248 END WHERE 400 249 ENDIF ! trc_ice_ratio -
branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC/TRP/trcsbc.F90
r5195 r5325 28 28 29 29 PUBLIC trc_sbc ! routine called by step.F90 30 31 REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) :: r2dt ! vertical profile time-step, = 2 rdttra 30 32 31 33 !! * Substitutions … … 63 65 ! 64 66 INTEGER :: ji, jj, jn ! dummy loop indices 65 REAL(wp) :: zse3t 67 REAL(wp) :: zse3t, zrtrn, zratio ! temporary scalars 66 68 REAL(wp) :: zswitch, zftra, zcd, zdtra, ztfx, ztra ! temporary scalars 67 69 CHARACTER (len=22) :: charout … … 76 78 CALL wrk_alloc( jpi, jpj, zsfx ) 77 79 IF( l_trdtrc ) CALL wrk_alloc( jpi, jpj, jpk, ztrtrd ) 80 ! 81 zrtrn = 1.e-15_wp 78 82 79 83 SELECT CASE( nn_ice_embd ) ! levitating or embedded sea-ice option … … 82 86 ! (2) embedded sea-ice : salt and volume fluxes and pressure 83 87 END SELECT 88 89 IF( ln_top_euler) THEN 90 r2dt(:) = rdttrc(:) ! = rdttrc (use Euler time stepping) 91 ELSE 92 IF( neuler == 0 .AND. kt == nittrc000 ) THEN ! at nittrc000 93 r2dt(:) = rdttrc(:) ! = rdttrc (restarting with Euler time stepping) 94 ELSEIF( kt <= nittrc000 + 1 ) THEN ! at nittrc000 or nittrc000+1 95 r2dt(:) = 2. * rdttrc(:) ! = 2 rdttrc (leapfrog) 96 ENDIF 97 ENDIF 98 84 99 85 100 IF( kt == nittrc000 ) THEN … … 99 114 ENDIF 100 115 101 WRITE(numout,*) ' trc_sbc initial values', trn(3,2,1,2), trb(3,2,1,2), tra(3,2,1,2)102 103 116 ! 0. initialization 104 117 DO jn = 1, jptra … … 107 120 ! ! add the trend to the general tracer trend 108 121 109 IF ( nn_ice_tr == -1 ) THEN ! identical concentrations in ice and ocean (old code)122 IF ( nn_ice_tr == -1 ) THEN ! No tracers in sea ice (null concentration in sea ice) 110 123 111 124 DO jj = 2, jpj 112 125 DO ji = fs_2, fs_jpim1 ! vector opt. 113 126 zse3t = 1. / fse3t(ji,jj,1) 114 tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zsfx(ji,jj) * r1_rau0 * tr n(ji,jj,1,jn) * zse3t127 tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zsfx(ji,jj) * r1_rau0 * trb(ji,jj,1,jn) * zse3t 115 128 END DO 116 129 END DO … … 131 144 ztfx = zftra + zswitch * zcd ! net tracer flux (+C/D if no ice/ocean mass exchange) 132 145 133 zdtra = r1_rau0 * ( ztfx + zsfx(ji,jj) * trn(ji,jj,1,jn) ) * zse3t 134 tra(ji,jj,1,jn) = MAX( tra(ji,jj,1,jn) + zdtra, 0.) ! avoid integral ocean uptake if freezing (for iron) 146 zdtra = r1_rau0 * ( ztfx + zsfx(ji,jj) * trb(ji,jj,1,jn) ) * zse3t 147 IF ( zdtra < 0. ) THEN 148 zratio = -zdtra * r2dt(1) / ( trb(ji,jj,1,jn) + zrtrn ) 149 zdtra = MIN(1.0, zratio) * zdtra ! avoid negative concentrations to arise 150 ENDIF 151 152 tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zdtra 135 153 136 154 END DO -
branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC/trc.F90
r5184 r5325 65 65 INTEGER , PUBLIC :: nittrc000 !: first time step of passive tracers model 66 66 67 !! Information for the ice module for tracers 68 !! ------------------------------------------ 69 TYPE TRC_I_NML !--- Ice tracer namelist structure 70 REAL(wp) :: trc_ratio ! ice-ocean trc ratio 71 REAL(wp) :: trc_prescr ! prescribed ice trc cc 72 CHARACTER(len=2) :: ctrc_o ! choice of ocean trc cc 73 END TYPE 74 75 REAL(wp), DIMENSION(jptra), PUBLIC :: trc_ice_ratio, & ! ice-ocean tracer ratio 76 trc_ice_prescr ! prescribed ice trc cc 77 CHARACTER(len=2), DIMENSION(jptra), PUBLIC :: cn_trc_o ! choice of ocean tracer cc 78 67 79 !! information for outputs 68 80 !! -------------------------------------------------- -
branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC/trcice.F90
r5193 r5325 16 16 USE trc ! passive tracers common variables 17 17 ! USE trcrst ! passive tracers restart 18 USE trcnam ! Namelist read19 18 ! USE trcice_cfc ! CFC initialisation 20 19 USE trcice_pisces ! PISCES initialisation … … 31 30 PRIVATE 32 31 33 PUBLIC trc_ice_ini ! called by trc_ init32 PUBLIC trc_ice_ini ! called by trc_nam 34 33 35 34 CONTAINS … … 39 38 !! *** ROUTINE trc_ice_ini *** 40 39 !! 41 !! ** Purpose : Communication between TOP and sea ice40 !! ** Purpose : Initialization of the ice module for tracers 42 41 !! 43 42 !! ** Method : - 44 43 !! 45 44 !!--------------------------------------------------------------------- 46 INTEGER :: jk, jn, jl ! dummy loop indices 47 INTEGER :: ios ! Local integer output status for namelist read 45 ! --- Variable declarations --- ! 48 46 49 NAMELIST/namtrc_ice/ nn_ice_tr50 !51 47 IF(lwp) THEN 52 48 WRITE(numout,*) … … 58 54 59 55 ! 60 REWIND( numnat_ref ) ! Namelist namtrc_dta in reference namelist : Passive tracer input data61 READ ( numnat_ref, namtrc_ice, IOSTAT = ios, ERR = 901)62 901 IF( ios /= 0 ) CALL ctl_nam ( ios , ' namtrc_ice in reference namelist ', lwp )63 64 REWIND( numnat_cfg ) ! Namelist nampissbc in configuration namelist : Pisces external sources of nutrients65 READ ( numnat_cfg, namtrc_ice, IOSTAT = ios, ERR = 902 )66 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ice in configuration namelist', lwp )67 68 WRITE(numout,*) ' '69 WRITE(numout,*) ' Sea ice tracers option (nn_ice_tr) : ', nn_ice_tr70 WRITE(numout,*) ' '71 72 56 trc_i(:,:,:) = 0.0d0 ! by default 73 57 trc_o(:,:,:) = 0.0d0 ! by default -
branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC/trcnam.F90
r4990 r5325 27 27 USE trd_oce 28 28 USE trdtrc_oce 29 USE trcnam_ice ! Ice module for tracers 29 30 USE iom ! I/O manager 30 31 … … 147 148 148 149 150 ! Call the ice module for tracers 151 ! ------------------------------- 152 CALL trc_nam_ice 153 149 154 ! namelist of SMS 150 155 ! ---------------
Note: See TracChangeset
for help on using the changeset viewer.