Changeset 6311
- Timestamp:
- 2016-02-15T12:28:31+01:00 (9 years ago)
- Location:
- branches/2015/nemo_v3_6_STABLE/NEMOGCM
- Files:
-
- 9 edited
Legend:
- Unmodified
- Added
- Removed
-
branches/2015/nemo_v3_6_STABLE/NEMOGCM/CONFIG/SHARED/namelist_ice_lim3_ref
r5429 r6311 21 21 cn_icerst_outdir = "." ! directory in which to write output ice restarts 22 22 ln_limdyn = .true. ! ice dynamics (T) or thermodynamics only (F) 23 rn_amax = 0.999 ! maximum tolerated ice concentration 23 rn_amax_n = 0.999 ! maximum tolerated ice concentration NH 24 rn_amax_s = 0.999 ! maximum tolerated ice concentration SH 24 25 ln_limdiahsb = .false. ! check the heat and salt budgets (T) or not (F) 25 26 ln_limdiaout = .true. ! output the heat and salt budgets (T) or not (F) -
branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/ice.F90
r5341 r6311 301 301 302 302 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ftr_ice !: transmitted solar radiation under ice 303 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: rn_amax_2d !: maximum ice concentration 2d array 303 304 304 305 !!-------------------------------------------------------------------------- … … 372 373 INTEGER , PUBLIC :: nlay_i !: number of ice layers 373 374 INTEGER , PUBLIC :: nlay_s !: number of snow layers 374 CHARACTER(len= 32), PUBLIC :: cn_icerst_in !: suffix of ice restart name (input)375 CHARACTER(len=80), PUBLIC :: cn_icerst_in !: suffix of ice restart name (input) 375 376 CHARACTER(len=256), PUBLIC :: cn_icerst_indir !: ice restart input directory 376 CHARACTER(len= 32), PUBLIC :: cn_icerst_out !: suffix of ice restart name (output)377 CHARACTER(len=80), PUBLIC :: cn_icerst_out !: suffix of ice restart name (output) 377 378 CHARACTER(len=256), PUBLIC :: cn_icerst_outdir!: ice restart output directory 378 379 LOGICAL , PUBLIC :: ln_limdyn !: flag for ice dynamics (T) or not (F) 379 380 LOGICAL , PUBLIC :: ln_icectl !: flag for sea-ice points output (T) or not (F) 380 REAL(wp) , PUBLIC :: rn_amax !: maximum ice concentration 381 REAL(wp) , PUBLIC :: rn_amax_n !: maximum ice concentration Northern hemisphere 382 REAL(wp) , PUBLIC :: rn_amax_s !: maximum ice concentration Southern hemisphere 381 383 INTEGER , PUBLIC :: iiceprt !: debug i-point 382 384 INTEGER , PUBLIC :: jiceprt !: debug j-point … … 438 440 & afx_tot(jpi,jpj) , afx_thd(jpi,jpj), afx_dyn(jpi,jpj) , & 439 441 & fhtur (jpi,jpj) , ftr_ice(jpi,jpj,jpl), qlead (jpi,jpj) , & 442 & rn_amax_2d(jpi,jpj), & 440 443 & sfx_res(jpi,jpj) , sfx_bri(jpi,jpj) , sfx_dyn(jpi,jpj) , & 441 444 & sfx_bog(jpi,jpj) , sfx_bom(jpi,jpj) , sfx_sum(jpi,jpj) , sfx_sni(jpi,jpj) , sfx_opw(jpi,jpj) , & -
branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/limcons.F90
r5183 r6311 256 256 ENDIF 257 257 IF ( zvmin < -epsi10 ) WRITE(numout,*) 'violation v_i<0 [m] (',cd_routine,') = ',zvmin 258 IF ( zamax > rn_amax+epsi10 .AND. cd_routine /= 'limtrp' .AND. cd_routine /= 'limitd_me' ) THEN 258 IF ( zamax > MAX( rn_amax_n, rn_amax_s ) + epsi10 .AND. & 259 & cd_routine /= 'limtrp' .AND. cd_routine /= 'limitd_me' ) THEN 259 260 WRITE(numout,*) 'violation a_i>amax (',cd_routine,') = ',zamax 260 261 ENDIF -
branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/limthd_lac.F90
r5202 r6311 297 297 END DO 298 298 299 CALL tab_2d_1d( nbpac, qlead_1d (1:nbpac) , qlead , jpi, jpj, npac(1:nbpac) ) 300 CALL tab_2d_1d( nbpac, t_bo_1d (1:nbpac) , t_bo , jpi, jpj, npac(1:nbpac) ) 301 CALL tab_2d_1d( nbpac, sfx_opw_1d(1:nbpac) , sfx_opw, jpi, jpj, npac(1:nbpac) ) 302 CALL tab_2d_1d( nbpac, wfx_opw_1d(1:nbpac) , wfx_opw, jpi, jpj, npac(1:nbpac) ) 303 CALL tab_2d_1d( nbpac, hicol_1d (1:nbpac) , hicol , jpi, jpj, npac(1:nbpac) ) 304 CALL tab_2d_1d( nbpac, zvrel_1d (1:nbpac) , zvrel , jpi, jpj, npac(1:nbpac) ) 305 306 CALL tab_2d_1d( nbpac, hfx_thd_1d(1:nbpac) , hfx_thd, jpi, jpj, npac(1:nbpac) ) 307 CALL tab_2d_1d( nbpac, hfx_opw_1d(1:nbpac) , hfx_opw, jpi, jpj, npac(1:nbpac) ) 299 CALL tab_2d_1d( nbpac, qlead_1d (1:nbpac), qlead , jpi, jpj, npac(1:nbpac) ) 300 CALL tab_2d_1d( nbpac, t_bo_1d (1:nbpac), t_bo , jpi, jpj, npac(1:nbpac) ) 301 CALL tab_2d_1d( nbpac, sfx_opw_1d(1:nbpac), sfx_opw , jpi, jpj, npac(1:nbpac) ) 302 CALL tab_2d_1d( nbpac, wfx_opw_1d(1:nbpac), wfx_opw , jpi, jpj, npac(1:nbpac) ) 303 CALL tab_2d_1d( nbpac, hicol_1d (1:nbpac), hicol , jpi, jpj, npac(1:nbpac) ) 304 CALL tab_2d_1d( nbpac, zvrel_1d (1:nbpac), zvrel , jpi, jpj, npac(1:nbpac) ) 305 306 CALL tab_2d_1d( nbpac, hfx_thd_1d(1:nbpac), hfx_thd , jpi, jpj, npac(1:nbpac) ) 307 CALL tab_2d_1d( nbpac, hfx_opw_1d(1:nbpac), hfx_opw , jpi, jpj, npac(1:nbpac) ) 308 CALL tab_2d_1d( nbpac, rn_amax_1d(1:nbpac), rn_amax_2d, jpi, jpj, npac(1:nbpac) ) 308 309 309 310 !------------------------------------------------------------------------------! … … 409 410 ! we keep the excessive volume in memory and attribute it later to bottom accretion 410 411 DO ji = 1, nbpac 411 IF ( za_newice(ji) > ( rn_amax - zat_i_1d(ji) ) ) THEN412 zda_res(ji) = za_newice(ji) - ( rn_amax - zat_i_1d(ji) )412 IF ( za_newice(ji) > ( rn_amax_1d(ji) - zat_i_1d(ji) ) ) THEN 413 zda_res(ji) = za_newice(ji) - ( rn_amax_1d(ji) - zat_i_1d(ji) ) 413 414 zdv_res(ji) = zda_res (ji) * zh_newice(ji) 414 415 za_newice(ji) = za_newice(ji) - zda_res (ji) -
branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/limtrp.F90
r5202 r6311 422 422 DO jj = 1, jpj 423 423 DO ji = 1, jpi 424 a_i(ji,jj,1) = MIN( a_i(ji,jj,1), rn_amax )424 a_i(ji,jj,1) = MIN( a_i(ji,jj,1), rn_amax_2d(ji,jj) ) 425 425 END DO 426 426 END DO -
branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/limupdate1.F90
r5215 r6311 80 80 DO jj = 1, jpj 81 81 DO ji = 1, jpi 82 IF( at_i(ji,jj) > rn_amax .AND. a_i(ji,jj,jl) > 0._wp ) THEN83 a_i (ji,jj,jl) = a_i (ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax / at_i(ji,jj) ) )84 oa_i(ji,jj,jl) = oa_i(ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax / at_i(ji,jj) ) )82 IF( at_i(ji,jj) > rn_amax_2d(ji,jj) .AND. a_i(ji,jj,jl) > 0._wp ) THEN 83 a_i (ji,jj,jl) = a_i (ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax_2d(ji,jj) / at_i(ji,jj) ) ) 84 oa_i(ji,jj,jl) = oa_i(ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax_2d(ji,jj) / at_i(ji,jj) ) ) 85 85 ENDIF 86 86 END DO -
branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/limupdate2.F90
r5410 r6311 94 94 DO jj = 1, jpj 95 95 DO ji = 1, jpi 96 IF( at_i(ji,jj) > rn_amax .AND. a_i(ji,jj,jl) > 0._wp ) THEN97 a_i (ji,jj,jl) = a_i (ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax / at_i(ji,jj) ) )98 oa_i(ji,jj,jl) = oa_i(ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax / at_i(ji,jj) ) )96 IF( at_i(ji,jj) > rn_amax_2d(ji,jj) .AND. a_i(ji,jj,jl) > 0._wp ) THEN 97 a_i (ji,jj,jl) = a_i (ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax_2d(ji,jj) / at_i(ji,jj) ) ) 98 oa_i(ji,jj,jl) = oa_i(ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax_2d(ji,jj) / at_i(ji,jj) ) ) 99 99 ENDIF 100 100 END DO -
branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/thd_ice.F90
r5407 r6311 51 51 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: hfx_dif_1d 52 52 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: hfx_opw_1d 53 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: rn_amax_1d 53 54 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: hfx_snw_1d 54 55 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: hfx_err_1d … … 144 145 & hfx_sum_1d(jpij) , hfx_bom_1d(jpij) ,hfx_bog_1d(jpij) , & 145 146 & hfx_dif_1d(jpij) , hfx_opw_1d(jpij) , & 147 & rn_amax_1d(jpij) , & 146 148 & hfx_thd_1d(jpij) , hfx_spr_1d(jpij) , & 147 149 & hfx_snw_1d(jpij) , hfx_sub_1d(jpij) , hfx_err_1d(jpij) , & -
branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90
r5540 r6311 265 265 !!---------------------------------------------------------------------- 266 266 INTEGER :: ierr 267 INTEGER :: ji, jj 267 268 !!---------------------------------------------------------------------- 268 269 IF(lwp) WRITE(numout,*) … … 321 322 tn_ice(:,:,:) = t_su(:,:,:) ! initialisation of surface temp for coupled simu 322 323 ! 324 DO jj = 1, jpj 325 DO ji = 1, jpi 326 IF( gphit(ji,jj) > 0._wp ) THEN ; rn_amax_2d(ji,jj) = rn_amax_n ! NH 327 ELSE ; rn_amax_2d(ji,jj) = rn_amax_s ! SH 328 ENDIF 329 ENDDO 330 ENDDO 331 ! 323 332 nstart = numit + nn_fsbc 324 333 nitrun = nitend - nit000 + 1 … … 343 352 INTEGER :: ios ! Local integer output status for namelist read 344 353 NAMELIST/namicerun/ jpl, nlay_i, nlay_s, cn_icerst_in, cn_icerst_indir, cn_icerst_out, cn_icerst_outdir, & 345 & ln_limdyn, rn_amax , ln_limdiahsb, ln_limdiaout, ln_icectl, iiceprt, jiceprt354 & ln_limdyn, rn_amax_n, rn_amax_s, ln_limdiahsb, ln_limdiaout, ln_icectl, iiceprt, jiceprt 346 355 !!------------------------------------------------------------------- 347 356 ! … … 364 373 WRITE(numout,*) ' number of snow layers = ', nlay_s 365 374 WRITE(numout,*) ' switch for ice dynamics (1) or not (0) ln_limdyn = ', ln_limdyn 366 WRITE(numout,*) ' maximum ice concentration = ', rn_amax 375 WRITE(numout,*) ' maximum ice concentration for NH = ', rn_amax_n 376 WRITE(numout,*) ' maximum ice concentration for SH = ', rn_amax_s 367 377 WRITE(numout,*) ' Diagnose heat/salt budget or not ln_limdiahsb = ', ln_limdiahsb 368 378 WRITE(numout,*) ' Output heat/salt budget or not ln_limdiaout = ', ln_limdiaout
Note: See TracChangeset
for help on using the changeset viewer.