Changeset 8486
- Timestamp:
- 2017-09-01T15:49:35+02:00 (7 years ago)
- Location:
- branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3
- Files:
-
- 28 edited
Legend:
- Unmodified
- Added
- Removed
-
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/ice.F90
r8426 r8486 17 17 PRIVATE 18 18 19 PUBLIC ice_alloc ! Called in ice_init19 PUBLIC ice_alloc ! called by icestp.F90 20 20 21 21 !!====================================================================== … … 288 288 REAL(wp), PUBLIC :: r1_nlay_s !: 1 / nlay_s 289 289 REAL(wp), PUBLIC :: rswitch !: switch for the presence of ice (1) or not (0) 290 REAL(wp), PUBLIC, PARAMETER :: epsi06 = 1.e-06_wp !: small number 291 REAL(wp), PUBLIC, PARAMETER :: epsi10 = 1.e-10_wp !: small number 292 REAL(wp), PUBLIC, PARAMETER :: epsi20 = 1.e-20_wp !: small number 290 REAL(wp), PUBLIC, PARAMETER :: epsi06 = 1.e-06_wp !: small number 291 REAL(wp), PUBLIC, PARAMETER :: epsi10 = 1.e-10_wp !: small number 292 REAL(wp), PUBLIC, PARAMETER :: epsi20 = 1.e-20_wp !: small number 293 ! 294 LOGICAL , PUBLIC :: l_piling !: =T simple conservative piling, comparable with LIM2 293 295 294 296 ! !!** define arrays 295 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: u_oce, 297 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: u_oce,v_oce !: surface ocean velocity used in ice dynamics 296 298 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: hicol !: ice collection thickness accreted in leads 297 299 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: strength !: ice strength … … 499 501 ! 500 502 !!---------------------------------------------------------------------- 501 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2010)503 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 502 504 !! $Id$ 503 505 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/ice1D.F90
r8420 r8486 8 8 #if defined key_lim3 9 9 !!---------------------------------------------------------------------- 10 !! 'key_lim3' LIM3 sea-ice model 11 !!---------------------------------------------------------------------- 10 !! 'key_lim3' LIM3 sea-ice model 11 !!---------------------------------------------------------------------- 12 USE ice , ONLY : nlay_i, nlay_s, jpl ! number of ice/snow layers and categories 13 ! 12 14 USE in_out_manager ! I/O manager 13 15 USE lib_mpp ! MPP library 14 USE ice, ONLY : nlay_i, nlay_s, jpl15 16 16 17 IMPLICIT NONE 17 18 PRIVATE 18 19 19 PUBLIC ice1D_alloc ! Routine called by nemogcm.F9020 PUBLIC ice1D_alloc ! called by icestp.F90 20 21 21 22 !!---------------------- … … 26 27 !: are the variables corresponding to 2d vectors 27 28 29 !! please, DOCTOR naming convention starting by i means LOCAL integer 30 !! ===>>> rename idxice as nidice or nidthd, or nidx_thd or midx ... ? 28 31 INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: idxice !: selected points for ice thermo 29 32 INTEGER , PUBLIC :: nidx ! number of selected points … … 151 154 152 155 !!---------------------------------------------------------------------- 153 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)156 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 154 157 !! $Id: ice1D.F90 8379 2017-07-26 15:35:49Z clem $ 155 158 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceadv.F90
r8426 r8486 10 10 #if defined key_lim3 11 11 !!---------------------------------------------------------------------- 12 !! 'key_lim3' LIM3 sea-ice model13 !!---------------------------------------------------------------------- 14 !! ice_adv : advection/diffusion process of sea ice12 !! 'key_lim3' LIM3 sea-ice model 13 !!---------------------------------------------------------------------- 14 !! ice_adv : advection/diffusion process of sea ice 15 15 !!---------------------------------------------------------------------- 16 16 USE phycst ! physical constant 17 17 USE dom_oce ! ocean domain 18 USE sbc_oce , ONLY : nn_fsbc 19 USE ice ! ice variables 20 USE icevar ! 21 USE iceadv_prather ! advection scheme (Prather) 22 USE iceadv_umx ! advection scheme (ultimate-macho) 18 USE sbc_oce , ONLY : nn_fsbc ! frequency of sea-ice call 19 USE ice ! sea-ice: variables 20 USE icevar ! sea-ice: operations 21 USE iceadv_prather ! sea-ice: advection scheme (Prather) 22 USE iceadv_umx ! sea-ice: advection scheme (ultimate-macho) 23 USE icectl ! sea-ice: control prints 23 24 ! 24 25 USE in_out_manager ! I/O manager 25 26 USE lbclnk ! lateral boundary conditions -- MPP exchanges 26 27 USE lib_mpp ! MPP library 27 USE wrk_nemo ! work arrays28 28 USE prtctl ! Print control 29 29 USE lib_fortran ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 30 30 USE timing ! Timing 31 USE icectl ! control prints32 31 33 32 IMPLICIT NONE … … 36 35 PUBLIC ice_adv ! called by icestp 37 36 38 INTEGER :: ncfl! number of ice time step with CFL>1/237 INTEGER :: ncfl ! number of ice time step with CFL>1/2 39 38 40 39 !! * Substitution 41 40 # include "vectopt_loop_substitute.h90" 42 41 !!---------------------------------------------------------------------- 43 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)42 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 44 43 !! $Id: iceadv.F90 8373 2017-07-25 17:44:54Z clem $ 45 44 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 48 47 49 48 SUBROUTINE ice_adv( kt ) 50 !!------------------------------------------------------------------- 49 !!---------------------------------------------------------------------- 51 50 !! *** ROUTINE ice_adv *** 52 51 !! … … 60 59 !! 61 60 !! ** action : 62 !!--------------------------------------------------------------------- 61 !!---------------------------------------------------------------------- 63 62 INTEGER, INTENT(in) :: kt ! number of iteration 64 63 ! … … 73 72 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zhimax, zviold, zvsold 74 73 ! --- ultimate macho only --- ! 75 REAL(wp) 76 REAL(wp), POINTER, DIMENSION(:,:) :: zudy, zvdx, zcu_box, zcv_box74 REAL(wp) :: zdt 75 REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zudy, zvdx, zcu_box, zcv_box 77 76 ! --- prather only --- ! 78 REAL(wp), POINTER, DIMENSION(:,:):: zarea79 REAL(wp), POINTER, DIMENSION(:,:,:):: z0opw80 REAL(wp), POINTER, DIMENSION(:,:,:):: z0ice, z0snw, z0ai, z0es , z0smi , z0oi77 REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zarea 78 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: z0opw 79 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: z0ice, z0snw, z0ai, z0es , z0smi , z0oi 81 80 ! MV MP 2016 82 REAL(wp), POINTER, DIMENSION(:,:,:):: z0ap , z0vp81 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: z0ap , z0vp 83 82 REAL(wp) :: za_old 84 83 ! END MV MP 2016 85 REAL(wp), POINTER, DIMENSION(:,:,:,:) :: z0ei 86 !! 84 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: z0ei 87 85 !!--------------------------------------------------------------------- 88 86 IF( nn_timing == 1 ) CALL timing_start('iceadv') … … 90 88 IF( kt == nit000 .AND. lwp ) THEN 91 89 WRITE(numout,*)'' 92 WRITE(numout,*)'iceadv '93 WRITE(numout,*)'~~~~~~ '90 WRITE(numout,*)'iceadv : sea-ice advection' 91 WRITE(numout,*)'~~~~~~~' 94 92 ncfl = 0 ! nb of time step with CFL > 1/2 95 93 ENDIF … … 127 125 DO jj = 2, jpjm1 128 126 DO ji = 2, jpim1 127 !!gm use of MAXVAL here is very probably less efficient than expending the 9 values 129 128 zhimax(ji,jj,jl) = MAXVAL( ht_i(ji-1:ji+1,jj-1:jj+1,jl) + ht_s(ji-1:ji+1,jj-1:jj+1,jl) ) 130 129 END DO … … 156 155 !=============================! 157 156 158 CALL wrk_alloc( jpi,jpj, zudy, zvdx, zcu_box, zcv_box)157 ALLOCATE( zudy(jpi,jpj) , zvdx(jpi,jpj) , zcu_box(jpi,jpj) , zcv_box(jpi,jpj) ) 159 158 160 159 IF( kt == nit000 .AND. lwp ) THEN … … 212 211 END DO 213 212 ! 214 CALL wrk_dealloc( jpi,jpj,zudy, zvdx, zcu_box, zcv_box )213 DEALLOCATE( zudy, zvdx, zcu_box, zcv_box ) 215 214 216 215 !=============================! … … 218 217 !=============================! 219 218 220 CALL wrk_alloc( jpi,jpj, zarea ) 221 CALL wrk_alloc( jpi,jpj,1, z0opw ) 222 CALL wrk_alloc( jpi,jpj,jpl, z0ice, z0snw, z0ai, z0es , z0smi , z0oi ) 223 CALL wrk_alloc( jpi,jpj,jpl, z0ap , z0vp ) 224 CALL wrk_alloc( jpi,jpj,nlay_i,jpl, z0ei ) 219 ALLOCATE( zarea(jpi,jpj) , z0opw(jpi,jpj, 1 ) , & 220 & z0ice(jpi,jpj,jpl) , z0snw(jpi,jpj,jpl) , z0ai(jpi,jpj,jpl) , z0es(jpi,jpj,jpl) , & 221 & z0smi(jpi,jpj,jpl) , z0oi (jpi,jpj,jpl) , z0ap(jpi,jpj,jpl) , z0vp(jpi,jpj,jpl) , & 222 & z0ei (jpi,jpj,nlay_i,jpl) ) 225 223 226 224 IF( kt == nit000 .AND. lwp ) THEN … … 237 235 z0opw(:,:,1) = ato_i(:,:) * e1e2t(:,:) ! Open water area 238 236 DO jl = 1, jpl 239 z0snw (:,:,jl)= v_s (:,:, jl) * e1e2t(:,:) ! Snow volume240 z0ice(:,:,jl) 241 z0ai (:,:,jl)= a_i (:,:, jl) * e1e2t(:,:) ! Ice area242 z0smi (:,:,jl)= smv_i(:,:, jl) * e1e2t(:,:) ! Salt content243 z0oi (:,:,jl) 244 z0es (:,:,jl) 237 z0snw(:,:,jl) = v_s (:,:, jl) * e1e2t(:,:) ! Snow volume 238 z0ice(:,:,jl) = v_i (:,:, jl) * e1e2t(:,:) ! Ice volume 239 z0ai (:,:,jl) = a_i (:,:, jl) * e1e2t(:,:) ! Ice area 240 z0smi(:,:,jl) = smv_i(:,:, jl) * e1e2t(:,:) ! Salt content 241 z0oi (:,:,jl) = oa_i (:,:, jl) * e1e2t(:,:) ! Age content 242 z0es (:,:,jl) = e_s (:,:,1,jl) * e1e2t(:,:) ! Snow heat content 245 243 DO jk = 1, nlay_i 246 z0ei (:,:,jk,jl) = e_i(:,:,jk,jl) * e1e2t(:,:) ! Ice heat content244 z0ei(:,:,jk,jl) = e_i(:,:,jk,jl) * e1e2t(:,:) ! Ice heat content 247 245 END DO 248 246 ! MV MP 2016 249 247 IF ( nn_pnd_scheme > 0 ) THEN 250 z0ap (:,:,jl) = a_ip(:,:,jl) * e1e2t(:,:) ! Melt pond fraction251 z0vp (:,:,jl) = v_ip(:,:,jl) * e1e2t(:,:) ! Melt pond volume248 z0ap(:,:,jl) = a_ip(:,:,jl) * e1e2t(:,:) ! Melt pond fraction 249 z0vp(:,:,jl) = v_ip(:,:,jl) * e1e2t(:,:) ! Melt pond volume 252 250 ENDIF 253 251 ! END MV MP 2016 254 255 END DO 256 252 END DO 257 253 258 254 IF( MOD( ( kt - 1) / nn_fsbc , 2 ) == 0 ) THEN !== odd ice time step: adv_x then adv_y ==! … … 383 379 ! END MV MP 2016 384 380 END DO 385 381 ! 386 382 at_i(:,:) = a_i(:,:,1) ! total ice fraction 387 383 DO jl = 2, jpl 388 384 at_i(:,:) = at_i(:,:) + a_i(:,:,jl) 389 385 END DO 390 391 CALL wrk_dealloc( jpi,jpj, zarea ) 392 CALL wrk_dealloc( jpi,jpj,1, z0opw ) 393 CALL wrk_dealloc( jpi,jpj,jpl, z0ice, z0snw, z0ai, z0es , z0smi , z0oi ) 394 ! MV MP 2016 395 CALL wrk_dealloc( jpi,jpj,jpl, z0ap , z0vp ) 396 ! END MV MP 2016 397 CALL wrk_dealloc( jpi,jpj,nlay_i,jpl, z0ei ) 398 386 ! 387 DEALLOCATE( zarea , z0opw , z0ice, z0snw , z0ai , z0es , z0smi , z0oi , z0ap , z0vp , z0ei ) 388 ! 399 389 END SELECT 400 390 … … 411 401 412 402 IF( nn_limdyn == 2) THEN 413 414 ! zap small areas 415 CALL ice_var_zapsmall 416 417 !--- Thickness correction in case too high --- ! 418 DO jl = 1, jpl 403 ! 404 CALL ice_var_zapsmall !--- zap small areas ---! 405 ! 406 DO jl = 1, jpl !--- Thickness correction in case too high --- ! 419 407 DO jj = 1, jpj 420 408 DO ji = 1, jpi 421 409 ! 422 410 IF ( v_i(ji,jj,jl) > 0._wp ) THEN 423 411 ! 424 412 rswitch = MAX( 0._wp , SIGN( 1._wp, a_i(ji,jj,jl) - epsi20 ) ) 425 413 ht_i (ji,jj,jl) = v_i (ji,jj,jl) / MAX( a_i(ji,jj,jl) , epsi20 ) * rswitch 426 414 ht_s (ji,jj,jl) = v_s (ji,jj,jl) / MAX( a_i(ji,jj,jl) , epsi20 ) * rswitch 427 415 ! 428 416 zdv = v_i(ji,jj,jl) + v_s(ji,jj,jl) - zviold(ji,jj,jl) - zvsold(ji,jj,jl) 429 417 ! 430 418 IF ( ( zdv > 0.0 .AND. (ht_i(ji,jj,jl)+ht_s(ji,jj,jl)) > zhimax(ji,jj,jl) .AND. zatold(ji,jj) < 0.80 ) .OR. & 431 419 & ( zdv <= 0.0 .AND. (ht_i(ji,jj,jl)+ht_s(ji,jj,jl)) > zhimax(ji,jj,jl) ) ) THEN 432 420 ! 433 421 rswitch = MAX( 0._wp, SIGN( 1._wp, zhimax(ji,jj,jl) - epsi20 ) ) 434 422 a_i(ji,jj,jl) = rswitch * ( v_i(ji,jj,jl) + v_s(ji,jj,jl) ) / MAX( zhimax(ji,jj,jl), epsi20 ) 435 423 ! 436 424 ! small correction due to *rswitch for a_i 437 425 v_i (ji,jj,jl) = rswitch * v_i (ji,jj,jl) … … 447 435 ENDIF 448 436 ! END MV MP 2016 449 437 ! 450 438 ENDIF 451 439 ! 452 440 ENDIF 453 441 ! 454 442 END DO 455 443 END DO 456 444 END DO 457 ! ------------------------------------------------- 458 459 ! Force the upper limit of ht_i to always be < hi_max (99 m). 460 DO jj = 1, jpj 445 446 DO jj = 1, jpj !--- bound ht_i to hi_max (99 m). 461 447 DO ji = 1, jpi 462 448 ! MV MP 2016 … … 474 460 END DO 475 461 END DO 476 477 462 ! 478 463 ENDIF 479 464 … … 482 467 !------------------------------------------------------------ 483 468 ! 484 at_i(:,:) = SUM( a_i(:,:,:), dim=3 ) 485 IF ( nn_limdyn == 1 .OR. ( ( nn_monocat == 2 ) .AND. ( jpl == 1 ) ) ) THEN ! simple conservative piling, comparable with LIM2 469 !!gm remplace the test by, l_piling a logical compute one for all in icestp.F90 (and its declaration in ice.F90 470 !!gm IF ( nn_limdyn == 1 .OR. ( ( nn_monocat == 2 ) .AND. ( jpl == 1 ) ) ) THEN ! simple conservative piling, comparable with LIM2 471 IF( l_piling ) THEN 472 at_i(:,:) = SUM( a_i(:,:,:), dim=3 ) 486 473 DO jl = 1, jpl 487 474 DO jj = 1, jpj 488 475 DO ji = 1, jpi 489 rswitch = MAX( 0._wp, SIGN( 1._wp, at_i(ji,jj) - epsi20 ) ) 490 zda = rswitch * MIN( rn_amax_2d(ji,jj) - at_i(ji,jj), 0._wp ) & 491 & * a_i(ji,jj,jl) / MAX( at_i(ji,jj), epsi20 ) 476 rswitch = MAX( 0._wp, SIGN( 1._wp, at_i(ji,jj) - epsi20 ) ) 477 zda = rswitch * MIN( rn_amax_2d(ji,jj) - at_i(ji,jj), 0._wp ) * a_i(ji,jj,jl) / MAX( at_i(ji,jj), epsi20 ) 492 478 a_i(ji,jj,jl) = a_i(ji,jj,jl) + zda 493 479 END DO 494 480 END DO 495 481 END DO 482 !!gm better and faster coding? 483 ! DO jl = 1, jpl 484 ! WHERE( at_i(:,:) > epsi20 ) 485 ! a_i(:,:,jl) = a_i(:,:,jl) * ( 1._wp + MIN( rn_amax_2d(:,:) - at_i(:,:) , 0._wp ) / at_i(:,:) ) 486 ! END WHERE 487 ! END DO 488 !!gm end 496 489 ENDIF 497 490 … … 527 520 !! Default option Empty Module No sea-ice model 528 521 !!---------------------------------------------------------------------- 529 CONTAINS530 SUBROUTINE ice_adv ! Empty routine531 END SUBROUTINE ice_adv532 522 #endif 523 533 524 !!====================================================================== 534 525 END MODULE iceadv -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceadv_prather.F90
r8409 r8486 5 5 !!====================================================================== 6 6 !! History : LIM ! 2008-03 (M. Vancoppenolle) LIM-3 from LIM-2 code 7 !! 3.2 ! 2009-06 (F. Dupont) correct a error in the North fold b. 7 !! 3.2 ! 2009-06 (F. Dupont) correct a error in the North fold b.c. 8 8 !! 4.0 ! 2011-02 (G. Madec) dynamical allocation 9 9 !!-------------------------------------------------------------------- 10 10 #if defined key_lim3 11 11 !!---------------------------------------------------------------------- 12 !! 'key_lim3' LIM3 sea-ice model13 !!---------------------------------------------------------------------- 14 !! ice_adv_x : advection of sea ice on x axis15 !! ice_adv_y : advection of sea ice on y axis16 !!---------------------------------------------------------------------- 17 USE dom_oce 18 USE ice ! LIM-3variables12 !! 'key_lim3' LIM3 sea-ice model 13 !!---------------------------------------------------------------------- 14 !! ice_adv_x : advection of sea ice on x axis 15 !! ice_adv_y : advection of sea ice on y axis 16 !!---------------------------------------------------------------------- 17 USE dom_oce ! ocean domain 18 USE ice ! sea-ice variables 19 19 ! 20 USE lbclnk 21 USE in_out_manager 22 USE prtctl 23 USE lib_mpp 24 USE lib_fortran 20 USE lbclnk ! lateral boundary condition - MPP exchanges 21 USE in_out_manager ! I/O manager 22 USE prtctl ! Print control 23 USE lib_mpp ! MPP library 24 USE lib_fortran ! to use key_nosignedzero 25 25 26 26 IMPLICIT NONE … … 33 33 # include "vectopt_loop_substitute.h90" 34 34 !!---------------------------------------------------------------------- 35 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)35 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 36 36 !! $Id: iceadv.F90 6746 2016-06-27 17:20:57Z clem $ 37 37 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 41 41 SUBROUTINE ice_adv_x( pdf, put , pcrh, psm , ps0 , & 42 42 & psx, psxx, psy , psyy, psxy ) 43 !!--------------------------------------------------------------------- 43 !!---------------------------------------------------------------------- 44 44 !! ** routine ice_adv_x ** 45 45 !! … … 52 52 !! 53 53 !! Reference: Prather, 1986, JGR, 91, D6. 6671-6681. 54 !!-------------------------------------------------------------------- 54 !!---------------------------------------------------------------------- 55 55 REAL(wp) , INTENT(in ) :: pdf ! reduction factor for the time step 56 56 REAL(wp) , INTENT(in ) :: pcrh ! call ice_adv_x then ice_adv_y (=1) or the opposite (=0) … … 68 68 REAL(wp), DIMENSION(jpi,jpj) :: zfm , zfxx , zfyy , zfxy ! - - 69 69 REAL(wp), DIMENSION(jpi,jpj) :: zalg, zalg1, zalg1q ! - - 70 !--------------------------------------------------------------------- 70 !----------------------------------------------------------------------- 71 71 72 72 ! Limitation of moments. -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceadv_umx.F90
r8409 r8486 4 4 !! LIM sea-ice model : sea-ice advection using the ULTIMATE-MACHO scheme 5 5 !!============================================================================== 6 !! History : 3.5 ! 2014-11 (C. Rousset, G. Madec) Original code 7 !!---------------------------------------------------------------------- 8 6 !! History : 3.6 ! 2014-11 (C. Rousset, G. Madec) Original code 7 !!---------------------------------------------------------------------- 8 #if defined key_lim3 9 !!---------------------------------------------------------------------- 10 !! 'key_lim3' LIM 3.0 sea-ice model 9 11 !!---------------------------------------------------------------------- 10 12 !! ice_adv_umx : update the tracer trend with the 3D advection trends using a TVD scheme 11 !! ultimate 12 !! macho : 13 !! ultimate_x(_y): compute a tracer value at velocity points using ULTIMATE scheme at various orders 14 !! macho : ??? 13 15 !! nonosc_2d : compute monotonic tracer fluxes by a non-oscillatory algorithm 14 !!----------------------------------------------------------------------15 #if defined key_lim316 !!----------------------------------------------------------------------17 !! 'key_lim3' : LIM 3.0 sea-ice model18 16 !!---------------------------------------------------------------------- 19 17 USE phycst ! physical constant 20 18 USE dom_oce ! ocean domain 21 USE sbc_oce , ONLY: nn_fsbc ! oceansurface boundary condition22 USE ice ! ice variables19 USE sbc_oce , ONLY : nn_fsbc ! update frequency of surface boundary condition 20 USE ice ! sea-ice variables 23 21 ! 24 22 USE in_out_manager ! I/O manager … … 33 31 PUBLIC ice_adv_umx ! routine called by iceadv.F90 34 32 35 REAL(wp) :: z1_6 = 1._wp / 6._wp ! =1/636 REAL(wp) :: z1_120 = 1._wp / 120._wp ! =1/12033 REAL(wp) :: z1_6 = 1._wp / 6._wp ! =1/6 34 REAL(wp) :: z1_120 = 1._wp / 120._wp ! =1/120 37 35 38 36 !! * Substitutions 39 37 # include "vectopt_loop_substitute.h90" 40 38 !!---------------------------------------------------------------------- 41 !! NEMO/ OPA 3.3 , NEMO Consortium (2010)39 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 42 40 !! $Id: iceadv_umx.F90 4499 2014-02-18 15:14:31Z timgraham $ 43 41 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 58 56 !! ** Action : - pt the after advective tracer 59 57 !!---------------------------------------------------------------------- 60 INTEGER , INTENT(in ) :: kt! number of iteration61 REAL(wp) , INTENT(in ) :: pdt! tracer time-step62 REAL(wp), DIMENSION(jpi,jpj), INTENT(in ) :: puc, pvc! 2 ice velocity components => u*e263 REAL(wp), DIMENSION(jpi,jpj), INTENT(in ) 64 REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: ptc! tracer content field58 INTEGER , INTENT(in ) :: kt ! number of iteration 59 REAL(wp) , INTENT(in ) :: pdt ! tracer time-step 60 REAL(wp), DIMENSION(jpi,jpj), INTENT(in ) :: puc , pvc ! 2 ice velocity components => u*e2 61 REAL(wp), DIMENSION(jpi,jpj), INTENT(in ) :: pubox, pvbox ! upstream velocity 62 REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: ptc ! tracer content field 65 63 ! 66 64 INTEGER :: ji, jj ! dummy loop indices … … 68 66 REAL(wp) :: zfp_ui, zfp_vj ! - - 69 67 REAL(wp) :: zfm_ui, zfm_vj ! - - 70 REAL(wp), DIMENSION(jpi,jpj) :: zt_ups, zfu_ups, zfv_ups, ztrd, zfu_ho, zfv_ho, zt_u, zt_v 68 REAL(wp), DIMENSION(jpi,jpj) :: zfu_ups, zfu_ho, zt_u, zt_ups 69 REAL(wp), DIMENSION(jpi,jpj) :: zfv_ups, zfv_ho, zt_v, ztrd 71 70 !!---------------------------------------------------------------------- 72 71 ! … … 394 393 ! 395 394 SELECT CASE (k_order ) 396 ! 397 CASE( 1 ) !== 1st order central TIM ==! (Eq. 21) 398 ! 395 ! 396 CASE( 1 ) !== 1st order central TIM ==! (Eq. 21) 399 397 DO jj = 1, jpjm1 400 398 DO ji = 1, jpi … … 404 402 END DO 405 403 ! 406 CASE( 2 ) 404 CASE( 2 ) !== 2nd order central TIM ==! (Eq. 23) 407 405 DO jj = 1, jpjm1 408 406 DO ji = 1, jpi … … 414 412 CALL lbc_lnk( pt_v(:,:) , 'V', 1. ) 415 413 ! 416 CASE( 3 ) !== 3rd order central TIM ==! (Eq. 24) 417 ! 414 CASE( 3 ) !== 3rd order central TIM ==! (Eq. 24) 418 415 DO jj = 1, jpjm1 419 416 DO ji = 1, jpi … … 428 425 END DO 429 426 ! 430 CASE( 4 ) !== 4th order central TIM ==! (Eq. 27) 431 ! 427 CASE( 4 ) !== 4th order central TIM ==! (Eq. 27) 432 428 DO jj = 1, jpjm1 433 429 DO ji = 1, jpi … … 442 438 END DO 443 439 ! 444 CASE( 5 ) !== 5th order central TIM ==! (Eq. 29) 445 ! 440 CASE( 5 ) !== 5th order central TIM ==! (Eq. 29) 446 441 DO jj = 1, jpjm1 447 442 DO ji = 1, jpi … … 569 564 !! Default option Dummy module NO LIM 3.0 sea-ice model 570 565 !!---------------------------------------------------------------------- 571 CONTAINS572 !573 SUBROUTINE ice_adv_umx ! Dummy routine574 WRITE(*,*) 'ice_adv_umx: You should not have seen this print! error?'575 END SUBROUTINE ice_adv_umx576 566 #endif 567 577 568 !!====================================================================== 578 569 END MODULE iceadv_umx -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icealb.F90
r8426 r8486 4 4 !! Ocean forcing: bulk thermohaline forcing of the ice 5 5 !!===================================================================== 6 !! History : 7 !! NEMO 4.0 ! 2017-07 (C. Rousset) Split ice and ocean albedos 8 !!---------------------------------------------------------------------- 9 !! ice_alb : albedo for ice (clear and overcast skies) 10 !! alb_init : initialisation of albedo computation 6 !! History : 4.0 ! 2017-07 (C. Rousset) Split ice and ocean albedos 11 7 !!---------------------------------------------------------------------- 12 8 #if defined key_lim3 13 9 !!---------------------------------------------------------------------- 14 !! 'key_lim3' : LIM 3.0 sea-ice model 15 !!---------------------------------------------------------------------- 16 USE ice, ONLY : jpl 10 !! 'key_lim3' LIM 3.0 sea-ice model 11 !!---------------------------------------------------------------------- 12 !! ice_alb : albedo for ice (clear and overcast skies) 13 !! alb_init : initialisation of albedo computation 14 !!---------------------------------------------------------------------- 15 USE ice , ONLY : jpl ! number of ice category 17 16 USE phycst ! physical constants 18 17 ! … … 24 23 PRIVATE 25 24 26 PUBLIC ice_alb ! routine called icestp.F90 27 28 REAL(wp), PUBLIC, PARAMETER :: rn_alb_oce = 0.066 ! ocean or lead albedo (Pegau and Paulson, Ann. Glac. 2001) 25 PUBLIC ice_alb ! routine called in iceforcing.F90 and iceupdate.F90 26 27 REAL(wp), PUBLIC, PARAMETER :: rn_alb_oce = 0.066 !: ocean or lead albedo (Pegau and Paulson, Ann. Glac. 2001) 28 29 !!gm real variable name starting with a "c" NOT DOCTOR !!!! 29 30 INTEGER :: albd_init = 0 ! control flag for initialization 30 REAL(wp) :: c1 = 0.05 ! snow thickness (only for nn_ice_alb=0) 31 REAL(wp) :: c2 = 0.10 ! " " 32 REAL(wp) :: rcloud = 0.06 ! cloud effect on albedo (only-for nn_ice_alb=0) 31 REAL(wp) , PARAMETER :: c1 = 0.05 ! snow thickness (only for nn_ice_alb=0) 32 REAL(wp) , PARAMETER :: c2 = 0.10 ! " " 33 REAL(wp) , PARAMETER :: rcloud = 0.06 ! cloud effect on albedo (only-for nn_ice_alb=0) 34 REAL(wp) , PARAMETER :: r1_c1 = 1. / c1 35 REAL(wp) , PARAMETER :: r1_c2 = 1. / c2 33 36 34 ! !!* namelist namsbc_alb 37 ! !!* namelist namsbc_alb * 35 38 INTEGER :: nn_ice_alb 36 39 REAL(wp) :: rn_alb_sdry, rn_alb_smlt, rn_alb_idry, rn_alb_imlt, rn_alb_dpnd 37 40 38 41 !!---------------------------------------------------------------------- 39 !! NEMO/ OPA 4.0 , NEMO Consortium (2010)42 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 40 43 !! $Id: icealb.F90 8268 2017-07-03 15:01:04Z clem $ 41 44 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 76 79 !! Brandt et al. 2005, J. Climate, vol 18 77 80 !! Grenfell & Perovich 2004, JGR, vol 109 78 !! 79 !!---------------------------------------------------------------------- 80 !! 81 REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: pt_ice ! ice surface temperature (Kelvin) 82 REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: ph_ice ! sea-ice thickness 83 REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: ph_snw ! snow depth 84 REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: pafrac_pnd ! melt pond relative fraction (per unit ice area) 85 REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: ph_pnd ! melt pond depth 86 LOGICAL , INTENT(in ) :: ld_pnd ! melt ponds radiatively active or not 87 REAL(wp), INTENT( out), DIMENSION(:,:,:) :: pa_ice_cs ! albedo of ice under clear sky 88 REAL(wp), INTENT( out), DIMENSION(:,:,:) :: pa_ice_os ! albedo of ice under overcast sky 89 ! 90 INTEGER :: ji, jj, jl ! dummy loop indices 91 REAL(wp) :: zswitch, z1_c1, z1_c2 92 REAL(wp) :: zhref_pnd 81 !!---------------------------------------------------------------------- 82 REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: pt_ice ! ice surface temperature (Kelvin) 83 REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: ph_ice ! sea-ice thickness 84 REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: ph_snw ! snow depth 85 REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: pafrac_pnd ! melt pond relative fraction (per unit ice area) 86 REAL(wp), INTENT(in ), DIMENSION(:,:,:) :: ph_pnd ! melt pond depth 87 LOGICAL , INTENT(in ) :: ld_pnd ! melt ponds radiatively active or not 88 REAL(wp), INTENT( out), DIMENSION(:,:,:) :: pa_ice_cs ! albedo of ice under clear sky 89 REAL(wp), INTENT( out), DIMENSION(:,:,:) :: pa_ice_os ! albedo of ice under overcast sky 90 ! 91 INTEGER :: ji, jj, jl ! dummy loop indices 92 REAL(wp) :: zswitch, z1_c1, z1_c2 ! local scalar 93 REAL(wp) :: z1_href_pnd ! - - 93 94 REAL(wp) :: zalb_sm, zalb_sf, zalb_st ! albedo of snow melting, freezing, total 94 95 ! 95 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zalb, zalb_it 96 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zalb, zalb_it ! intermediate variable & albedo of ice (snow free) 96 97 !! MV MP 97 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zalb_pnd ! ponded sea ice albedo 98 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zalb_ice ! bare sea ice albedo 99 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zalb_snw ! snow-covered sea ice albedo 100 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zafrac_snw ! relative snow fraction 101 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zafrac_ice ! relative ice fraction 102 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zafrac_pnd ! relative ice fraction (effective) 103 !! 98 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zalb_pnd ! ponded sea ice albedo 99 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zalb_ice ! bare sea ice albedo 100 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zalb_snw ! snow-covered sea ice albedo 101 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zafrac_snw ! relative snow fraction 102 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zafrac_ice ! relative ice fraction 103 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zafrac_pnd ! relative ice fraction (effective) 104 104 !!--------------------------------------------------------------------- 105 105 … … 120 120 ENDIF 121 121 122 SELECT CASE ( nn_ice_alb ) 123 124 !------------------------------------------ 125 ! Shine and Henderson-Sellers (1985) 126 !------------------------------------------ 127 ! NB: This parameterization is based on clear sky values 128 129 CASE( 0 ) 130 131 ! Thickness-dependent bare ice albedo 122 SELECT CASE ( nn_ice_alb ) ! select a parameterization 123 ! 124 ! !------------------------------------------ 125 CASE( 0 ) ! Shine and Henderson-Sellers (1985) ! (based on clear sky values) 126 ! !------------------------------------------ 127 ! 128 ! ! Thickness-dependent bare ice albedo 132 129 WHERE ( 1.5 < ph_ice ) ; zalb_it = zalb 133 130 ELSE WHERE( 1.0 < ph_ice .AND. ph_ice <= 1.5 ) ; zalb_it = 0.472 + 2.0 * ( zalb - 0.472 ) * ( ph_ice - 1.0 ) … … 137 134 ELSE WHERE ; zalb_it = 0.1 + 3.6 * ph_ice 138 135 END WHERE 139 140 IF ( ld_pnd ) THEN 141 ! Depth-dependent ponded ice albedo142 z href_pnd = 0.05 ! Characteristic length scale for thickness dependence of ponded ice albedo, Lecomte et al (2015)143 zalb_pnd = rn_alb_dpnd - ( rn_alb_dpnd - zalb_it ) * EXP( - ph_pnd / zhref_pnd )144 145 ! Snow-free ice albedo is a function of pond fraction146 WHERE ( ph_snw == 0._wp .AND. pt_ice >= rt0_ice ) ; zalb_it = zalb_it * ( 1. - pafrac_pnd ) + zalb_pnd * pafrac_pnd ;END WHERE136 ! 137 IF ( ld_pnd ) THEN ! Depth-dependent ponded ice albedo 138 z1_href_pnd = 1. / 0.05 ! inverse of the characteristic length scale (Lecomte et al. 2015) 139 zalb_pnd = rn_alb_dpnd - ( rn_alb_dpnd - zalb_it ) * EXP( - ph_pnd * z1_href_pnd ) 140 ! ! Snow-free ice albedo is a function of pond fraction 141 WHERE ( ph_snw == 0._wp .AND. pt_ice >= rt0_ice ) 142 zalb_it = zalb_it * ( 1. - pafrac_pnd ) + zalb_pnd * pafrac_pnd 143 END WHERE 147 144 ENDIF 148 145 ! 146 !!gm: optimization ( rn_alb_smlt - rn_alb_imlt ) * r1_c2 can be computed one for all 147 !!gm before the DO-loop below 149 148 DO jl = 1, jpl 150 149 DO jj = 1, jpj 151 150 DO ji = 1, jpi 152 ! Freezing snow151 ! ! Freezing snow 153 152 ! no effect of underlying ice layer IF snow thickness > c1. Albedo does not depend on snow thick if > c2 154 zswitch 155 zalb_sf 156 & + ph_snw(ji,jj,jl) * ( rn_alb_sdry - zalb_it(ji,jj,jl) ) /c1 ) &157 & +zswitch * rn_alb_sdry158 159 ! Melting snow153 zswitch = 1._wp - MAX( 0._wp , SIGN( 1._wp , - ( ph_snw(ji,jj,jl) - c1 ) ) ) 154 zalb_sf = ( 1._wp - zswitch ) * ( zalb_it(ji,jj,jl) & 155 & + ph_snw(ji,jj,jl) * ( rn_alb_sdry - zalb_it(ji,jj,jl) ) * r1_c1 ) & 156 & + zswitch * rn_alb_sdry 157 ! 158 ! ! Melting snow 160 159 ! no effect of underlying ice layer. Albedo does not depend on snow thick IF > c2 161 zswitch = MAX( 0._wp , SIGN( 1._wp , ph_snw(ji,jj,jl) - c2 ) ) 162 zalb_sm = ( 1._wp - zswitch ) * ( rn_alb_imlt + ph_snw(ji,jj,jl) * ( rn_alb_smlt - rn_alb_imlt ) / c2 ) & 163 & + zswitch * rn_alb_smlt 160 zswitch = MAX( 0._wp , SIGN( 1._wp , ph_snw(ji,jj,jl) - c2 ) ) 161 zalb_sm = ( 1._wp - zswitch ) * ( rn_alb_imlt + ph_snw(ji,jj,jl) * ( rn_alb_smlt - rn_alb_imlt ) * r1_c2 ) & 162 & + zswitch * rn_alb_smlt 163 ! 164 ! ! Snow albedo 165 zswitch = MAX( 0._wp , SIGN( 1._wp , pt_ice(ji,jj,jl) - rt0_snow ) ) 166 zalb_st = zswitch * zalb_sm + ( 1._wp - zswitch ) * zalb_sf 164 167 ! 165 ! Snow albedo 166 zswitch = MAX( 0._wp , SIGN( 1._wp , pt_ice(ji,jj,jl) - rt0_snow ) ) 167 zalb_st = zswitch * zalb_sm + ( 1._wp - zswitch ) * zalb_sf 168 169 ! Surface albedo 168 ! ! Surface albedo 170 169 zswitch = 1._wp - MAX( 0._wp , SIGN( 1._wp , - ph_snw(ji,jj,jl) ) ) 171 170 pa_ice_cs(ji,jj,jl) = zswitch * zalb_st + ( 1._wp - zswitch ) * zalb_it(ji,jj,jl) … … 174 173 END DO 175 174 END DO 176 175 ! 177 176 pa_ice_os(:,:,:) = pa_ice_cs(:,:,:) + rcloud ! Oberhuber correction for overcast sky 178 179 !------------------------------------------ 180 ! New parameterization (2016) 181 !------------------------------------------ 182 ! NB: This parameterization is based on overcast skies values 183 184 CASE( 1 ) 185 186 ! compilation of values from literature (reference overcast sky values) 187 ! rn_alb_sdry = 0.85 ! dry snow 188 ! rn_alb_smlt = 0.75 ! melting snow 189 ! rn_alb_idry = 0.60 ! bare frozen ice 190 ! rn_alb_dpnd = 0.36 ! ponded-ice overcast albedo (Lecomte et al, 2015) 191 ! ! early melt pnds 0.27, late melt ponds 0.14 Grenfell & Perovich 192 ! Perovich et al 2002 (Sheba) => the only dataset for which all types of ice/snow were retrieved 193 ! rn_alb_sdry = 0.85 ! dry snow 194 ! rn_alb_smlt = 0.72 ! melting snow 195 ! rn_alb_idry = 0.65 ! bare frozen ice 196 ! Brandt et al 2005 (East Antarctica) 197 ! rn_alb_sdry = 0.87 ! dry snow 198 ! rn_alb_smlt = 0.82 ! melting snow 199 ! rn_alb_idry = 0.54 ! bare frozen ice 200 ! 201 ! Computation of snow-free ice albedo 177 ! 178 ! 179 ! !------------------------------------------ 180 CASE( 1 ) ! New parameterization (2016) ! (based on overcast sky values) 181 ! !------------------------------------------ 182 ! 183 ! compilation of values from literature (reference overcast sky values) 184 ! rn_alb_sdry = 0.85 ! dry snow 185 ! rn_alb_smlt = 0.75 ! melting snow 186 ! rn_alb_idry = 0.60 ! bare frozen ice 187 ! rn_alb_dpnd = 0.36 ! ponded-ice overcast albedo (Lecomte et al, 2015) 188 ! ! early melt pnds 0.27, late melt ponds 0.14 Grenfell & Perovich 189 ! Perovich et al 2002 (Sheba) => the only dataset for which all types of ice/snow were retrieved 190 ! rn_alb_sdry = 0.85 ! dry snow 191 ! rn_alb_smlt = 0.72 ! melting snow 192 ! rn_alb_idry = 0.65 ! bare frozen ice 193 ! Brandt et al 2005 (East Antarctica) 194 ! rn_alb_sdry = 0.87 ! dry snow 195 ! rn_alb_smlt = 0.82 ! melting snow 196 ! rn_alb_idry = 0.54 ! bare frozen ice 197 ! 198 ! !--- Computation of snow-free ice albedo 202 199 z1_c1 = 1. / ( LOG(1.5) - LOG(0.05) ) 203 200 z1_c2 = 1. / 0.05 204 201 205 ! Accounting for the ice-thickness dependency206 WHERE ( 1.5 < ph_ice ) ;zalb_it = zalb207 ELSE WHERE( 0.05 < ph_ice .AND. ph_ice <= 1.5 ) ; zalb_it = zalb + ( 0.18 - zalb ) * z1_c1 * &208 & ( LOG(1.5) - LOG(ph_ice) )209 E LSE WHERE ; zalb_it = rn_alb_oce + ( 0.18 - rn_alb_oce ) * z1_c2 * ph_ice210 END WHERE211 212 IF ( ld_pnd ) THEN213 ! Depth-dependent ponded ice albedo214 zhref_pnd = 0.05 ! Characteristic length scale for thickness dependence of ponded ice albedo, Lecomte et al (2015)215 zalb_pnd = rn_alb_dpnd - ( rn_alb_dpnd - zalb_it ) * EXP( - ph_pnd / zhref_pnd )216 217 ! Snow-free ice albedo is weighted mean of ponded ice and bare ice contributions218 WHERE ( ph_snw == 0._wp .AND. pt_ice >= rt0_ice ) ; zalb_it = zalb_it * ( 1. - pafrac_pnd ) + zalb_pnd * pafrac_pnd ;END WHERE202 ! !--- Accounting for the ice-thickness dependency 203 WHERE ( 1.5 < ph_ice ) ; zalb_it = zalb 204 ELSE WHERE( 0.05 < ph_ice .AND. ph_ice <= 1.5 ) ; zalb_it = zalb + ( 0.18 - zalb ) * z1_c1 * ( LOG(1.5) - LOG(ph_ice) ) 205 ELSE WHERE ; zalb_it = rn_alb_oce + ( 0.18 - rn_alb_oce ) * z1_c2 * ph_ice 206 END WHERE 207 ! 208 IF ( ld_pnd ) THEN ! Depth-dependent ponded ice albedo 209 z1_href_pnd = 0.05 ! inverse of the characteristic length scale (Lecomte et al. 2015) 210 zalb_pnd = rn_alb_dpnd - ( rn_alb_dpnd - zalb_it ) * EXP( - ph_pnd * z1_href_pnd ) 211 ! 212 ! ! Snow-free ice albedo is weighted mean of ponded ice and bare ice contributions 213 WHERE ( ph_snw == 0._wp .AND. pt_ice >= rt0_ice ) 214 zalb_it = zalb_it * ( 1. - pafrac_pnd ) + zalb_pnd * pafrac_pnd 215 END WHERE 219 216 ENDIF 220 217 ! 218 ! !--- Overcast sky surface albedo (accounting for snow, ice melt ponds) 221 219 z1_c1 = 1. / 0.02 222 220 z1_c2 = 1. / 0.03 223 224 ! Overcast sky surface albedo (accounting for snow, ice melt ponds)225 221 DO jl = 1, jpl 226 222 DO jj = 1, jpj … … 241 237 END DO 242 238 END DO 243 244 ! Clear sky surface albedo239 ! 240 ! !--- Clear sky surface albedo 245 241 pa_ice_cs = pa_ice_os - ( - 0.1010 * pa_ice_os * pa_ice_os + 0.1933 * pa_ice_os - 0.0148 ); 246 247 !--------------------------------------------------- 248 ! Fractional surface-based parameterization (2017) 249 !--------------------------------------------------- 250 CASE( 2 ) 251 252 ! MV: I propose this formulation that is more elegant, and more easy to expand towards 253 ! varying pond and snow fraction. 254 ! Formulation 1 has issues to handle ponds and snow together that 255 ! can't easily be fixed. This one handles it better, I believe. 256 257 !----------------------------------------- 258 ! Snow, bare ice and ponded ice fractions 259 !----------------------------------------- 260 ! Specific fractions (zafrac) refer to relative area covered by snow within each ice category 261 262 !--- Effective pond fraction (for now, we prevent melt ponds and snow at the same time) 263 zafrac_pnd = 0._wp 264 IF ( ld_pnd ) THEN 265 WHERE( ph_snw == 0._wp ) ; zafrac_pnd = pafrac_pnd ; END WHERE ! Snow fully "shades" melt ponds 266 ENDIF 267 268 !--- Specific snow fraction (for now, prescribed) 269 WHERE ( ph_snw > 0._wp ) ; zafrac_snw = 1. 270 ELSE WHERE ; zafrac_snw = 0. 271 END WHERE 272 273 !--- Specific ice fraction 274 zafrac_ice = 1. - zafrac_snw - zafrac_pnd 275 276 !-------------------------------------------------- 277 ! Snow-covered, pond-covered, and bare ice albedos 278 !-------------------------------------------------- 279 ! Bare ice albedo 280 z1_c1 = 1. / ( LOG(1.5) - LOG(0.05) ) 281 z1_c2 = 1. / 0.05 282 WHERE ( 1.5 < ph_ice ) ; zalb_ice = zalb 283 ELSE WHERE( 0.05 < ph_ice .AND. ph_ice <= 1.5 ) ; zalb_ice = zalb + ( 0.18 - zalb ) * z1_c1 * & 242 ! 243 ! 244 ! !------------------------------------------ 245 CASE( 2 ) ! Fractional surface-based parameterization (2017) 246 ! !------------------------------------------ 247 ! MV: I propose this formulation that is more elegant, and more easy to expand towards 248 ! varying pond and snow fraction. 249 ! Formulation 1 has issues to handle ponds and snow together that can't easily be fixed. 250 ! This one handles it better, I believe. 251 ! 252 ! !== Snow, bare ice and ponded ice fractions ==! 253 ! 254 ! ! Specific fractions (zafrac) refer to relative area covered by snow within each ice category 255 ! 256 ! !--- Effective pond fraction (for now, we prevent melt ponds and snow at the same time) 257 zafrac_pnd = 0._wp 258 IF ( ld_pnd ) THEN 259 WHERE( ph_snw == 0._wp ) ; zafrac_pnd = pafrac_pnd ; END WHERE ! Snow fully "shades" melt ponds 260 ENDIF 261 ! 262 ! !--- Specific snow fraction (for now, prescribed) 263 WHERE ( ph_snw > 0._wp ) ; zafrac_snw = 1. 264 ELSE WHERE ; zafrac_snw = 0. 265 END WHERE 266 ! 267 ! !--- Specific ice fraction 268 zafrac_ice = 1. - zafrac_snw - zafrac_pnd 269 ! 270 ! !== Snow-covered, pond-covered, and bare ice albedos ==! 271 ! 272 ! !--- Bare ice albedo 273 z1_c1 = 1. / ( LOG(1.5) - LOG(0.05) ) 274 z1_c2 = 1. / 0.05 275 WHERE ( 1.5 < ph_ice ) ; zalb_ice = zalb 276 ELSE WHERE( 0.05 < ph_ice .AND. ph_ice <= 1.5 ) ; zalb_ice = zalb + ( 0.18 - zalb ) * z1_c1 * & 284 277 & ( LOG(1.5) - LOG(ph_ice) ) 285 ELSE WHERE ; zalb_ice = rn_alb_oce + ( 0.18 - rn_alb_oce ) * z1_c2 * ph_ice 286 END WHERE 287 288 ! Snow-covered ice albedo (freezing, melting cases) 289 z1_c1 = 1. / 0.02 290 z1_c2 = 1. / 0.03 291 292 WHERE( pt_ice < rt0_snow ) ; zalb_snw = rn_alb_sdry - ( rn_alb_sdry - zalb_ice ) * EXP( - ph_snw * z1_c1 ); 293 ELSE WHERE ; zalb_snw = rn_alb_smlt - ( rn_alb_smlt - zalb_ice ) * EXP( - ph_snw * z1_c2 ); 294 END WHERE 295 296 ! Depth-dependent ponded ice albedo 297 IF ( ld_pnd ) THEN 298 zhref_pnd = 0.05 ! Characteristic length scale for thickness dependence of ponded ice albedo, Lecomte et al (2015) 299 zalb_pnd = rn_alb_dpnd - ( rn_alb_dpnd - zalb_ice ) * EXP( - ph_pnd / zhref_pnd ) 300 ELSE 301 zalb_pnd = rn_alb_dpnd 302 ENDIF 303 304 ! Surface albedo is weighted mean of snow, ponds and bare ice contributions 305 pa_ice_os = zafrac_snw * zalb_snw + zafrac_pnd * zalb_pnd + zafrac_ice * zalb_ice 306 307 pa_ice_cs = pa_ice_os - ( - 0.1010 * pa_ice_os * pa_ice_os + 0.1933 * pa_ice_os - 0.0148 ) 278 ELSE WHERE ; zalb_ice = rn_alb_oce + ( 0.18 - rn_alb_oce ) * z1_c2 * ph_ice 279 END WHERE 280 ! 281 z1_c1 = 1. / 0.02 !--- Snow-covered ice albedo (freezing, melting cases) 282 z1_c2 = 1. / 0.03 283 ! 284 WHERE( pt_ice < rt0_snow ) ; zalb_snw = rn_alb_sdry - ( rn_alb_sdry - zalb_ice ) * EXP( - ph_snw * z1_c1 ); 285 ELSE WHERE ; zalb_snw = rn_alb_smlt - ( rn_alb_smlt - zalb_ice ) * EXP( - ph_snw * z1_c2 ); 286 END WHERE 287 ! 288 IF ( ld_pnd ) THEN !--- Depth-dependent ponded ice albedo 289 z1_href_pnd = 0.05 ! inverse of the characteristic length scale (Lecomte et al. 2015) 290 zalb_pnd = rn_alb_dpnd - ( rn_alb_dpnd - zalb_ice ) * EXP( - ph_pnd * z1_href_pnd ) 291 ELSE 292 zalb_pnd = rn_alb_dpnd 293 ENDIF 294 ! !--- Surface albedo is weighted mean of snow, ponds and bare ice contributions 295 pa_ice_os = zafrac_snw * zalb_snw + zafrac_pnd * zalb_pnd + zafrac_ice * zalb_ice 296 pa_ice_cs = pa_ice_os - ( - 0.1010 * pa_ice_os * pa_ice_os + 0.1933 * pa_ice_os - 0.0148 ) 308 297 309 298 END SELECT … … 311 300 END SUBROUTINE ice_alb 312 301 302 313 303 SUBROUTINE alb_init 314 304 !!---------------------------------------------------------------------- … … 320 310 !!---------------------------------------------------------------------- 321 311 INTEGER :: ios ! Local integer output status for namelist read 312 !! 322 313 NAMELIST/namicealb/ nn_ice_alb, rn_alb_sdry, rn_alb_smlt, rn_alb_idry, rn_alb_imlt, rn_alb_dpnd 323 314 !!---------------------------------------------------------------------- … … 353 344 !! Default option Dummy module NO LIM 3.0 sea-ice model 354 345 !!---------------------------------------------------------------------- 355 CONTAINS356 !357 SUBROUTINE ice_alb ! Dummy routine358 WRITE(*,*) 'ice_alb: You should not have seen this print! error?'359 END SUBROUTINE ice_alb360 346 #endif 361 347 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icecor.F90
r8426 r8486 9 9 #if defined key_lim3 10 10 !!---------------------------------------------------------------------- 11 !! 'key_lim3' LIM3 sea-ice model12 !!---------------------------------------------------------------------- 13 !! ice_cor : computes update of sea-ice global variables from trend terms14 !!---------------------------------------------------------------------- 15 USE dom_oce 16 USE phycst 17 USE ice 18 USE ice1D ! LIMthermodynamic sea-ice variables19 USE iceitd 20 USE icevar 21 USE icectl !control prints11 !! 'key_lim3' LIM3 sea-ice model 12 !!---------------------------------------------------------------------- 13 !! ice_cor : computes update of sea-ice global variables from trend terms 14 !!---------------------------------------------------------------------- 15 USE dom_oce ! ocean domain 16 USE phycst ! physical constants 17 USE ice ! sea-ice: variable 18 USE ice1D ! sea-ice: thermodynamic sea-ice variables 19 USE iceitd ! sea-ice: rebining 20 USE icevar ! sea-ice: operations 21 USE icectl ! sea-ice: control prints 22 22 ! 23 USE in_out_manager 24 USE lib_fortran 25 USE lbclnk 26 USE lib_mpp 27 USE timing 23 USE in_out_manager ! I/O manager 24 USE lib_fortran ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 25 USE lbclnk ! lateral boundary condition - MPP link 26 USE lib_mpp ! MPP library 27 USE timing ! Timing 28 28 29 29 IMPLICIT NONE 30 30 PRIVATE 31 31 32 PUBLIC ice_cor 32 PUBLIC ice_cor ! called by icestp.F90 33 33 34 34 !! * Substitutions 35 35 # include "vectopt_loop_substitute.h90" 36 36 !!---------------------------------------------------------------------- 37 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)37 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 38 38 !! $Id: icecor.F90 8378 2017-07-26 13:55:59Z clem $ 39 39 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 41 41 CONTAINS 42 42 43 SUBROUTINE ice_cor( kt 44 !!------------------------------------------------------------------- 43 SUBROUTINE ice_cor( kt, kn ) 44 !!---------------------------------------------------------------------- 45 45 !! *** ROUTINE ice_cor *** 46 46 !! 47 !! ** Purpose : Computes update of sea-ice global variables at 48 !! the end of the dynamics. 49 !! 50 !!--------------------------------------------------------------------- 47 !! ** Purpose : Computes corrections on sea-ice global variables at 48 !! the end of the dynamics. 49 !!---------------------------------------------------------------------- 51 50 INTEGER, INTENT(in) :: kt ! number of iteration 52 51 INTEGER, INTENT(in) :: kn ! 1 = after dyn ; 2 = after thermo 52 ! 53 53 INTEGER :: ji, jj, jk, jl ! dummy loop indices 54 REAL(wp) :: zsal 55 REAL(wp) :: zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b 56 !!------------------------------------------------------------------- 57 IF( nn_timing == 1 ) CALL timing_start('icecor') 58 54 REAL(wp) :: zsal, zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b, zzc 55 !!---------------------------------------------------------------------- 56 IF( nn_timing == 1 ) CALL timing_start('icecor') 57 ! 59 58 IF( kt == nit000 .AND. lwp .AND. kn == 2 ) THEN 60 59 WRITE(numout,*) 61 WRITE(numout,*)' icecor ' 62 WRITE(numout,*)' ~~~~~~ ' 63 ENDIF 64 65 ! conservation test 66 IF( ln_limdiachk ) CALL ice_cons_hsm(0, 'icecor', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 67 68 !---------------------------------------------------------------------- 69 ! Constrain the thickness of the smallest category above himin 70 !---------------------------------------------------------------------- 71 IF( kn == 2 ) THEN 72 60 WRITE(numout,*)' icecor : correct sea ice variables if out of bounds ' 61 WRITE(numout,*)' ~~~~~~~' 62 ENDIF 63 ! !--- conservation test 64 IF( ln_limdiachk ) CALL ice_cons_hsm(0, 'icecor', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 65 ! 66 ! 67 ! !----------------------------------------------------- 68 IF( kn == 2 ) THEN ! thickness of the smallest category above himin ! 69 ! !----------------------------------------------------- 70 ! 73 71 DO jj = 1, jpj 74 72 DO ji = 1, jpi 73 !!gm replace this 75 74 rswitch = MAX( 0._wp , SIGN( 1._wp, a_i(ji,jj,1) - epsi20 ) ) !0 if no ice and 1 if yes 76 75 ht_i(ji,jj,1) = v_i (ji,jj,1) / MAX( a_i(ji,jj,1) , epsi20 ) * rswitch 76 !!gm by more readable coding (not slower coding since already a IF in the loop): 77 ! IF( a_i(ji,jj,1) >= epsi20 ) ht_i(ji,jj,1) = v_i (ji,jj,1) / a_i(ji,jj,1) 78 !!gm 77 79 IF( v_i(ji,jj,1) > 0._wp .AND. ht_i(ji,jj,1) < rn_himin ) THEN 78 80 a_i (ji,jj,1) = a_i (ji,jj,1) * ht_i(ji,jj,1) / rn_himin … … 80 82 END DO 81 83 END DO 82 83 ENDIF 84 85 !---------------------------------------------------- 86 ! ice concentration should not exceed amax 87 !----------------------------------------------------- 88 at_i(:,:) = 0._wp 89 DO jl = 1, jpl 84 ! 85 ENDIF 86 87 ! !----------------------------------------------------- 88 at_i(:,:) = a_i(:,:,1) ! ice concentration should not exceed amax ! 89 DO jl = 2, jpl !----------------------------------------------------- 90 90 at_i(:,:) = a_i(:,:,jl) + at_i(:,:) 91 91 END DO 92 92 ! 93 !!gm Question it seams to me that we have the following equality (dropping the "(ji,jj)": 94 ! ( 1. - ( 1. - rn_amax_2d / at_i ) ) = ( 1. - ( at_i - rn_amax_2d ) / at_i ) 95 ! = ( at_i - ( at_i - rn_amax_2d ) ) / at_i 96 ! = ( + rn_amax_2d ) / at_i 97 ! = rn_amax_2d / at_i 98 ! No ? if yes see "!!gm better" juste below 99 !gm 93 100 DO jl = 1, jpl 94 101 DO jj = 1, jpj 95 102 DO ji = 1, jpi 96 103 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) ) ) 104 a_i(ji,jj,jl) = a_i(ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax_2d(ji,jj) / at_i(ji,jj) ) ) 105 !!gm better: a_i(ji,jj,jl) = a_i(ji,jj,jl) * rn_amax_2d(ji,jj) / at_i(ji,jj) 98 106 ENDIF 99 107 END DO 100 108 END DO 101 109 END DO 110 !!gm Other question: why testing a_i(ji,jj,jl) > 0._wp ? a_i is >=0, a multiplication by 0 does not change the results.... 111 !!gm so at the end, the loop can be recoded without IF as: 112 ! WHERE( at_i(:,:) > rn_amax_2d(:,:) ) 113 ! DO jl = 1, jpl 114 ! a_i(:,:,jl) = a_i(:,:,jl) * MAX( rn_amax_2d(:,:), at_i(:,:) ) / at_i(:,:) 115 ! END DO 116 ! END WHERE 117 !!gm No? 102 118 103 ! ---------------------104 ! Ice salinity bounds105 ! ---------------------106 IF ( nn_icesal == 2 ) THEN107 DO jl = 1, jpl 119 ! !----------------------------------------------------- 120 IF ( nn_icesal == 2 ) THEN ! Ice salinity bounds ! 121 ! !----------------------------------------------------- 122 zzc = rhoic * r1_rdtice 123 DO jl = 1, jpl ! salinity stays in bounds [Simin,Simax] 108 124 DO jj = 1, jpj 109 125 DO ji = 1, jpi 110 zsal = smv_i(ji,jj,jl) 111 ! salinity stays in bounds 112 rswitch = 1._wp - MAX( 0._wp, SIGN( 1._wp, - v_i(ji,jj,jl) ) ) 113 smv_i(ji,jj,jl) = rswitch * MAX( MIN( rn_simax * v_i(ji,jj,jl), smv_i(ji,jj,jl) ), rn_simin * v_i(ji,jj,jl) ) 126 zsal = smv_i(ji,jj,jl) 127 smv_i(ji,jj,jl) = MIN( MAX( rn_simin*v_i(ji,jj,jl) , smv_i(ji,jj,jl) ) , rn_simax*v_i(ji,jj,jl) ) 114 128 ! associated salt flux 115 sfx_res(ji,jj) = sfx_res(ji,jj) - ( smv_i(ji,jj,jl) - zsal ) * rhoic * r1_rdtice129 sfx_res(ji,jj) = sfx_res(ji,jj) - ( smv_i(ji,jj,jl) - zsal ) * zzc 116 130 END DO 117 131 END DO … … 119 133 ENDIF 120 134 121 !---------------------------------------------------- 122 ! Rebin categories with thickness out of bounds 123 !---------------------------------------------------- 124 IF ( jpl > 1 ) CALL ice_itd_reb 125 126 !----------------- 127 ! zap small values 128 !----------------- 129 CALL ice_var_zapsmall 130 131 !---------------------------------------------- 132 ! Ice drift. Corrections to avoid wrong values 133 !---------------------------------------------- 134 IF( kn == 2 ) THEN 135 DO jj = 2, jpjm1 135 ! !----------------------------------------------------- 136 ! ! Rebin categories with thickness out of bounds ! 137 ! !----------------------------------------------------- 138 IF ( jpl > 1 ) CALL ice_itd_reb 139 140 ! !----------------------------------------------------- 141 CALL ice_var_zapsmall ! Zap small values ! 142 ! !----------------------------------------------------- 143 144 ! !----------------------------------------------------- 145 IF( kn == 2 ) THEN ! Ice drift case: Corrections to avoid wrong values ! 146 DO jj = 2, jpjm1 !----------------------------------------------------- 136 147 DO ji = 2, jpim1 137 IF ( at_i(ji,jj) == 0._wp ) THEN ! what to do if there is no ice138 IF ( at_i(ji+1,jj) == 0._wp ) u_ice(ji,jj) = 0._wp! right side139 IF ( at_i(ji-1,jj) == 0._wp ) u_ice(ji-1,jj) = 0._wp! left side140 IF ( at_i(ji,jj+1) == 0._wp ) v_ice(ji,jj) = 0._wp! upper side141 IF ( at_i(ji,jj-1) == 0._wp ) v_ice(ji,jj-1) = 0._wp! bottom side148 IF ( at_i(ji,jj) == 0._wp ) THEN ! what to do if there is no ice 149 IF ( at_i(ji+1,jj) == 0._wp ) u_ice(ji ,jj) = 0._wp ! right side 150 IF ( at_i(ji-1,jj) == 0._wp ) u_ice(ji-1,jj) = 0._wp ! left side 151 IF ( at_i(ji,jj+1) == 0._wp ) v_ice(ji,jj ) = 0._wp ! upper side 152 IF ( at_i(ji,jj-1) == 0._wp ) v_ice(ji,jj-1) = 0._wp ! bottom side 142 153 ENDIF 143 154 END DO 144 155 END DO 145 !lateral boundary conditions146 CALL lbc_lnk_multi( u_ice, 'U', -1., v_ice, 'V', -1. )147 !mask velocities 148 u_ice(:,:) = u_ice(:,:) * umask(:,:,1) 156 CALL lbc_lnk_multi( u_ice, 'U', -1., v_ice, 'V', -1. ) ! lateral boundary conditions 157 ! 158 !!gm I think masking here is unnecessary, u_ice already masked and we only introduce zeros in the field 159 u_ice(:,:) = u_ice(:,:) * umask(:,:,1) ! mask velocities 149 160 v_ice(:,:) = v_ice(:,:) * vmask(:,:,1) 150 161 ENDIF 151 152 ! ------------------------------------------------- 153 ! Diagnostics 154 ! ------------------------------------------------- 155 IF( kn == 1 ) THEN 162 163 !!gm I guess the trends are only out on demand 164 !! So please, only do this is it exite an iom_use of on a these variables 165 !! furthermore, only allocate the diag_ arrays in this case 166 !! and do the iom_put here so that it is only a local allocation 167 !!gm 168 ! !----------------------------------------------------- 169 SELECT CASE( kn ) ! Diagnostics ! 170 ! !----------------------------------------------------- 171 CASE( 1 ) !--- dyn trend diagnostics 156 172 DO jl = 1, jpl 157 173 afx_dyn(:,:) = afx_dyn(:,:) + ( a_i(:,:,jl) - a_i_b(:,:,jl) ) * r1_rdtice 158 174 END DO 159 175 ! 176 !!gm here I think the number of ice cat is too small to use a SUM instruction... 160 177 DO jj = 1, jpj 161 178 DO ji = 1, jpi 162 ! heat content variation (W.m-2) 163 diag_heat(ji,jj) = - ( SUM( e_i(ji,jj,1:nlay_i,:) - e_i_b(ji,jj,1:nlay_i,:) ) + & 164 & SUM( e_s(ji,jj,1:nlay_s,:) - e_s_b(ji,jj,1:nlay_s,:) ) & 165 & ) * r1_rdtice 166 ! salt, volume 179 ! ! heat content variation (W.m-2) 180 diag_heat(ji,jj) = - ( SUM( e_i(ji,jj,1:nlay_i,:) - e_i_b(ji,jj,1:nlay_i,:) ) & 181 & + SUM( e_s(ji,jj,1:nlay_s,:) - e_s_b(ji,jj,1:nlay_s,:) ) ) * r1_rdtice 182 ! ! salt, volume 167 183 diag_smvi(ji,jj) = SUM( smv_i(ji,jj,:) - smv_i_b(ji,jj,:) ) * rhoic * r1_rdtice 168 184 diag_vice(ji,jj) = SUM( v_i (ji,jj,:) - v_i_b (ji,jj,:) ) * rhoic * r1_rdtice … … 170 186 END DO 171 187 END DO 172 173 ELSEIF( kn == 2 ) THEN174 188 ! 189 CASE( 2 ) !--- thermo trend diagnostics & ice aging 190 ! 175 191 DO jl = 1, jpl 176 oa_i(:,:,jl) = oa_i(:,:,jl) + a_i(:,:,jl) * rdt_ice ! ice natural aging 177 afx_thd(:,:) = afx_thd(:,:) + ( a_i(:,:,jl) - a_i_b(:,:,jl) ) * r1_rdtice 178 END DO 179 afx_tot = afx_thd + afx_dyn 180 192 oa_i(:,:,jl) = oa_i(:,:,jl) + a_i(:,:,jl) * rdt_ice ! ice natural aging incrementation 193 afx_thd(:,:) = afx_thd(:,:) + ( a_i(:,:,jl) - a_i_b(:,:,jl) ) * r1_rdtice ! thermo tendancy 194 END DO 195 afx_tot(:,:) = afx_thd(:,:) + afx_dyn(:,:) 196 ! 197 !!gm here I think the number of ice cat is too small to use a SUM instruction... 181 198 DO jj = 1, jpj 182 199 DO ji = 1, jpi 183 ! heat content variation (W.m-2) 184 diag_heat(ji,jj) = diag_heat(ji,jj) - & 185 & ( SUM( e_i(ji,jj,1:nlay_i,:) - e_i_b(ji,jj,1:nlay_i,:) ) + & 186 & SUM( e_s(ji,jj,1:nlay_s,:) - e_s_b(ji,jj,1:nlay_s,:) ) & 187 & ) * r1_rdtice 188 ! salt, volume 200 ! ! heat content variation (W.m-2) 201 diag_heat(ji,jj) = diag_heat(ji,jj) - ( SUM( e_i(ji,jj,1:nlay_i,:) - e_i_b(ji,jj,1:nlay_i,:) ) & 202 & + SUM( e_s(ji,jj,1:nlay_s,:) - e_s_b(ji,jj,1:nlay_s,:) ) ) * r1_rdtice 203 ! ! salt, volume 189 204 diag_smvi(ji,jj) = diag_smvi(ji,jj) + SUM( smv_i(ji,jj,:) - smv_i_b(ji,jj,:) ) * rhoic * r1_rdtice 190 205 diag_vice(ji,jj) = diag_vice(ji,jj) + SUM( v_i (ji,jj,:) - v_i_b (ji,jj,:) ) * rhoic * r1_rdtice … … 192 207 END DO 193 208 END DO 194 195 ENDIF 196 197 ! conservation test 198 IF( ln_limdiachk ) CALL ice_cons_hsm(1, 'icecor', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 199 200 ! control prints 201 IF( ln_ctl ) CALL ice_prt3D( 'icecor' ) 202 IF( ln_limctl .AND. kn == 2 ) & 203 & CALL ice_prt( kt, iiceprt, jiceprt, 2, ' - Final state - ' ) 204 205 IF( nn_timing == 1 ) CALL timing_stop('icecor') 206 209 ! 210 END SELECT 211 ! 212 ! !--- conservation test 213 IF( ln_limdiachk ) CALL ice_cons_hsm(1, 'icecor', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 214 ! 215 ! !--- control prints 216 IF( ln_ctl ) CALL ice_prt3D( 'icecor' ) 217 IF( ln_limctl .AND. kn == 2 ) CALL ice_prt( kt, iiceprt, jiceprt, 2, ' - Final state - ' ) 218 ! 219 IF( nn_timing == 1 ) CALL timing_stop('icecor') 220 ! 207 221 END SUBROUTINE ice_cor 208 222 223 #else 224 !!---------------------------------------------------------------------- 225 !! Default option Dummy module NO LIM 3.0 sea-ice model 226 !!---------------------------------------------------------------------- 209 227 #endif 210 228 229 !!====================================================================== 211 230 END MODULE icecor -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icectl.F90
r8426 r8486 9 9 #if defined key_lim3 10 10 !!---------------------------------------------------------------------- 11 !! 'key_lim3' LIM3 sea-ice model11 !! 'key_lim3' LIM3 sea-ice model 12 12 !!---------------------------------------------------------------------- 13 13 !! ice_ctl : control prints in case of crash … … 15 15 !! ice_prt3D : control prints of ice arrays 16 16 !!---------------------------------------------------------------------- 17 USE oce 18 USE dom_oce 19 USE ice 20 USE ice1D 21 USE sbc_oce 22 USE sbc_ice 23 USE phycst 17 USE oce ! ocean dynamics and tracers 18 USE dom_oce ! ocean space and time domain 19 USE ice ! LIM-3: ice variables 20 USE ice1D ! LIM-3: thermodynamical variables 21 USE sbc_oce ! Surface boundary condition: ocean fields 22 USE sbc_ice ! Surface boundary condition: ice fields 23 USE phycst ! Define parameters for the routines 24 24 ! 25 USE lib_mpp 26 USE timing 27 USE in_out_manager 28 USE prtctl 29 USE lib_fortran 25 USE lib_mpp ! MPP library 26 USE timing ! Timing 27 USE in_out_manager ! I/O manager 28 USE prtctl ! Print control 29 USE lib_fortran ! 30 30 31 31 IMPLICIT NONE … … 41 41 # include "vectopt_loop_substitute.h90" 42 42 !!---------------------------------------------------------------------- 43 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)43 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 44 44 !! $Id: icectl.F90 5043 2015-01-28 16:44:18Z clem $ 45 45 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 46 46 !!---------------------------------------------------------------------- 47 48 47 CONTAINS 49 48 50 49 SUBROUTINE ice_cons_hsm( icount, cd_routine, zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b ) 51 !!---------------------------------------------------------------------- ----------------------------------52 !! 50 !!---------------------------------------------------------------------- 51 !! *** ROUTINE ice_cons_hsm *** 53 52 !! 54 53 !! ** Purpose : Test the conservation of heat, salt and mass for each ice routine … … 61 60 !! For salt and heat thresholds, ice is considered to have a salinity of 10 62 61 !! and a heat content of 3e5 J/kg (=latent heat of fusion) 63 !!-------------------------------------------------------------------------------------------------------- 64 INTEGER , INTENT(in) :: icount ! determine wether this is the beggining of the routine (0) or the end (1) 65 CHARACTER(len=*), INTENT(in) :: cd_routine ! name of the routine 66 REAL(wp) , INTENT(inout) :: zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b 62 !!---------------------------------------------------------------------- 63 INTEGER , INTENT(in) :: icount ! called at: =0 the begining of the routine, =1 the end 64 CHARACTER(len=*), INTENT(in) :: cd_routine ! name of the routine 65 REAL(wp) , INTENT(inout) :: zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b ! ???? 66 !! 67 67 REAL(wp) :: zvi, zsmv, zei, zfs, zfw, zft 68 68 REAL(wp) :: zvmin, zamin, zamax … … 70 70 REAL(wp) :: zarea, zv_sill, zs_sill, zh_sill 71 71 REAL(wp), PARAMETER :: zconv = 1.e-9 ! convert W to GW and kg to Mt 72 72 !!---------------------------------------------------------------------- 73 74 !!gm Note that glo_sum for a 2D or 3D array use a multiplication by tmask_i(ji,jj) 75 !! so below the * tmask(:,:,1) is useless ===>> I have removed them 76 !! I also move the conversion factor from then glo_sum argument (become a single multiplication 77 73 78 IF( icount == 0 ) THEN 74 75 ! salt flux 79 ! ! salt flux 76 80 zfs_b = glob_sum( ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) + & 77 81 & sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) + sfx_sub(:,:) + sfx_lam(:,:) & 78 & ) * e1e2t(:,:) * tmask(:,:,1) * zconv )79 80 ! water flux82 & ) * e1e2t(:,:) ) * zconv 83 ! 84 ! ! water flux 81 85 zfw_b = glob_sum( -( wfx_bog(:,:) + wfx_bom(:,:) + wfx_sum(:,:) + wfx_sni(:,:) + & 82 86 & wfx_opw(:,:) + wfx_res(:,:) + wfx_dyn(:,:) + wfx_lam(:,:) + wfx_ice_sub(:,:) + & 83 & wfx_snw_sni(:,:) + wfx_snw_sum(:,:) + wfx_snw_dyn(:,:) + wfx_snw_sub(:,:) + wfx_spr(:,:) 84 & ) * e1e2t(:,:) * tmask(:,:,1) * zconv )85 86 ! heat flux87 & wfx_snw_sni(:,:) + wfx_snw_sum(:,:) + wfx_snw_dyn(:,:) + wfx_snw_sub(:,:) + wfx_spr(:,:) & 88 & ) * e1e2t(:,:) ) * zconv 89 ! 90 ! ! heat flux 87 91 zft_b = glob_sum( ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:) & 88 92 & - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:) & 89 & ) * e1e2t(:,:) * tmask(:,:,1) * zconv ) 90 91 zvi_b = glob_sum( SUM( v_i * rhoic + v_s * rhosn, dim=3 ) * e1e2t * tmask(:,:,1) * zconv ) 92 93 zsmv_b = glob_sum( SUM( smv_i * rhoic , dim=3 ) * e1e2t * tmask(:,:,1) * zconv ) 94 95 zei_b = glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) + & 96 & SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 ) & 97 ) * e1e2t * tmask(:,:,1) * zconv ) 93 & ) * e1e2t(:,:) ) * zconv 94 95 zvi_b = glob_sum( SUM( v_i * rhoic + v_s * rhosn, dim=3 ) * e1e2t * zconv ) 96 97 zsmv_b = glob_sum( SUM( smv_i * rhoic , dim=3 ) * e1e2t * zconv ) 98 99 zei_b = glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) & 100 & + SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 ) ) * e1e2t ) * zconv 98 101 99 102 ELSEIF( icount == 1 ) THEN … … 102 105 zfs = glob_sum( ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) + & 103 106 & sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) + sfx_sub(:,:) + sfx_lam(:,:) & 104 & ) * e1e2t(:,:) * tmask(:,:,1) * zconv )- zfs_b107 & ) * e1e2t(:,:) ) * zconv - zfs_b 105 108 106 109 ! water flux … … 108 111 & wfx_opw(:,:) + wfx_res(:,:) + wfx_dyn(:,:) + wfx_lam(:,:) + wfx_ice_sub(:,:) + & 109 112 & wfx_snw_sni(:,:) + wfx_snw_sum(:,:) + wfx_snw_dyn(:,:) + wfx_snw_sub(:,:) + wfx_spr(:,:) & 110 & ) * e1e2t(:,:) * tmask(:,:,1) * zconv )- zfw_b113 & ) * e1e2t(:,:) ) * zconv - zfw_b 111 114 112 115 ! heat flux 113 116 zft = glob_sum( ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:) & 114 117 & - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:) & 115 & ) * e1e2t(:,:) * tmask(:,:,1) * zconv )- zft_b118 & ) * e1e2t(:,:) ) * zconv - zft_b 116 119 117 120 ! outputs 118 zvi = ( ( glob_sum( SUM( v_i * rhoic + v_s * rhosn, dim=3 ) &119 & * e1e2t * tmask(:,:,1) * zconv )- zvi_b ) * r1_rdtice - zfw ) * rday120 121 zsmv = ( ( glob_sum( SUM( smv_i * rhoic , dim=3 ) &122 & * e1e2t * tmask(:,:,1) * zconv )- zsmv_b ) * r1_rdtice + zfs ) * rday123 124 zei = ( glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) +&125 & SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 )&126 & ) * e1e2t * tmask(:,:,1) * zconv )- zei_b ) * r1_rdtice + zft121 zvi = ( ( glob_sum( SUM( v_i * rhoic + v_s * rhosn, dim=3 ) * e1e2t ) * zconv & 122 & - zvi_b ) * r1_rdtice - zfw ) * rday 123 124 zsmv = ( ( glob_sum( SUM( smv_i * rhoic , dim=3 ) * e1e2t ) * zconv & 125 & - zsmv_b ) * r1_rdtice + zfs ) * rday 126 127 zei = ( glob_sum( ( SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 ) & 128 & + SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 ) ) * e1e2t ) * zconv & 129 & - zei_b ) * r1_rdtice + zft 127 130 128 131 ! zvtrp and zetrp must be close to 0 if the advection scheme is conservative 129 zvtrp = glob_sum( ( diag_trp_vi * rhoic + diag_trp_vs * rhosn ) * e1e2t * tmask(:,:,1) * zconv )* rday130 zetrp = glob_sum( ( diag_trp_ei + diag_trp_es ) * e1e2t * tmask(:,:,1) * zconv )132 zvtrp = glob_sum( ( diag_trp_vi * rhoic + diag_trp_vs * rhosn ) * e1e2t ) * zconv * rday 133 zetrp = glob_sum( ( diag_trp_ei + diag_trp_es ) * e1e2t ) * zconv 131 134 132 135 zvmin = glob_min( v_i ) … … 135 138 136 139 ! set threshold values and calculate the ice area (+epsi10 to set a threshold > 0 when there is no ice) 137 zarea = glob_sum( SUM( a_i + epsi10, dim=3 ) * e1e2t * zconv )! in 1.e9 m2140 zarea = glob_sum( SUM( a_i + epsi10, dim=3 ) * e1e2t ) * zconv ! in 1.e9 m2 138 141 zv_sill = zarea * 2.5e-5 139 142 zs_sill = zarea * 25.e-5 … … 156 159 IF ( zamin < -epsi10 ) WRITE(numout,*) 'violation a_i<0 (',cd_routine,') = ',zamin 157 160 ENDIF 158 161 ! 159 162 ENDIF 160 163 … … 163 166 164 167 SUBROUTINE ice_cons_final( cd_routine ) 165 !!---------------------------------------------------------------------- -----------------------------------166 !! 168 !!---------------------------------------------------------------------- 169 !! *** ROUTINE ice_cons_final *** 167 170 !! 168 171 !! ** Purpose : Test the conservation of heat, salt and mass at the end of each ice time-step … … 174 177 !! For salt and heat thresholds, ice is considered to have a salinity of 10 175 178 !! and a heat content of 3e5 J/kg (=latent heat of fusion) 176 !!---------------------------------------------------------------------- ----------------------------------179 !!---------------------------------------------------------------------- 177 180 CHARACTER(len=*), INTENT(in) :: cd_routine ! name of the routine 178 181 REAL(wp) :: zhfx, zsfx, zvfx 179 182 REAL(wp) :: zarea, zv_sill, zs_sill, zh_sill 180 183 REAL(wp), PARAMETER :: zconv = 1.e-9 ! convert W to GW and kg to Mt 184 !!---------------------------------------------------------------------- 181 185 182 186 ! heat flux 183 187 zhfx = glob_sum( ( hfx_in - hfx_out - diag_heat - diag_trp_ei - diag_trp_es & 184 188 ! & - SUM( qevap_ice * a_i_b, dim=3 ) & !!clem: I think this line must be commented (but need check) 185 & ) * e1e2t * tmask(:,:,1) * zconv )189 & ) * e1e2t ) * zconv 186 190 ! salt flux 187 zsfx = glob_sum( ( sfx + diag_smvi ) * e1e2t * tmask(:,:,1) * zconv )* rday191 zsfx = glob_sum( ( sfx + diag_smvi ) * e1e2t ) * zconv * rday 188 192 ! water flux 189 zvfx = glob_sum( ( wfx_ice + wfx_snw + wfx_spr + wfx_sub + diag_vice + diag_vsnw ) * e1e2t * tmask(:,:,1) * zconv )* rday193 zvfx = glob_sum( ( wfx_ice + wfx_snw + wfx_spr + wfx_sub + diag_vice + diag_vsnw ) * e1e2t ) * zconv * rday 190 194 191 195 ! set threshold values and calculate the ice area (+epsi10 to set a threshold > 0 when there is no ice) 192 zarea = glob_sum( SUM( a_i + epsi10, dim=3 ) * e1e2t * zconv )! in 1.e9 m2196 zarea = glob_sum( SUM( a_i + epsi10, dim=3 ) * e1e2t ) * zconv ! in 1.e9 m2 193 197 zv_sill = zarea * 2.5e-5 194 198 zs_sill = zarea * 25.e-5 195 199 zh_sill = zarea * 10.e-5 196 200 197 IF( ABS( zvfx ) > zv_sill ) WRITE(numout,*) 'violation vfx [Mt/day] (',cd_routine,') = ',(zvfx) 198 IF( ABS( zsfx ) > zs_sill ) WRITE(numout,*) 'violation sfx [psu*Mt/day] (',cd_routine,') = ',(zsfx) 199 IF( ABS( zhfx ) > zh_sill ) WRITE(numout,*) 'violation hfx [GW] (',cd_routine,') = ',(zhfx) 200 201 IF(lwp) THEN 202 IF( ABS( zvfx ) > zv_sill ) WRITE(numout,*) 'violation vfx [Mt/day] (',cd_routine,') = ',(zvfx) 203 IF( ABS( zsfx ) > zs_sill ) WRITE(numout,*) 'violation sfx [psu*Mt/day] (',cd_routine,') = ',(zsfx) 204 IF( ABS( zhfx ) > zh_sill ) WRITE(numout,*) 'violation hfx [GW] (',cd_routine,') = ',(zhfx) 205 ENDIF 206 ! 201 207 END SUBROUTINE ice_cons_final 202 208 … … 671 677 !! Default option Empty Module No LIM3 sea-ice model 672 678 !!-------------------------------------------------------------------------- 673 CONTAINS674 SUBROUTINE ice_ctl ! Empty routine675 END SUBROUTINE ice_ctl676 SUBROUTINE ice_prt ! Empty routine677 END SUBROUTINE ice_prt678 SUBROUTINE ice_prt3D ! Empty routine679 END SUBROUTINE ice_prt3D680 679 #endif 680 681 681 !!====================================================================== 682 682 END MODULE icectl -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icedia.F90
r8426 r8486 1 1 MODULE icedia 2 2 !!====================================================================== 3 !! *** MODULE limdia_hsb***4 !! LIM-3 sea ice model : diagnostics of ice model3 !! *** MODULE icedia *** 4 !! Sea-Ice model : global budgets 5 5 !!====================================================================== 6 6 !! History : 3.4 ! 2012-10 (C. Rousset) original code 7 !! 4.0 ! 2017-08 (C. Rousset) fits nemo4.0 standards 7 8 !!---------------------------------------------------------------------- 8 9 #if defined key_lim3 … … 10 11 !! 'key_lim3' LIM3 sea-ice model 11 12 !!---------------------------------------------------------------------- 12 !! lim_dia_hsb : computation and output of the time evolution of keys variables 13 !! lim_dia_hsb_init : initialization and namelist read 14 !!---------------------------------------------------------------------- 15 USE ice ! LIM-3: sea-ice variable 16 USE dom_oce ! ocean domain 17 USE sbc_oce, ONLY: sfx ! surface boundary condition: ocean fields 18 USE daymod ! model calendar 19 USE phycst ! physical constant 20 USE in_out_manager ! I/O manager 21 USE lib_mpp ! MPP library 22 USE timing ! preformance summary 23 USE iom ! I/O manager 24 USE lib_fortran ! glob_sum 25 USE icerst ! ice restart 13 !! ice_dia : diagnostic of the sea-ice global heat content, salt content and volume conservation 14 !! ice_dia_init : initialization of budget calculation 15 !! ice_dia_rst : read/write budgets restart 16 !!---------------------------------------------------------------------- 17 USE ice ! LIM-3: sea-ice variable 18 USE dom_oce ! ocean domain 19 USE phycst ! physical constant 20 USE daymod ! model calendar 21 USE sbc_oce , ONLY : sfx ! surface boundary condition: ocean fields 22 USE icerst ! ice restart 23 ! 24 USE in_out_manager ! I/O manager 25 USE lib_mpp ! MPP library 26 USE timing ! preformance summary 27 USE iom ! I/O manager 28 USE lib_fortran ! glob_sum 26 29 27 30 IMPLICIT NONE … … 36 39 !! * Substitutions 37 40 # include "vectopt_loop_substitute.h90" 38 39 !!---------------------------------------------------------------------- 40 !! NEMO/OPA 3.4 , NEMO Consortium (2012) 41 !!---------------------------------------------------------------------- 42 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 41 43 !! $Id: icedia.F90 8413 2017-08-07 17:05:39Z clem $ 42 44 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 43 45 !!---------------------------------------------------------------------- 44 45 46 CONTAINS 46 47 … … 49 50 !! *** ROUTINE ice_dia *** 50 51 !! 51 !! ** Purpose: Compute the ice global heat content, salt content and volume conservation 52 !! 53 !!--------------------------------------------------------------------------- 54 INTEGER, INTENT(in) :: kt ! number of iteration 55 !! 56 real(wp) :: zbg_ivol, zbg_svol, zbg_area, zbg_isal, zbg_item ,zbg_stem 57 REAL(wp) :: z_frc_voltop, z_frc_volbot, z_frc_sal, z_frc_temtop, z_frc_tembot 52 !! ** Purpose: Compute the sea-ice global heat content, salt content 53 !! and volume conservation 54 !!--------------------------------------------------------------------------- 55 INTEGER, INTENT(in) :: kt ! ocean time step 56 !! 57 REAL(wp) :: zbg_ivol, zbg_item, zbg_area, zbg_isal 58 REAL(wp) :: zbg_svol, zbg_stem 59 REAL(wp) :: z_frc_voltop, z_frc_temtop, z_frc_sal 60 REAL(wp) :: z_frc_volbot, z_frc_tembot 58 61 REAL(wp) :: zdiff_vol, zdiff_sal, zdiff_tem 59 62 !!--------------------------------------------------------------------------- … … 62 65 IF( kt == nit000 .AND. lwp ) THEN 63 66 WRITE(numout,*) 64 WRITE(numout,*)'icedia '67 WRITE(numout,*)'icedia : outpout ice diagnostics (integrated over the domain)' 65 68 WRITE(numout,*)'~~~~~~' 66 69 ENDIF 67 70 71 !!gm glob_sum includes a " * tmask_i ", so remove " * tmask(:,:,1) " 72 68 73 ! ----------------------- ! 69 74 ! 1 - Contents ! 70 75 ! ----------------------- ! 71 zbg_ivol = glob_sum( vt_i(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )! ice volume (km3)72 zbg_svol = glob_sum( vt_s(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )! snow volume (km3)73 zbg_area = glob_sum( at_i(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-6 )! area (km2)74 zbg_isal = glob_sum( SUM( smv_i(:,:,:), dim=3 ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )! salt content (pss*km3)75 zbg_item = glob_sum( et_i * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 )! heat content (1.e20 J)76 zbg_stem = glob_sum( et_s * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 )! heat content (1.e20 J)76 zbg_ivol = glob_sum( vt_i(:,:) * e1e2t(:,:) ) * 1.e-9 ! ice volume (km3) 77 zbg_svol = glob_sum( vt_s(:,:) * e1e2t(:,:) ) * 1.e-9 ! snow volume (km3) 78 zbg_area = glob_sum( at_i(:,:) * e1e2t(:,:) ) * 1.e-6 ! area (km2) 79 zbg_isal = glob_sum( SUM( smv_i(:,:,:), dim=3 ) * e1e2t(:,:) ) * 1.e-9 ! salt content (pss*km3) 80 zbg_item = glob_sum( et_i * e1e2t(:,:) ) * 1.e-20 ! heat content (1.e20 J) 81 zbg_stem = glob_sum( et_s * e1e2t(:,:) ) * 1.e-20 ! heat content (1.e20 J) 77 82 78 83 ! ---------------------------! 79 84 ! 2 - Trends due to forcing ! 80 85 ! ---------------------------! 81 z_frc_volbot = r1_rau0 * glob_sum( - ( wfx_ice(:,:) + wfx_snw(:,:) + wfx_err_sub(:,:) ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )! freshwater flux ice/snow-ocean82 z_frc_voltop = r1_rau0 * glob_sum( - ( wfx_sub(:,:) + wfx_spr(:,:) ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )! freshwater flux ice/snow-atm83 z_frc_sal = r1_rau0 * glob_sum( - sfx(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )! salt fluxes ice/snow-ocean84 z_frc_tembot = glob_sum( hfx_out(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 )! heat on top of ocean (and below ice)85 z_frc_temtop = glob_sum( hfx_in (:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 )! heat on top of ice-coean86 z_frc_volbot = r1_rau0 * glob_sum( - ( wfx_ice(:,:) + wfx_snw(:,:) + wfx_err_sub(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! freshwater flux ice/snow-ocean 87 z_frc_voltop = r1_rau0 * glob_sum( - ( wfx_sub(:,:) + wfx_spr(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! freshwater flux ice/snow-atm 88 z_frc_sal = r1_rau0 * glob_sum( - sfx(:,:) * e1e2t(:,:) ) * 1.e-9 ! salt fluxes ice/snow-ocean 89 z_frc_tembot = glob_sum( hfx_out(:,:) * e1e2t(:,:) ) * 1.e-20 ! heat on top of ocean (and below ice) 90 z_frc_temtop = glob_sum( hfx_in (:,:) * e1e2t(:,:) ) * 1.e-20 ! heat on top of ice-coean 86 91 ! 87 92 frc_voltop = frc_voltop + z_frc_voltop * rdt_ice ! km3 … … 94 99 ! 3 - Content variations ! 95 100 ! ----------------------- ! 96 zdiff_vol = r1_rau0 * glob_sum( ( rhoic * vt_i(:,:) + rhosn * vt_s(:,:) - vol_loc_ini(:,:) & ! freshwater trend (km3) 97 & ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 ) 98 zdiff_sal = r1_rau0 * glob_sum( ( rhoic * SUM( smv_i(:,:,:), dim=3 ) - sal_loc_ini(:,:) & ! salt content trend (km3*pss) 99 & ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 ) 100 zdiff_tem = glob_sum( ( et_i(:,:) + et_s(:,:) - tem_loc_ini(:,:) & ! heat content trend (1.e20 J) 101 ! & + SUM( qevap_ice * a_i_b, dim=3 ) & !! clem: I think this line should be commented (but needs a check) 102 & ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 ) 101 zdiff_vol = r1_rau0 * glob_sum( ( rhoic*vt_i(:,:) + rhosn*vt_s(:,:) - vol_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! freshwater trend (km3) 102 zdiff_sal = r1_rau0 * glob_sum( ( rhoic* SUM( smv_i(:,:,:), dim=3 ) - sal_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! salt content trend (km3*pss) 103 zdiff_tem = glob_sum( ( et_i(:,:) + et_s(:,:) - tem_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-20 ! heat content trend (1.e20 J) 104 ! + SUM( qevap_ice * a_i_b, dim=3 ) !! clem: I think this term should not be there (but needs a check) 103 105 104 106 ! ----------------------- ! … … 112 114 ! 5 - Diagnostics writing ! 113 115 ! ----------------------- ! 114 ! 115 IF( iom_use('ibgvolume') ) CALL iom_put( 'ibgvolume' , zdiff_vol ) ! ice/snow volume drift (km3 equivalent ocean water) 116 IF( iom_use('ibgsaltco') ) CALL iom_put( 'ibgsaltco' , zdiff_sal ) ! ice salt content drift (psu*km3 equivalent ocean water) 117 IF( iom_use('ibgheatco') ) CALL iom_put( 'ibgheatco' , zdiff_tem ) ! ice/snow heat content drift (1.e20 J) 118 IF( iom_use('ibgheatfx') ) CALL iom_put( 'ibgheatfx' , zdiff_tem / & ! ice/snow heat flux drift (W/m2) 119 & glob_sum( e1e2t(:,:) * tmask(:,:,1) * 1.e-20 * kt*rdt ) ) 120 121 IF( iom_use('ibgfrcvoltop') ) CALL iom_put( 'ibgfrcvoltop' , frc_voltop ) ! vol forcing ice/snw-atm (km3 equivalent ocean water) 122 IF( iom_use('ibgfrcvolbot') ) CALL iom_put( 'ibgfrcvolbot' , frc_volbot ) ! vol forcing ice/snw-ocean (km3 equivalent ocean water) 123 IF( iom_use('ibgfrcsal') ) CALL iom_put( 'ibgfrcsal' , frc_sal ) ! sal - forcing (psu*km3 equivalent ocean water) 124 IF( iom_use('ibgfrctemtop') ) CALL iom_put( 'ibgfrctemtop' , frc_temtop ) ! heat on top of ice/snw/ocean (1.e20 J) 125 IF( iom_use('ibgfrctembot') ) CALL iom_put( 'ibgfrctembot' , frc_tembot ) ! heat on top of ocean(below ice) (1.e20 J) 126 IF( iom_use('ibgfrchfxtop') ) CALL iom_put( 'ibgfrchfxtop' , frc_temtop / & ! heat on top of ice/snw/ocean (W/m2) 127 & glob_sum( e1e2t(:,:) * tmask(:,:,1) * 1.e-20 * kt*rdt ) ) 128 IF( iom_use('ibgfrchfxbot') ) CALL iom_put( 'ibgfrchfxbot' , frc_tembot / & ! heat on top of ocean(below ice) (W/m2) 129 & glob_sum( e1e2t(:,:) * tmask(:,:,1) * 1.e-20 * kt*rdt ) ) 130 131 IF( iom_use('ibgvol_tot' ) ) CALL iom_put( 'ibgvol_tot' , zbg_ivol ) ! ice volume (km3) 132 IF( iom_use('sbgvol_tot' ) ) CALL iom_put( 'sbgvol_tot' , zbg_svol ) ! snow volume (km3) 133 IF( iom_use('ibgarea_tot') ) CALL iom_put( 'ibgarea_tot' , zbg_area ) ! ice area (km2) 134 IF( iom_use('ibgsalt_tot') ) CALL iom_put( 'ibgsalt_tot' , zbg_isal ) ! ice salinity content (pss*km3) 135 IF( iom_use('ibgheat_tot') ) CALL iom_put( 'ibgheat_tot' , zbg_item ) ! ice heat content (1.e20 J) 136 IF( iom_use('sbgheat_tot') ) CALL iom_put( 'sbgheat_tot' , zbg_stem ) ! snow heat content (1.e20 J) 116 !!gm I don't understand the division by the ocean surface (i.e. glob_sum( e1e2t(:,:) ) * 1.e-20 * kt*rdt ) 117 !! and its multiplication bu kt ! is it really what we want ? what is this quantity ? 118 !! IF it is really what we want, compute it at kt=nit000, not 3 time by time-step ! 119 !! kt*rdt : you mean rdtice ? 120 !!gm 121 ! 122 IF( iom_use('ibgvolume') ) CALL iom_put( 'ibgvolume' , zdiff_vol ) ! ice/snow volume drift (km3 equivalent ocean water) 123 IF( iom_use('ibgsaltco') ) CALL iom_put( 'ibgsaltco' , zdiff_sal ) ! ice salt content drift (psu*km3 equivalent ocean water) 124 IF( iom_use('ibgheatco') ) CALL iom_put( 'ibgheatco' , zdiff_tem ) ! ice/snow heat content drift (1.e20 J) 125 IF( iom_use('ibgheatfx') ) CALL iom_put( 'ibgheatfx' , & ! ice/snow heat flux drift (W/m2) 126 & zdiff_tem /glob_sum( e1e2t(:,:) * 1.e-20 * kt*rdt ) ) 127 128 IF( iom_use('ibgfrcvoltop') ) CALL iom_put( 'ibgfrcvoltop' , frc_voltop ) ! vol forcing ice/snw-atm (km3 equivalent ocean water) 129 IF( iom_use('ibgfrcvolbot') ) CALL iom_put( 'ibgfrcvolbot' , frc_volbot ) ! vol forcing ice/snw-ocean (km3 equivalent ocean water) 130 IF( iom_use('ibgfrcsal') ) CALL iom_put( 'ibgfrcsal' , frc_sal ) ! sal - forcing (psu*km3 equivalent ocean water) 131 IF( iom_use('ibgfrctemtop') ) CALL iom_put( 'ibgfrctemtop' , frc_temtop ) ! heat on top of ice/snw/ocean (1.e20 J) 132 IF( iom_use('ibgfrctembot') ) CALL iom_put( 'ibgfrctembot' , frc_tembot ) ! heat on top of ocean(below ice) (1.e20 J) 133 IF( iom_use('ibgfrchfxtop') ) CALL iom_put( 'ibgfrchfxtop' , & ! heat on top of ice/snw/ocean (W/m2) 134 & frc_temtop / glob_sum( e1e2t(:,:) ) * 1.e-20 * kt*rdt ) 135 IF( iom_use('ibgfrchfxbot') ) CALL iom_put( 'ibgfrchfxbot' , & ! heat on top of ocean(below ice) (W/m2) 136 & frc_tembot / glob_sum( e1e2t(:,:) ) * 1.e-20 * kt*rdt ) 137 138 IF( iom_use('ibgvol_tot' ) ) CALL iom_put( 'ibgvol_tot' , zbg_ivol ) ! ice volume (km3) 139 IF( iom_use('sbgvol_tot' ) ) CALL iom_put( 'sbgvol_tot' , zbg_svol ) ! snow volume (km3) 140 IF( iom_use('ibgarea_tot') ) CALL iom_put( 'ibgarea_tot' , zbg_area ) ! ice area (km2) 141 IF( iom_use('ibgsalt_tot') ) CALL iom_put( 'ibgsalt_tot' , zbg_isal ) ! ice salinity content (pss*km3) 142 IF( iom_use('ibgheat_tot') ) CALL iom_put( 'ibgheat_tot' , zbg_item ) ! ice heat content (1.e20 J) 143 IF( iom_use('sbgheat_tot') ) CALL iom_put( 'sbgheat_tot' , zbg_stem ) ! snow heat content (1.e20 J) 137 144 ! 138 145 IF( lrst_ice ) CALL ice_dia_rst( 'WRITE', kt_ice ) … … 174 181 RETURN 175 182 ENDIF 176 183 ! 177 184 CALL ice_dia_rst( 'READ' ) !* read or initialize all required files 178 185 ! 179 186 END SUBROUTINE ice_dia_init 180 187 188 181 189 SUBROUTINE ice_dia_rst( cdrw, kt ) 182 !!--------------------------------------------------------------------- 183 !! *** ROUTINE limdia_rst *** 184 !! 185 !! ** Purpose : Read or write DIA file in restart file 186 !! 187 !! ** Method : use of IOM library 188 !!---------------------------------------------------------------------- 189 CHARACTER(len=*), INTENT(in) :: cdrw ! "READ"/"WRITE" flag 190 INTEGER , INTENT(in), OPTIONAL :: kt ! ice time-step 191 REAL(wp) :: ziter 192 INTEGER :: iter 193 ! 194 !!---------------------------------------------------------------------- 195 ! 196 IF( TRIM(cdrw) == 'READ' ) THEN ! Read/initialise 197 IF( ln_rstart ) THEN !* Read the restart file 198 ! 199 CALL iom_get( numrir, 'kt_ice' , ziter ) 200 IF(lwp) WRITE(numout,*) 201 IF(lwp) WRITE(numout,*) ' ice_dia_rst read at time step = ', ziter 202 IF(lwp) WRITE(numout,*) '~~~~~~~' 203 CALL iom_get( numrir, 'frc_voltop' , frc_voltop ) 204 CALL iom_get( numrir, 'frc_volbot' , frc_volbot ) 205 CALL iom_get( numrir, 'frc_temtop' , frc_temtop ) 206 CALL iom_get( numrir, 'frc_tembot' , frc_tembot ) 207 CALL iom_get( numrir, 'frc_sal' , frc_sal ) 208 CALL iom_get( numrir, jpdom_autoglo, 'vol_loc_ini', vol_loc_ini ) 209 CALL iom_get( numrir, jpdom_autoglo, 'tem_loc_ini', tem_loc_ini ) 210 CALL iom_get( numrir, jpdom_autoglo, 'sal_loc_ini', sal_loc_ini ) 211 ELSE 212 IF(lwp) WRITE(numout,*) 213 IF(lwp) WRITE(numout,*) ' ice_dia at initial state ' 214 IF(lwp) WRITE(numout,*) '~~~~~~~' 215 ! set trends to 0 216 frc_voltop = 0._wp 217 frc_volbot = 0._wp 218 frc_temtop = 0._wp 219 frc_tembot = 0._wp 220 frc_sal = 0._wp 221 ! record initial ice volume, salt and temp 222 vol_loc_ini(:,:) = rhoic * vt_i(:,:) + rhosn * vt_s(:,:) ! ice/snow volume (kg/m2) 223 tem_loc_ini(:,:) = et_i(:,:) + et_s(:,:) ! ice/snow heat content (J) 224 sal_loc_ini(:,:) = rhoic * SUM( smv_i(:,:,:), dim=3 ) ! ice salt content (pss*kg/m2) 225 226 ENDIF 227 228 ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN ! Create restart file 229 ! ! ------------------- 230 iter = kt + nn_fsbc - 1 ! ice restarts are written at kt == nitrst - nn_fsbc + 1 231 232 IF( iter == nitrst ) THEN 233 IF(lwp) WRITE(numout,*) 234 IF(lwp) WRITE(numout,*) ' ice_dia_rst write at time step = ', kt 235 IF(lwp) WRITE(numout,*) '~~~~~~~' 236 ENDIF 237 238 ! Write in numriw (if iter == nitrst) 239 ! ------------------ 240 CALL iom_rstput( iter, nitrst, numriw, 'frc_voltop' , frc_voltop ) 241 CALL iom_rstput( iter, nitrst, numriw, 'frc_volbot' , frc_volbot ) 242 CALL iom_rstput( iter, nitrst, numriw, 'frc_temtop' , frc_temtop ) 243 CALL iom_rstput( iter, nitrst, numriw, 'frc_tembot' , frc_tembot ) 244 CALL iom_rstput( iter, nitrst, numriw, 'frc_sal' , frc_sal ) 245 CALL iom_rstput( iter, nitrst, numriw, 'vol_loc_ini', vol_loc_ini ) 246 CALL iom_rstput( iter, nitrst, numriw, 'tem_loc_ini', tem_loc_ini ) 247 CALL iom_rstput( iter, nitrst, numriw, 'sal_loc_ini', sal_loc_ini ) 248 ! 249 ENDIF 250 ! 190 !!--------------------------------------------------------------------- 191 !! *** ROUTINE limdia_rst *** 192 !! 193 !! ** Purpose : Read or write DIA file in restart file 194 !! 195 !! ** Method : use of IOM library 196 !!---------------------------------------------------------------------- 197 CHARACTER(len=*) , INTENT(in) :: cdrw ! "READ"/"WRITE" flag 198 INTEGER, OPTIONAL, INTENT(in) :: kt ! ice time-step 199 ! 200 INTEGER :: iter ! local integer 201 REAL(wp) :: ziter ! local scalar 202 !!---------------------------------------------------------------------- 203 ! 204 IF( TRIM(cdrw) == 'READ' ) THEN ! Read/initialise 205 IF( ln_rstart ) THEN !* Read the restart file 206 ! 207 CALL iom_get( numrir, 'kt_ice' , ziter ) 208 IF(lwp) WRITE(numout,*) 209 IF(lwp) WRITE(numout,*) ' ice_dia_rst read at time step = ', ziter 210 IF(lwp) WRITE(numout,*) '~~~~~~~' 211 CALL iom_get( numrir, 'frc_voltop' , frc_voltop ) 212 CALL iom_get( numrir, 'frc_volbot' , frc_volbot ) 213 CALL iom_get( numrir, 'frc_temtop' , frc_temtop ) 214 CALL iom_get( numrir, 'frc_tembot' , frc_tembot ) 215 CALL iom_get( numrir, 'frc_sal' , frc_sal ) 216 CALL iom_get( numrir, jpdom_autoglo, 'vol_loc_ini', vol_loc_ini ) 217 CALL iom_get( numrir, jpdom_autoglo, 'tem_loc_ini', tem_loc_ini ) 218 CALL iom_get( numrir, jpdom_autoglo, 'sal_loc_ini', sal_loc_ini ) 219 ELSE 220 IF(lwp) WRITE(numout,*) 221 IF(lwp) WRITE(numout,*) ' ice_dia at initial state ' 222 IF(lwp) WRITE(numout,*) '~~~~~~~' 223 ! set trends to 0 224 frc_voltop = 0._wp 225 frc_volbot = 0._wp 226 frc_temtop = 0._wp 227 frc_tembot = 0._wp 228 frc_sal = 0._wp 229 ! record initial ice volume, salt and temp 230 vol_loc_ini(:,:) = rhoic * vt_i(:,:) + rhosn * vt_s(:,:) ! ice/snow volume (kg/m2) 231 tem_loc_ini(:,:) = et_i(:,:) + et_s(:,:) ! ice/snow heat content (J) 232 sal_loc_ini(:,:) = rhoic * SUM( smv_i(:,:,:), dim=3 ) ! ice salt content (pss*kg/m2) 233 ENDIF 234 ! 235 ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN ! Create restart file 236 ! ! ------------------- 237 iter = kt + nn_fsbc - 1 ! ice restarts are written at kt == nitrst - nn_fsbc + 1 238 ! 239 IF( iter == nitrst ) THEN 240 IF(lwp) WRITE(numout,*) 241 IF(lwp) WRITE(numout,*) ' ice_dia_rst write at time step = ', kt 242 IF(lwp) WRITE(numout,*) '~~~~~~~' 243 ENDIF 244 ! 245 ! Write in numriw (if iter == nitrst) 246 ! ------------------ 247 CALL iom_rstput( iter, nitrst, numriw, 'frc_voltop' , frc_voltop ) 248 CALL iom_rstput( iter, nitrst, numriw, 'frc_volbot' , frc_volbot ) 249 CALL iom_rstput( iter, nitrst, numriw, 'frc_temtop' , frc_temtop ) 250 CALL iom_rstput( iter, nitrst, numriw, 'frc_tembot' , frc_tembot ) 251 CALL iom_rstput( iter, nitrst, numriw, 'frc_sal' , frc_sal ) 252 CALL iom_rstput( iter, nitrst, numriw, 'vol_loc_ini', vol_loc_ini ) 253 CALL iom_rstput( iter, nitrst, numriw, 'tem_loc_ini', tem_loc_ini ) 254 CALL iom_rstput( iter, nitrst, numriw, 'sal_loc_ini', sal_loc_ini ) 255 ! 256 ENDIF 257 ! 251 258 END SUBROUTINE ice_dia_rst 252 259 … … 255 262 !! Default option : Empty module NO LIM sea-ice model 256 263 !!---------------------------------------------------------------------- 257 CONTAINS258 SUBROUTINE ice_dia ! Empty routine259 END SUBROUTINE ice_dia260 264 #endif 265 261 266 !!====================================================================== 262 267 END MODULE icedia -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceforcing.F90
r8426 r8486 2 2 !!====================================================================== 3 3 !! *** MODULE iceforcing *** 4 !! call surface forcing for sea ice model4 !! Sea-Ice : air-ice forcing fields 5 5 !!===================================================================== 6 6 !! History : 4.0 ! 2017-08 (C. Rousset) Original code … … 10 10 !! 'key_lim3' : LIM 3.0 sea-ice model 11 11 !!---------------------------------------------------------------------- 12 USE oce ! ocean dynamics and tracers 13 USE dom_oce ! ocean space and time domain 14 USE ice ! LIM-3: ice variables 12 USE oce ! ocean dynamics and tracers 13 USE dom_oce ! ocean space and time domain 14 USE ice ! sea-ice variables 15 USE sbc_oce ! Surface boundary condition: ocean fields 16 USE sbc_ice ! Surface boundary condition: ice fields 17 USE usrdef_sbc ! user defined: surface boundary condition 18 USE sbcblk ! Surface boundary condition: bulk 19 USE sbccpl ! Surface boundary condition: coupled interface 20 USE icealb ! ice albedo 15 21 ! 16 USE sbc_oce ! Surface boundary condition: ocean fields 17 USE sbc_ice ! Surface boundary condition: ice fields 18 USE usrdef_sbc ! user defined: surface boundary condition 19 USE sbcblk ! Surface boundary condition: bulk 20 USE sbccpl ! Surface boundary condition: coupled interface 21 USE icealb ! ice albedo 22 ! 23 USE iom ! I/O manager library 24 USE in_out_manager ! I/O manager 25 USE lbclnk ! lateral boundary condition - MPP link 26 USE lib_mpp ! MPP library 27 USE lib_fortran ! 28 USE timing ! Timing 22 USE iom ! I/O manager library 23 USE in_out_manager ! I/O manager 24 USE lbclnk ! lateral boundary condition - MPP link 25 USE lib_mpp ! MPP library 26 USE lib_fortran ! 27 USE timing ! Timing 29 28 30 29 IMPLICIT NONE … … 37 36 # include "vectopt_loop_substitute.h90" 38 37 !!---------------------------------------------------------------------- 39 !! NEMO/ OPA 4.0 , UCL NEMO Consortium (2011)38 !! NEMO/ICE 4.0 , UCL NEMO Consortium (2017) 40 39 !! $Id: icestp.F90 8319 2017-07-11 15:00:44Z clem $ 41 40 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 113 112 !! alb_ice = albedo above sea ice 114 113 !!--------------------------------------------------------------------- 115 INTEGER, INTENT(in) :: kt ! ocean time step 116 INTEGER, INTENT(in) :: ksbc ! type of sbc flux ( 1 = user defined formulation, 117 ! 3 = bulk formulation, 118 ! 4 = Pure Coupled formulation) 114 INTEGER, INTENT(in) :: kt ! ocean time step 115 INTEGER, INTENT(in) :: ksbc ! flux formulation (user defined, bulk or Pure Coupled) 116 ! 119 117 INTEGER :: ji, jj, jl ! dummy loop index 120 118 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zalb_os, zalb_cs ! ice albedo under overcast/clear sky 121 119 REAL(wp), DIMENSION(jpi,jpj) :: zalb ! 2D workspace 122 120 !!---------------------------------------------------------------------- 123 121 ! 124 122 IF( nn_timing == 1 ) CALL timing_start('ice_forcing_flx') 125 123 … … 136 134 DO jl = 1, jpl 137 135 DO jj = 2, jpjm1 138 DO ji = 2, jpim1 136 DO ji = 2, jpim1 137 !!gm cldf_ice is a real, DOCTOR naming rule: start with cd means CHARACTER passed in argument ! 139 138 alb_ice(ji,jj,jl) = ( 1. - cldf_ice ) * zalb_cs(ji,jj,jl) + cldf_ice * zalb_os(ji,jj,jl) 140 139 END DO … … 143 142 CALL lbc_lnk( alb_ice, 'T', 1. ) 144 143 145 ! --- fluxes over sea ice --- ! 146 SELECT CASE( ksbc ) 147 CASE( jp_usr ) ! user defined formulation 148 CALL usrdef_sbc_ice_flx( kt ) 149 150 CASE( jp_blk ) ! bulk formulation 151 CALL blk_ice_flx( t_su, alb_ice ) 152 IF( ln_mixcpl ) CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su ) 153 IF( nn_limflx /= 2 ) CALL ice_flx_dist( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx ) 154 155 CASE ( jp_purecpl ) ! coupled formulation 156 CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su ) 157 IF( nn_limflx == 2 ) CALL ice_flx_dist( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx ) 158 END SELECT 159 160 ! --- albedo output --- ! 161 WHERE( at_i_b <= epsi06 ) ; zalb(:,:) = rn_alb_oce 162 ELSEWHERE ; zalb(:,:) = SUM( alb_ice * a_i_b, dim=3 ) / at_i_b 163 END WHERE 164 IF( iom_use('icealb' ) ) CALL iom_put( "icealb" , zalb(:,:) ) ! ice albedo 165 166 zalb(:,:) = SUM( alb_ice * a_i_b, dim=3 ) + rn_alb_oce * ( 1._wp - at_i_b ) 167 IF( iom_use('albedo' ) ) CALL iom_put( "albedo" , zalb(:,:) ) ! surface albedo 168 ! 144 SELECT CASE( ksbc ) !== fluxes over sea ice ==! 145 ! 146 CASE( jp_usr ) !--- user defined formulation 147 CALL usrdef_sbc_ice_flx( kt ) 148 ! 149 CASE( jp_blk ) !--- bulk formulation 150 CALL blk_ice_flx( t_su, alb_ice ) ! 151 IF( ln_mixcpl ) CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su ) 152 IF( nn_limflx /= 2 ) CALL ice_flx_dist( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx ) 153 ! 154 CASE ( jp_purecpl ) !--- coupled formulation 155 CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su ) 156 IF( nn_limflx == 2 ) CALL ice_flx_dist( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_limflx ) 157 ! 158 END SELECT 159 160 IF( iom_use('icealb') ) THEN !--- output ice albedo 161 WHERE( at_i_b <= epsi06 ) ; zalb(:,:) = rn_alb_oce 162 ELSEWHERE ; zalb(:,:) = SUM( alb_ice * a_i_b, dim=3 ) / at_i_b 163 END WHERE 164 CALL iom_put( "icealb" , zalb(:,:) ) ! ice albedo 165 ENDIF 166 167 IF( iom_use('albedo') ) THEN !--- surface albedo 168 zalb(:,:) = SUM( alb_ice * a_i_b, dim=3 ) + rn_alb_oce * ( 1._wp - at_i_b ) 169 CALL iom_put( "albedo" , zalb(:,:) ) 170 ENDIF 169 171 ! 170 172 IF( nn_timing == 1 ) CALL timing_stop('ice_forcing_flx') 171 173 ! 172 174 END SUBROUTINE ice_forcing_flx 173 175 … … 177 179 !! *** ROUTINE ice_flx_dist *** 178 180 !! 179 !! ** Purpose : update the ice surface boundary condition by averaging and / or180 !! 181 !! ** Purpose : update the ice surface boundary condition by averaging 182 !! and/or redistributing fluxes on ice categories 181 183 !! 182 184 !! ** Method : average then redistribute … … 208 210 IF( nn_timing == 1 ) CALL timing_start('ice_flx_dist') 209 211 ! 210 SELECT CASE( k_limflx ) !== averaged on all ice categories ==! 212 SELECT CASE( k_limflx ) !== averaged on all ice categories ==! 213 ! 211 214 CASE( 0 , 1 ) 212 ! 213 z_qns_m (:,:) = fice_ice_ave ( pqns_ice (:,:,:) ) 214 z_qsr_m (:,:) = fice_ice_ave ( pqsr_ice (:,:,:) ) 215 z_dqn_m (:,:) = fice_ice_ave ( pdqn_ice (:,:,:) ) 216 z_evap_m (:,:) = fice_ice_ave ( pevap_ice (:,:,:) ) 217 z_devap_m(:,:) = fice_ice_ave ( pdevap_ice (:,:,:) ) 215 z_qns_m (:,:) = fice_ice_ave( pqns_ice (:,:,:) ) 216 z_qsr_m (:,:) = fice_ice_ave( pqsr_ice (:,:,:) ) 217 z_dqn_m (:,:) = fice_ice_ave( pdqn_ice (:,:,:) ) 218 z_evap_m (:,:) = fice_ice_ave( pevap_ice (:,:,:) ) 219 z_devap_m(:,:) = fice_ice_ave( pdevap_ice(:,:,:) ) 220 !!gm faster coding 221 ! REAL(wp), DIMENSION(jpi,jpj) :: z1_at_i ! 222 ! ... 223 ! WHERE ( at_i (:,:) > 0._wp ) ; z1_at_i(:,:) = 1._wp / at_i (:,:) 224 ! ELSEWHERE ; z1_at_i(:,:) = 0._wp 225 ! END WHERE 226 ! z_qns_m (:,:) = SUM( a_i(:,:,:) * pqns_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) 227 ! z_qsr_m (:,:) = SUM( a_i(:,:,:) * pqsr_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) 228 ! z_dqn_m (:,:) = SUM( a_i(:,:,:) * pdqn_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) 229 ! z_evap_m (:,:) = SUM( a_i(:,:,:) * pevap_ice (:,:,:) , dim=3 ) * z1_at_i(:,:) 230 ! z_devap_m(:,:) = SUM( a_i(:,:,:) * pdevap_ice(:,:,:) , dim=3 ) * z1_at_i(:,:) 231 !! and remove the 2 functions: fice_ice_ave and fice_cell_ave 232 !!gm 218 233 DO jl = 1, jpl 219 pdqn_ice (:,:,jl) = z_dqn_m (:,:)234 pdqn_ice (:,:,jl) = z_dqn_m (:,:) 220 235 pdevap_ice(:,:,jl) = z_devap_m(:,:) 221 END DO 222 ! 223 DO jl = 1, jpl 224 pqns_ice (:,:,jl) = z_qns_m(:,:) 225 pqsr_ice (:,:,jl) = z_qsr_m(:,:) 226 pevap_ice(:,:,jl) = z_evap_m(:,:) 227 END DO 228 ! 229 END SELECT 230 ! 231 SELECT CASE( k_limflx ) !== redistribution on all ice categories ==! 236 pqns_ice (:,:,jl) = z_qns_m (:,:) 237 pqsr_ice (:,:,jl) = z_qsr_m (:,:) 238 pevap_ice (:,:,jl) = z_evap_m(:,:) 239 END DO 240 ! 241 END SELECT 242 ! 243 SELECT CASE( k_limflx ) !== redistribution on all ice categories ==! 232 244 CASE( 1 , 2 ) 233 245 ! 234 zalb_m(:,:) = fice_ice_ave ( palb_ice(:,:,:) )235 ztem_m(:,:) = fice_ice_ave ( ptn_ice(:,:,:) )246 zalb_m(:,:) = fice_ice_ave( palb_ice(:,:,:) ) 247 ztem_m(:,:) = fice_ice_ave( ptn_ice (:,:,:) ) 236 248 DO jl = 1, jpl 237 249 pqns_ice (:,:,jl) = pqns_ice (:,:,jl) + pdqn_ice (:,:,jl) * ( ptn_ice(:,:,jl) - ztem_m(:,:) ) … … 246 258 END SUBROUTINE ice_flx_dist 247 259 248 260 !!gm TO BE REMOVED ====>>>>> 249 261 FUNCTION fice_cell_ave ( ptab ) 250 262 !!-------------------------------------------------------------------------- 251 263 !! * Compute average over categories, for grid cell (ice covered and free ocean) 252 264 !!-------------------------------------------------------------------------- 253 REAL(wp), DIMENSION(jpi,jpj ) :: fice_cell_ave254 REAL(wp), DIMENSION(jpi,jpj ,jpl), INTENT (in) :: ptab265 REAL(wp), DIMENSION(jpi,jpj,jpl), INTENT(in) :: ptab 266 REAL(wp), DIMENSION(jpi,jpj) :: fice_cell_ave 255 267 INTEGER :: jl 256 268 !!-------------------------------------------------------------------------- 257 258 fice_cell_ave (:,:) = 0._wp 259 DO jl = 1, jpl 260 fice_cell_ave (:,:) = fice_cell_ave (:,:) + a_i (:,:,jl) * ptab (:,:,jl) 269 fice_cell_ave(:,:) = a_i(:,:,1) * ptab (:,:,1) 270 DO jl = 2, jpl 271 fice_cell_ave(:,:) = fice_cell_ave(:,:) + a_i(:,:,jl) * ptab (:,:,jl) 261 272 END DO 262 263 273 END FUNCTION fice_cell_ave 264 274 … … 268 278 !! * Compute average over categories, for ice covered part of grid cell 269 279 !!-------------------------------------------------------------------------- 270 REAL(wp), DIMENSION(jpi,jpj) :: fice_ice_ave 271 REAL(wp), DIMENSION(jpi,jpj,jpl), INTENT(in) :: ptab 272 !!-------------------------------------------------------------------------- 273 280 REAL(wp), DIMENSION(jpi,jpj,jpl), INTENT(in) :: ptab ! 281 REAL(wp), DIMENSION(jpi,jpj) :: fice_ice_ave 282 !!-------------------------------------------------------------------------- 274 283 WHERE ( at_i (:,:) > 0.0_wp ) ; fice_ice_ave (:,:) = fice_cell_ave( ptab (:,:,:) ) / at_i (:,:) 275 284 ELSEWHERE ; fice_ice_ave (:,:) = 0.0_wp 276 285 END WHERE 277 278 286 END FUNCTION fice_ice_ave 279 287 288 !!gm <<<<<<==== end of TO BE REMOVED 289 290 #else 291 !!---------------------------------------------------------------------- 292 !! Default option : Empty module NO LIM sea-ice model 293 !!---------------------------------------------------------------------- 280 294 #endif 281 295 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceist.F90
r8426 r8486 5 5 !!====================================================================== 6 6 !! History : 2.0 ! 2004-01 (C. Ethe, G. Madec) Original code 7 !! 3.0 ! 2011-02 (G. Madec) dynamical allocation 8 !! - ! 2014 (C. Rousset) add N/S initializations 7 !! 3.0 ! 2007 (M. Vancoppenolle) Rewrite for ice cats 8 !! 3.0 ! 2009-11 (M. Vancoppenolle) Enhanced version for ice cats 9 !! 3.0 ! 2011-02 (G. Madec) dynamical allocation 10 !! - ! 2014 (C. Rousset) add N/S initializations 9 11 !!---------------------------------------------------------------------- 10 12 #if defined key_lim3 11 13 !!---------------------------------------------------------------------- 12 !! 'key_lim3' :LIM3 sea-ice model13 !!---------------------------------------------------------------------- 14 !! ice_ist : Initialisation of diagnostics ice variables15 !! ice_ist_init : initialization of ice state and namelist read14 !! 'key_lim3' LIM3 sea-ice model 15 !!---------------------------------------------------------------------- 16 !! ice_ist : initialization of diagnostics ice variables 17 !! ice_ist_init : initialization of ice state and namelist read 16 18 !!---------------------------------------------------------------------- 17 19 USE phycst ! physical constant … … 34 36 PRIVATE 35 37 36 PUBLIC ice_ist ! routine called by lim_init.F9038 PUBLIC ice_ist ! called by icestp.F90 37 39 38 40 INTEGER , PARAMETER :: jpfldi = 6 ! maximum number of files to read … … 45 47 TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: si ! structure of input fields (file informations, fields read) 46 48 !!---------------------------------------------------------------------- 47 !! LIM 3.0, UCL-LOCEAN-IPSL (2008)49 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 48 50 !! $Id: iceist.F90 8378 2017-07-26 13:55:59Z clem $ 49 51 !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) … … 51 53 CONTAINS 52 54 55 !!gm better name: ice_istate 53 56 SUBROUTINE ice_ist 54 57 !!------------------------------------------------------------------- … … 71 74 !! ** Notes : o_i, t_su, t_s, t_i, s_i must be filled everywhere, even 72 75 !! where there is no ice (clem: I do not know why, is it mandatory?) 73 !!74 !! History :75 !! 2.0 ! 01-04 (C. Ethe, G. Madec) Original code76 !! 3.0 ! 2007 (M. Vancoppenolle) Rewrite for ice cats77 !! 4.0 ! 09-11 (M. Vancoppenolle) Enhanced version for ice cats78 76 !!-------------------------------------------------------------------- 79 !! * Local variables80 77 INTEGER :: ji, jj, jk, jl ! dummy loop indices 81 78 REAL(wp) :: ztmelts, zdh … … 591 588 !! Default option : Empty module NO LIM sea-ice model 592 589 !!---------------------------------------------------------------------- 593 CONTAINS594 SUBROUTINE ice_ist ! Empty routine595 END SUBROUTINE ice_ist596 590 #endif 597 591 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceitd.F90
r8426 r8486 11 11 #if defined key_lim3 12 12 !!---------------------------------------------------------------------- 13 !! 'key_lim3' :LIM3 sea-ice model13 !! 'key_lim3' LIM3 sea-ice model 14 14 !!---------------------------------------------------------------------- 15 15 !! ice_itd_rem : … … 18 18 !! ice_itd_shiftice : 19 19 !!---------------------------------------------------------------------- 20 USE par_oce 21 USE dom_oce 22 USE phycst ! physical constants (ocean directory)23 USE ice1D ! LIM-3thermodynamic variables24 USE ice ! LIM-3variables25 USE icectl !conservation tests26 USE icetab 20 USE par_oce ! ocean parameters 21 USE dom_oce ! ocean domain 22 USE phycst ! physical constants 23 USE ice1D ! sea-ice: thermodynamic variables 24 USE ice ! sea-ice: variables 25 USE icectl ! sea-ice: conservation tests 26 USE icetab ! sea-ice: convert 1D<=>2D 27 27 ! 28 USE prtctl 29 USE in_out_manager 30 USE lib_mpp 31 USE lib_fortran 28 USE prtctl ! Print control 29 USE in_out_manager ! I/O manager 30 USE lib_mpp ! MPP library 31 USE lib_fortran ! to use key_nosignedzero 32 32 33 33 IMPLICIT NONE … … 38 38 39 39 !!---------------------------------------------------------------------- 40 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2010)40 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 41 41 !! $Id: iceitd.F90 8420 2017-08-08 12:18:46Z clem $ 42 42 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 86 86 ! 1) Identify grid cells with ice 87 87 !----------------------------------------------------------------------------------------------- 88 nidx = 0 ;idxice(:) = 088 nidx = 0 ; idxice(:) = 0 89 89 DO jj = 1, jpj 90 90 DO ji = 1, jpi … … 118 118 ! --- New boundaries for category 1:jpl-1 --- ! 119 119 DO jl = 1, jpl - 1 120 120 ! 121 121 DO ji = 1, nidx 122 122 ! … … 134 134 zhbnew(ji,jl) = hi_max(jl) 135 135 ENDIF 136 136 ! 137 137 ! --- 2 conditions for remapping --- ! 138 138 ! 1) hn(t+1)+espi < Hn* < hn+1(t+1)-epsi … … 148 148 END DO 149 149 END DO 150 150 ! 151 151 ! --- New boundaries for category jpl --- ! 152 152 DO ji = 1, nidx … … 164 164 IF( ht_ib_2d(ji,1) > ( hi_max(1) - epsi10 ) ) idxice(ji) = 0 165 165 END DO 166 166 ! 167 167 !----------------------------------------------------------------------------------------------- 168 168 ! 3) Identify cells where remapping … … 178 178 idxice(:) = idxice2(:) 179 179 nidx = nidx2 180 180 ! 181 181 ENDIF 182 182 … … 186 186 !----------------------------------------------------------------------------------------------- 187 187 IF( nidx > 0 ) THEN 188 189 zhb0(:) = hi_max(0) ;zhb1(:) = hi_max(1)190 g0(:,:) = 0._wp ;g1(:,:) = 0._wp191 hL(:,:) = 0._wp ;hR(:,:) = 0._wp192 188 ! 189 zhb0(:) = hi_max(0) ; zhb1(:) = hi_max(1) 190 g0(:,:) = 0._wp ; g1(:,:) = 0._wp 191 hL(:,:) = 0._wp ; hR(:,:) = 0._wp 192 ! 193 193 DO jl = 1, jpl 194 194 ! 195 195 CALL tab_2d_1d( nidx, idxice(1:nidx), ht_ib_1d(1:nidx), ht_i_b(:,:,jl) ) 196 196 CALL tab_2d_1d( nidx, idxice(1:nidx), ht_i_1d (1:nidx), ht_i(:,:,jl) ) 197 197 CALL tab_2d_1d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i(:,:,jl) ) 198 198 CALL tab_2d_1d( nidx, idxice(1:nidx), v_i_1d (1:nidx), v_i(:,:,jl) ) 199 199 ! 200 200 IF( jl == 1 ) THEN 201 201 ! 202 202 ! --- g(h) for category 1 --- ! 203 CALL ice_itd_glinear( zhb0(1:nidx) , zhb1(1:nidx), ht_ib_1d(1:nidx), a_i_1d(1:nidx), & ! in204 & g0 (1:nidx,1), g1(1:nidx,1), hL(1:nidx,1) , hR(1:nidx,1) )! out205 203 CALL ice_itd_glinear( zhb0(1:nidx) , zhb1(1:nidx) , ht_ib_1d(1:nidx) , a_i_1d(1:nidx) , & ! in 204 & g0 (1:nidx,1), g1 (1:nidx,1), hL (1:nidx,1), hR (1:nidx,1) ) ! out 205 ! 206 206 ! Area lost due to melting of thin ice 207 207 DO ji = 1, nidx 208 208 ! 209 209 IF( a_i_1d(ji) > epsi10 ) THEN 210 210 ! 211 211 zdh0 = ht_i_1d(ji) - ht_ib_1d(ji) 212 212 IF( zdh0 < 0.0 ) THEN !remove area from category 1 … … 214 214 !Integrate g(1) from 0 to dh0 to estimate area melted 215 215 zetamax = MIN( zdh0, hR(ji,1) ) - hL(ji,1) 216 216 ! 217 217 IF( zetamax > 0.0 ) THEN 218 218 zx1 = zetamax … … 227 227 v_i_1d(ji) = a_i_1d(ji) * ht_i_1d(ji) ! clem-useless ? 228 228 ENDIF 229 229 ! 230 230 ELSE ! if ice accretion zdh0 > 0 231 231 ! zhbnew was 0, and is shifted to the right to account for thin ice growth in openwater (F0 = f1) 232 232 zhbnew(ji,0) = MIN( zdh0, hi_max(1) ) 233 233 ENDIF 234 234 ! 235 235 ENDIF 236 236 ! 237 237 END DO 238 238 ! 239 239 CALL tab_1d_2d( nidx, idxice(1:nidx), ht_i_1d (1:nidx), ht_i(:,:,jl) ) 240 240 CALL tab_1d_2d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i(:,:,jl) ) 241 241 CALL tab_1d_2d( nidx, idxice(1:nidx), v_i_1d (1:nidx), v_i(:,:,jl) ) 242 242 ! 243 243 ENDIF ! jl=1 244 244 ! 245 245 ! --- g(h) for each thickness category --- ! 246 CALL ice_itd_glinear( zhbnew(1:nidx,jl-1), zhbnew(1:nidx,jl), ht_i_1d(1:nidx) , a_i_1d(1:nidx), &! in247 & g0 (1:nidx,jl) , g1(1:nidx,jl) , hL(1:nidx,jl) , hR(1:nidx,jl) )! out248 246 CALL ice_itd_glinear( zhbnew(1:nidx,jl-1), zhbnew(1:nidx,jl), ht_i_1d(1:nidx) , a_i_1d(1:nidx) , & ! in 247 & g0 (1:nidx,jl ), g1 (1:nidx,jl), hL (1:nidx,jl), hR (1:nidx,jl) ) ! out 248 ! 249 249 END DO 250 250 … … 253 253 !----------------------------------------------------------------------------------------------- 254 254 DO jl = 1, jpl - 1 255 255 ! 256 256 DO ji = 1, nidx 257 257 ! 258 258 ! left and right integration limits in eta space 259 259 IF (zhbnew(ji,jl) > hi_max(jl)) THEN ! Hn* > Hn => transfer from jl to jl+1 … … 267 267 ENDIF 268 268 zetamax = MAX( zetamax, zetamin ) ! no transfer if etamax < etamin 269 269 ! 270 270 zx1 = zetamax - zetamin 271 271 zwk1 = zetamin * zetamin … … 278 278 zdaice(ji,jl) = g1(ji,jcat)*zx2 + g0(ji,jcat)*zx1 279 279 zdvice(ji,jl) = g1(ji,jcat)*zx3 + g0(ji,jcat)*zx2 + zdaice(ji,jl)*hL(ji,jcat) 280 280 ! 281 281 END DO 282 282 END DO … … 305 305 ENDIF 306 306 END DO 307 307 ! 308 308 CALL tab_1d_2d( nidx, idxice(1:nidx), ht_i_1d (1:nidx), ht_i(:,:,1) ) 309 309 CALL tab_1d_2d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i(:,:,1) ) 310 310 CALL tab_1d_2d( nidx, idxice(1:nidx), a_ip_1d (1:nidx), a_ip(:,:,1) ) 311 311 ! 312 312 ENDIF 313 314 IF( ln_limdiachk ) CALL ice_cons_hsm(1, 'iceitd_rem', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b)315 313 ! 314 IF( ln_limdiachk ) CALL ice_cons_hsm(1, 'iceitd_rem', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 315 ! 316 316 END SUBROUTINE ice_itd_rem 317 317 … … 325 325 !! ** Method : g(h) is linear and written as: g(eta) = g1(eta) + g0 326 326 !! with eta = h - HL 327 !!328 327 !!------------------------------------------------------------------ 329 328 REAL(wp), DIMENSION(:), INTENT(in ) :: HbL, HbR ! left and right category boundaries … … 333 332 ! 334 333 INTEGER :: ji ! horizontal indices 334 REAL(wp) :: z1_3 , z2_3 ! 1/3 , 2/3 335 335 REAL(wp) :: zh13 ! HbL + 1/3 * (HbR - HbL) 336 336 REAL(wp) :: zh23 ! HbL + 2/3 * (HbR - HbL) … … 339 339 !!------------------------------------------------------------------ 340 340 ! 341 DO ji = 1, nidx 342 ! 343 IF( paice(ji) > epsi10 .AND. phice(ji) > 0._wp ) THEN 344 345 ! Initialize hL and hR 346 phL(ji) = HbL(ji) 347 phR(ji) = HbR(ji) 348 349 ! Change hL or hR if hice falls outside central third of range, 350 ! so that hice is in the central third of the range [HL HR] 351 zh13 = 1.0 / 3.0 * ( 2.0 * phL(ji) + phR(ji) ) 352 zh23 = 1.0 / 3.0 * ( phL(ji) + 2.0 * phR(ji) ) 353 354 IF ( phice(ji) < zh13 ) THEN ; phR(ji) = 3._wp * phice(ji) - 2._wp * phL(ji) ! move HR to the left 355 ELSEIF( phice(ji) > zh23 ) THEN ; phL(ji) = 3._wp * phice(ji) - 2._wp * phR(ji) ! move HL to the right 356 ENDIF 357 358 ! Compute coefficients of g(eta) = g0 + g1*eta 359 zdhr = 1._wp / (phR(ji) - phL(ji)) 360 zwk1 = 6._wp * paice(ji) * zdhr 361 zwk2 = ( phice(ji) - phL(ji) ) * zdhr 362 pg0(ji) = zwk1 * ( 2._wp / 3._wp - zwk2 ) ! Eq. 14 363 pg1(ji) = 2._wp * zdhr * zwk1 * ( zwk2 - 0.5 ) ! Eq. 14 364 ! 365 ELSE ! remap_flag = .false. or a_i < epsi10 366 phL(ji) = 0._wp 367 phR(ji) = 0._wp 368 pg0(ji) = 0._wp 369 pg1(ji) = 0._wp 370 ENDIF 371 ! 372 END DO 341 z1_3 = 1._wp / 3._wp 342 z2_3 = 2._wp / 3._wp 343 ! 344 DO ji = 1, nidx 345 ! 346 IF( paice(ji) > epsi10 .AND. phice(ji) > 0._wp ) THEN 347 ! 348 ! Initialize hL and hR 349 phL(ji) = HbL(ji) 350 phR(ji) = HbR(ji) 351 ! 352 ! Change hL or hR if hice falls outside central third of range, 353 ! so that hice is in the central third of the range [HL HR] 354 zh13 = z1_3 * ( 2._wp * phL(ji) + phR(ji) ) 355 zh23 = z1_3 * ( phL(ji) + 2._wp * phR(ji) ) 356 ! 357 IF ( phice(ji) < zh13 ) THEN ; phR(ji) = 3._wp * phice(ji) - 2._wp * phL(ji) ! move HR to the left 358 ELSEIF( phice(ji) > zh23 ) THEN ; phL(ji) = 3._wp * phice(ji) - 2._wp * phR(ji) ! move HL to the right 359 ENDIF 360 ! 361 ! Compute coefficients of g(eta) = g0 + g1*eta 362 zdhr = 1._wp / (phR(ji) - phL(ji)) 363 zwk1 = 6._wp * paice(ji) * zdhr 364 zwk2 = ( phice(ji) - phL(ji) ) * zdhr 365 pg0(ji) = zwk1 * ( z2_3 - zwk2 ) ! Eq. 14 366 pg1(ji) = 2._wp * zdhr * zwk1 * ( zwk2 - 0.5_wp ) ! Eq. 14 367 ! 368 ELSE ! remap_flag = .false. or a_i < epsi10 369 phL(ji) = 0._wp 370 phR(ji) = 0._wp 371 pg0(ji) = 0._wp 372 pg1(ji) = 0._wp 373 ENDIF 374 ! 375 END DO 373 376 ! 374 377 END SUBROUTINE ice_itd_glinear … … 381 384 !! ** Purpose : shift ice across category boundaries, conserving everything 382 385 !! ( area, volume, energy, age*vol, and mass of salt ) 383 !!384 !! ** Method :385 386 !!------------------------------------------------------------------ 386 387 INTEGER , DIMENSION(:,:), INTENT(in) :: kdonor ! donor category index 387 388 REAL(wp), DIMENSION(:,:), INTENT(in) :: pdaice ! ice area transferred across boundary 388 389 REAL(wp), DIMENSION(:,:), INTENT(in) :: pdvice ! ice volume transferred across boundary 389 390 INTEGER :: ii,ij, ji, jj, jl, jl2, jl1, jk ! dummy loop indices 391 392 REAL(wp), DIMENSION(jpij,jpl) :: zaTsfn 393 REAL(wp), DIMENSION(jpij) :: zworka ! temporary array used here 394 REAL(wp), DIMENSION(jpij) :: zworkv ! temporary array used here 395 390 ! 391 INTEGER :: ji, jj, jl, jk ! dummy loop indices 392 INTEGER :: ii, ij, jl2, jl1 ! local integers 396 393 REAL(wp) :: ztrans ! ice/snow transferred 394 REAL(wp), DIMENSION(jpij) :: zworka, zworkv ! workspace 395 REAL(wp), DIMENSION(jpij,jpl) :: zaTsfn ! - - 397 396 !!------------------------------------------------------------------ 398 397 … … 421 420 DO jl = 1, jpl - 1 422 421 DO ji = 1, nidx 423 422 ! 424 423 jl1 = kdonor(ji,jl) 425 IF ( jl1 == jl ) THEN ; jl2 = jl1+1 426 ELSE ; jl2 = jl 427 ENDIF 428 429 rswitch = MAX( 0._wp , SIGN( 1._wp , v_i_2d(ji,jl1) - epsi10 ) ) 430 zworkv(ji) = pdvice(ji,jl) / MAX( v_i_2d(ji,jl1), epsi10 ) * rswitch 431 432 rswitch = MAX( 0._wp , SIGN( 1._wp , a_i_2d(ji,jl1) - epsi10 ) ) 433 zworka(ji) = pdaice(ji,jl) / MAX( a_i_2d(ji,jl1), epsi10 ) * rswitch 434 435 ! Ice areas 436 a_i_2d(ji,jl1) = a_i_2d(ji,jl1) - pdaice(ji,jl) 424 IF ( jl1 == jl ) THEN ; jl2 = jl1+1 425 ELSE ; jl2 = jl 426 ENDIF 427 ! 428 !!gm use of rswitch not faster as there is already IF in the DO-loop ==>>> use IF which is more readable 429 ! rswitch = MAX( 0._wp , SIGN( 1._wp , v_i_2d(ji,jl1) - epsi10 ) ) 430 ! zworkv(ji) = pdvice(ji,jl) / MAX( v_i_2d(ji,jl1), epsi10 ) * rswitch 431 ! ! 432 ! rswitch = MAX( 0._wp , SIGN( 1._wp , a_i_2d(ji,jl1) - epsi10 ) ) 433 ! zworka(ji) = pdaice(ji,jl) / MAX( a_i_2d(ji,jl1), epsi10 ) * rswitch 434 435 IF( v_i_2d(ji,jl1) >= epsi10 ) THEN ; zworkv(ji) = pdvice(ji,jl) / v_i_2d(ji,jl1) 436 ELSE ; zworkv(ji) = 0._wp 437 ENDIF 438 IF( a_i_2d(ji,jl1) >= epsi10 ) THEN ; zworka(ji) = pdaice(ji,jl) / a_i_2d(ji,jl1) 439 ELSE ; zworka(ji) = 0._wp 440 ENDIF 441 !!gm end 442 ! 443 a_i_2d(ji,jl1) = a_i_2d(ji,jl1) - pdaice(ji,jl) ! Ice areas 437 444 a_i_2d(ji,jl2) = a_i_2d(ji,jl2) + pdaice(ji,jl) 438 439 ! Ice volumes 440 v_i_2d(ji,jl1) = v_i_2d(ji,jl1) - pdvice(ji,jl) 445 ! 446 v_i_2d(ji,jl1) = v_i_2d(ji,jl1) - pdvice(ji,jl) ! Ice volumes 441 447 v_i_2d(ji,jl2) = v_i_2d(ji,jl2) + pdvice(ji,jl) 442 443 ! Snow volumes 444 ztrans = v_s_2d(ji,jl1) * zworkv(ji) 448 ! 449 ztrans = v_s_2d(ji,jl1) * zworkv(ji) ! Snow volumes 445 450 v_s_2d(ji,jl1) = v_s_2d(ji,jl1) - ztrans 446 451 v_s_2d(ji,jl2) = v_s_2d(ji,jl2) + ztrans 447 448 ! Ice age449 ztrans = oa_i_2d(ji,jl1) * pdaice(ji,jl) !!clem: should be * zworka(ji) but it does not work452 ! 453 ! ! Ice age 454 ztrans = oa_i_2d(ji,jl1) * pdaice(ji,jl) !!clem: should be * zworka(ji) but it does not work ???? 450 455 oa_i_2d(ji,jl1) = oa_i_2d(ji,jl1) - ztrans 451 456 oa_i_2d(ji,jl2) = oa_i_2d(ji,jl2) + ztrans 452 453 ! Ice salinity454 ztrans = smv_i_2d(ji,jl1) * zworkv(ji) 457 ! 458 ztrans = smv_i_2d(ji,jl1) * zworkv(ji) ! Ice salinity 459 455 460 smv_i_2d(ji,jl1) = smv_i_2d(ji,jl1) - ztrans 456 461 smv_i_2d(ji,jl2) = smv_i_2d(ji,jl2) + ztrans 457 458 ! Surface temperature459 ztrans = t_su_2d(ji,jl1) * pdaice(ji,jl) !!clem: should be * zworka(ji) but it does not work462 ! 463 ! ! Surface temperature 464 ztrans = t_su_2d(ji,jl1) * pdaice(ji,jl) !!clem: should be * zworka(ji) but it does not work ???? 460 465 zaTsfn(ji,jl1) = zaTsfn(ji,jl1) - ztrans 461 466 zaTsfn(ji,jl2) = zaTsfn(ji,jl2) + ztrans 462 467 ! 463 468 ! MV MP 2016 464 469 IF ( nn_pnd_scheme > 0 ) THEN 465 ! Pond fraction470 ! ! Pond fraction 466 471 ztrans = a_ip_2d(ji,jl1) * pdaice(ji,jl) !!clem: should be * zworka(ji) but it does not work 467 472 a_ip_2d(ji,jl1) = a_ip_2d(ji,jl1) - ztrans 468 473 a_ip_2d(ji,jl2) = a_ip_2d(ji,jl2) + ztrans 469 470 ! Pond volume (also proportional to da/a) 474 ! ! Pond volume (also proportional to da/a) 471 475 ztrans = v_ip_2d(ji,jl1) * pdaice(ji,jl) !!clem: should be * zworka(ji) but it does not work 472 476 v_ip_2d(ji,jl1) = v_ip_2d(ji,jl1) - ztrans … … 474 478 ENDIF 475 479 ! END MV MP 2016 476 477 END DO 478 479 ! Snow heat content 480 DO jk = 1, nlay_s 481 480 END DO 481 ! 482 DO jk = 1, nlay_s !--- Snow heat content 483 ! 482 484 DO ji = 1, nidx 483 485 ii = MOD( idxice(ji) - 1, jpi ) + 1 484 486 ij = ( idxice(ji) - 1 ) / jpi + 1 485 487 ! 486 488 jl1 = kdonor(ji,jl) 487 489 IF(jl1 == jl) THEN ; jl2 = jl+1 488 490 ELSE ; jl2 = jl 489 491 ENDIF 490 492 ! 491 493 ztrans = e_s(ii,ij,jk,jl1) * zworkv(ji) 492 494 e_s(ii,ij,jk,jl1) = e_s(ii,ij,jk,jl1) - ztrans … … 495 497 END DO 496 498 497 498 ! Ice heat content 499 DO jk = 1, nlay_i 499 DO jk = 1, nlay_i !--- Ice heat content 500 500 DO ji = 1, nidx 501 501 ii = MOD( idxice(ji) - 1, jpi ) + 1 502 502 ij = ( idxice(ji) - 1 ) / jpi + 1 503 503 ! 504 504 jl1 = kdonor(ji,jl) 505 505 IF(jl1 == jl) THEN ; jl2 = jl+1 506 506 ELSE ; jl2 = jl 507 507 ENDIF 508 508 ! 509 509 ztrans = e_i(ii,ij,jk,jl1) * zworkv(ji) 510 510 e_i(ii,ij,jk,jl1) = e_i(ii,ij,jk,jl1) - ztrans … … 512 512 END DO 513 513 END DO 514 514 ! 515 515 END DO ! boundaries, 1 to jpl-1 516 516 … … 521 521 DO ji = 1, nidx 522 522 IF ( a_i_2d(ji,jl) > epsi10 ) THEN 523 ht_i_2d(ji,jl) = v_i_2d 523 ht_i_2d(ji,jl) = v_i_2d(ji,jl) / a_i_2d(ji,jl) 524 524 t_su_2d(ji,jl) = zaTsfn(ji,jl) / a_i_2d(ji,jl) 525 525 ELSE … … 529 529 END DO 530 530 END DO 531 532 CALL tab_2d_3d( nidx, idxice(1:nidx), ht_i_2d (1:nidx,1:jpl), ht_i ) 533 CALL tab_2d_3d( nidx, idxice(1:nidx), a_i_2d (1:nidx,1:jpl), a_i ) 534 CALL tab_2d_3d( nidx, idxice(1:nidx), v_i_2d (1:nidx,1:jpl), v_i ) 535 CALL tab_2d_3d( nidx, idxice(1:nidx), v_s_2d (1:nidx,1:jpl), v_s ) 536 CALL tab_2d_3d( nidx, idxice(1:nidx), oa_i_2d (1:nidx,1:jpl), oa_i ) 537 CALL tab_2d_3d( nidx, idxice(1:nidx), smv_i_2d(1:nidx,1:jpl), smv_i ) 538 CALL tab_2d_3d( nidx, idxice(1:nidx), a_ip_2d (1:nidx,1:jpl), a_ip ) 539 CALL tab_2d_3d( nidx, idxice(1:nidx), v_ip_2d (1:nidx,1:jpl), v_ip ) 540 CALL tab_2d_3d( nidx, idxice(1:nidx), t_su_2d (1:nidx,1:jpl), t_su ) 541 531 ! 532 CALL tab_2d_3d( nidx, idxice(1:nidx), ht_i_2d (1:nidx,1:jpl), ht_i ) 533 CALL tab_2d_3d( nidx, idxice(1:nidx), a_i_2d (1:nidx,1:jpl), a_i ) 534 CALL tab_2d_3d( nidx, idxice(1:nidx), v_i_2d (1:nidx,1:jpl), v_i ) 535 CALL tab_2d_3d( nidx, idxice(1:nidx), v_s_2d (1:nidx,1:jpl), v_s ) 536 CALL tab_2d_3d( nidx, idxice(1:nidx), oa_i_2d (1:nidx,1:jpl), oa_i ) 537 CALL tab_2d_3d( nidx, idxice(1:nidx), smv_i_2d(1:nidx,1:jpl), smv_i ) 538 CALL tab_2d_3d( nidx, idxice(1:nidx), a_ip_2d (1:nidx,1:jpl), a_ip ) 539 CALL tab_2d_3d( nidx, idxice(1:nidx), v_ip_2d (1:nidx,1:jpl), v_ip ) 540 CALL tab_2d_3d( nidx, idxice(1:nidx), t_su_2d (1:nidx,1:jpl), t_su ) 542 541 ! 543 542 END SUBROUTINE ice_itd_shiftice … … 559 558 REAL(wp), DIMENSION(jpij,jpl-1) :: zdaice, zdvice ! ice area and volume transferred 560 559 !!------------------------------------------------------------------ 561 562 DO jl = 1, jpl-1 563 jdonor(:,jl) = 0 564 zdaice(:,jl) = 0._wp 565 zdvice(:,jl) = 0._wp 566 END DO 567 568 !--------------------------------------- 569 ! identify thicknesses that are too big 570 !--------------------------------------- 571 DO jl = 1, jpl - 1 572 573 nidx = 0 ; idxice(:) = 0 560 ! 561 jdonor(:,:) = 0 562 zdaice(:,:) = 0._wp 563 zdvice(:,:) = 0._wp 564 ! 565 ! !--------------------------------------- 566 DO jl = 1, jpl-1 ! identify thicknesses that are too big 567 ! !--------------------------------------- 568 nidx = 0 ; idxice(:) = 0 574 569 DO jj = 1, jpj 575 570 DO ji = 1, jpi … … 578 573 idxice( nidx ) = (jj - 1) * jpi + ji 579 574 ENDIF 580 END DO581 END DO582 575 END DO 576 END DO 577 ! 583 578 !!clem CALL tab_2d_1d( nidx, idxice(1:nidx), ht_i_1d (1:nidx), ht_i(:,:,jl) ) 584 579 CALL tab_2d_1d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i(:,:,jl) ) 585 580 CALL tab_2d_1d( nidx, idxice(1:nidx), v_i_1d (1:nidx), v_i(:,:,jl) ) 586 581 ! 587 582 DO ji = 1, nidx 588 583 jdonor(ji,jl) = jl … … 597 592 zdaice(ji,jl) = a_i_1d(ji) * 0.5_wp 598 593 zdvice(ji,jl) = v_i_1d(ji) - zdaice(ji,jl) * ( hi_max(jl) + hi_max(jl-1) ) * 0.5_wp 599 600 END DO 601 594 END DO 595 ! 602 596 IF( nidx > 0 ) THEN 603 597 CALL ice_itd_shiftice( jdonor(1:nidx,:), zdaice(1:nidx,:), zdvice(1:nidx,:) ) ! Shift jl=>jl+1 … … 610 604 END DO 611 605 612 !----------------------------------------- 613 ! Identify thicknesses that are too small 614 !----------------------------------------- 615 DO jl = jpl - 1, 1, -1 616 606 ! !----------------------------------------- 607 DO jl = jpl-1, 1, -1 ! Identify thicknesses that are too small 608 ! !----------------------------------------- 617 609 nidx = 0 ; idxice(:) = 0 618 610 DO jj = 1, jpj … … 622 614 idxice( nidx ) = (jj - 1) * jpi + ji 623 615 ENDIF 624 END DO625 END DO626 616 END DO 617 END DO 618 ! 627 619 CALL tab_2d_1d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i(:,:,jl+1) ) ! jl+1 is ok 628 620 CALL tab_2d_1d( nidx, idxice(1:nidx), v_i_1d (1:nidx), v_i(:,:,jl+1) ) ! jl+1 is ok … … 632 624 zdvice(ji,jl) = v_i_1d(ji) 633 625 END DO 634 626 ! 635 627 IF( nidx > 0 ) THEN 636 628 CALL ice_itd_shiftice( jdonor(1:nidx,:), zdaice(1:nidx,:), zdvice(1:nidx,:) ) ! Shift jl+1=>jl … … 640 632 zdvice(1:nidx,jl) = 0._wp 641 633 ENDIF 642 634 ! 643 635 END DO 644 636 ! 645 637 END SUBROUTINE ice_itd_reb 646 638 639 #else 640 !!---------------------------------------------------------------------- 641 !! Default option : Empty module NO LIM sea-ice model 642 !!---------------------------------------------------------------------- 647 643 #endif 644 648 645 !!====================================================================== 649 646 END MODULE iceitd -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icerdgrft.F90
r8426 r8486 12 12 !! 'key_lim3' LIM-3 sea-ice model 13 13 !!---------------------------------------------------------------------- 14 USE par_oce 15 USE dom_oce 16 USE phycst 17 USE sbc_oce , ONLY: sss_m, sst_m! surface boundary condition: ocean fields18 USE ice1D ! LIMthermodynamics19 USE ice ! LIMvariables20 USE icevar ! LIM21 USE icectl !control prints14 USE par_oce ! ocean parameters 15 USE dom_oce ! ocean domain 16 USE phycst ! physical constants (ocean directory) 17 USE sbc_oce , ONLY : sss_m, sst_m ! surface boundary condition: ocean fields 18 USE ice1D ! sea-ice: thermodynamics 19 USE ice ! sea-ice: variables 20 USE icevar ! sea-ice: operations 21 USE icectl ! sea-ice: control prints 22 22 ! 23 USE lbclnk 24 USE lib_mpp 25 USE in_out_manager 26 USE iom 27 USE lib_fortran 28 USE timing 23 USE lbclnk ! lateral boundary condition - MPP exchanges 24 USE lib_mpp ! MPP library 25 USE in_out_manager ! I/O manager 26 USE iom ! I/O manager 27 USE lib_fortran ! glob_sum 28 USE timing ! Timing 29 29 30 30 IMPLICIT NONE … … 32 32 33 33 PUBLIC ice_rdgrft ! called by ice_stp 34 PUBLIC ice_rdgrft_icestrength 35 PUBLIC ice_rdgrft_init 36 PUBLIC ice_rdgrft_alloc ! called by ice_init34 PUBLIC ice_rdgrft_icestrength ! called by icerhg_evp 35 PUBLIC ice_rdgrft_init ! called by ice_stp 36 PUBLIC ice_rdgrft_alloc ! called by ice_init 37 37 38 38 !----------------------------------------------------------------------- … … 52 52 REAL(wp), PARAMETER :: kraft = 0.5_wp ! rafting multipliyer 53 53 54 REAL(wp) :: Cp ! 54 !!gm Cp is 1) not DOCTOR, 55 !! 2) misleading name: heat capacity instead of a constant, 56 !! 3) recomputed at each time-step, whereas it is stored in the module memory... 57 !! ===>>> compute it one for all inside the IF( kt == nit000 ) (i.e. without the ".AND. lwp") 58 REAL(wp) :: Cp ! ??? !!gm Not doctor ! 59 55 60 ! 56 61 ! 57 62 !!---------------------------------------------------------------------- 58 !! NEMO/ LIM3 3.3 , UCL - NEMO Consortium (2010)63 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 59 64 !! $Id: icerdgrft.F90 8378 2017-07-26 13:55:59Z clem $ 60 65 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 66 71 !! *** ROUTINE ice_rdgrft_alloc *** 67 72 !!---------------------------------------------------------------------! 68 ALLOCATE( & 69 !* Variables shared among ridging subroutines 70 & asum (jpi,jpj) , athorn(jpi,jpj,0:jpl) , aksum (jpi,jpj) , & 71 & hrmin(jpi,jpj,jpl) , hraft(jpi,jpj,jpl) , aridge(jpi,jpj,jpl) , & 72 & hrmax(jpi,jpj,jpl) , krdg (jpi,jpj,jpl) , araft (jpi,jpj,jpl) , STAT=ice_rdgrft_alloc ) 73 ALLOCATE( asum (jpi,jpj) , athorn(jpi,jpj,0:jpl) , aksum (jpi,jpj) , & 74 & hrmin(jpi,jpj,jpl) , hraft (jpi,jpj,jpl) , aridge(jpi,jpj,jpl) , & 75 & hrmax(jpi,jpj,jpl) , krdg (jpi,jpj,jpl) , araft (jpi,jpj,jpl) , STAT=ice_rdgrft_alloc ) 73 76 ! 74 77 IF( ice_rdgrft_alloc /= 0 ) CALL ctl_warn( 'ice_rdgrft_alloc: failed to allocate arrays' ) … … 105 108 INTEGER, INTENT(in) :: kt ! number of iteration 106 109 !! 107 INTEGER :: ji, jj, jk, jl 108 INTEGER :: niter 109 INTEGER :: iterate_ridging ! if true, repeat the ridging110 REAL(wp) :: za, zfac 110 INTEGER :: ji, jj, jk, jl ! dummy loop index 111 INTEGER :: niter ! local integer 112 INTEGER :: iterate_ridging ! if =1, repeat the ridging 113 REAL(wp) :: za, zfac, zcs_2 ! local scalar 111 114 CHARACTER (len = 15) :: fieldid 112 REAL(wp), DIMENSION(jpi,jpj) 113 114 REAL(wp), DIMENSION(jpi,jpj) 115 REAL(wp), DIMENSION(jpi,jpj) 116 REAL(wp), DIMENSION(jpi,jpj) 115 REAL(wp), DIMENSION(jpi,jpj) :: closing_net ! net rate at which area is removed (1/s) 116 ! ! (ridging ice area - area of new ridges) / dt 117 REAL(wp), DIMENSION(jpi,jpj) :: divu_adv ! divu as implied by transport scheme (1/s) 118 REAL(wp), DIMENSION(jpi,jpj) :: opning ! rate of opening due to divergence/shear 119 REAL(wp), DIMENSION(jpi,jpj) :: closing_gross ! rate at which area removed, not counting area of new ridges 117 120 ! 118 121 INTEGER, PARAMETER :: nitermax = 20 … … 124 127 IF( kt == nit000 .AND. lwp ) THEN 125 128 WRITE(numout,*) 126 WRITE(numout,*)'icerdgrft '127 WRITE(numout,*)'~~~~~~~~~ '129 WRITE(numout,*)'icerdgrft : ice ridging and rafting' 130 WRITE(numout,*)'~~~~~~~~~~' 128 131 ENDIF 129 130 ! conservation test 131 IF( ln_limdiachk ) CALL ice_cons_hsm(0, 'icerdgrft', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 132 !!gm should be: 133 ! IF( kt == nit000 ) THEN 134 ! IF(lwp) WRITE(numout,*) 135 ! IF(lwp) WRITE(numout,*)'icerdgrft : ???' 136 ! IF(lwp) WRITE(numout,*)'~~~~~~~~~~' 137 ! ! 138 ! Cp = 0.5 * grav * (rau0-rhoic) * rhoic * r1_rau0 ! proport const for PE 139 ! ! 140 !!gm why not adding here zcs_2 computation 141 ! ! 142 ! ENDIF 143 !!gm end 144 145 ! ! conservation test 146 IF( ln_limdiachk ) CALL ice_cons_hsm(0, 'icerdgrft', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 132 147 133 148 !-----------------------------------------------------------------------------! 134 149 ! 1) Thickness categories boundaries, ice / o.w. concentrations, init_ons 135 150 !-----------------------------------------------------------------------------! 136 Cp = 0.5 * grav * (rau0-rhoic) * rhoic * r1_rau0! proport const for PE137 !138 CALL ice_rdgrft_ridgeprep ! prepare ridging139 !140 141 DO jj = 1, jpj ! Initialize arrays.151 Cp = 0.5 * grav * (rau0-rhoic) * rhoic * r1_rau0 ! proport const for PE 152 zcs_2 = rn_cs * 0.5_wp 153 ! 154 CALL ice_rdgrft_ridgeprep ! prepare ridging 155 ! 156 DO jj = 1, jpj ! Initialize arrays. 142 157 DO ji = 1, jpi 143 144 158 !-----------------------------------------------------------------------------! 145 159 ! 2) Dynamical inputs (closing rate, divu_adv, opning) … … 161 175 ! (thick, newly ridged ice). 162 176 163 closing_net(ji,jj) = rn_cs * 0.5* ( delta_i(ji,jj) - ABS( divu_i(ji,jj) ) ) - MIN( divu_i(ji,jj), 0._wp )177 closing_net(ji,jj) = zcs_2 * ( delta_i(ji,jj) - ABS( divu_i(ji,jj) ) ) - MIN( divu_i(ji,jj), 0._wp ) 164 178 165 179 ! 2.2 divu_adv … … 233 247 ! 3.3 Redistribute area, volume, and energy. 234 248 !-----------------------------------------------------------------------------! 235 236 249 CALL ice_rdgrft_ridgeshift( opning, closing_gross ) 237 238 250 239 251 ! 3.4 Compute total area of ice plus open water after ridging. … … 246 258 ! Check whether asum = 1. If not (because the closing and opening 247 259 ! rates were reduced above), ridge again with new rates. 248 249 260 iterate_ridging = 0 250 261 DO jj = 1, jpj … … 262 273 END DO 263 274 END DO 264 265 275 IF( lk_mpp ) CALL mpp_max( iterate_ridging ) 266 276 267 277 ! Repeat if necessary. 268 278 ! NOTE: If strength smoothing is turned on, the ridging must be 269 ! iterated globally because of the boundary update in the 270 ! smoothing. 271 279 ! iterated globally because of the boundary update in the smoothing. 272 280 niter = niter + 1 273 281 ! 274 282 IF( iterate_ridging == 1 ) THEN 275 283 CALL ice_rdgrft_ridgeprep … … 279 287 ENDIF 280 288 ENDIF 281 289 ! 282 290 END DO !! on the do while over iter 283 291 … … 287 295 ! control prints 288 296 !-----------------------------------------------------------------------------! 289 ! conservation test290 IF( ln_limdiachk ) CALL ice_cons_hsm(1, 'icerdgrft', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b)291 292 ! control prints293 IF( ln_ctl )CALL ice_prt3D( 'icerdgrft' )297 ! ! conservation test 298 IF( ln_limdiachk ) CALL ice_cons_hsm(1, 'icerdgrft', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 299 300 ! ! control prints 301 IF( ln_ctl ) CALL ice_prt3D( 'icerdgrft' ) 294 302 ! 295 303 IF( nn_timing == 1 ) CALL timing_stop('icerdgrft') 304 ! 296 305 END SUBROUTINE ice_rdgrft 306 297 307 298 308 SUBROUTINE ice_rdgrft_ridgeprep … … 305 315 !! participating in ridging and of the resulting ridges. 306 316 !!---------------------------------------------------------------------! 307 INTEGER :: ji, jj, jl ! dummy loop indices308 REAL(wp) :: Gstari, astari, hrmean, zdummy ! local scalar 317 INTEGER :: ji, jj, jl ! dummy loop indices 318 REAL(wp) :: Gstari, astari, hrmean, zdummy ! local scalar !!gm DOCTOR norme should start with z !!!!! 309 319 REAL(wp), DIMENSION(jpi,jpj,-1:jpl) :: Gsum ! Gsum(n) = sum of areas in categories 0 to n 310 320 !------------------------------------------------------------------------------! 311 321 312 Gstari = 1.0/rn_gstar 313 astari = 1.0/rn_astar 314 aksum(:,:) = 0.0 315 athorn(:,:,:) = 0.0 316 aridge(:,:,:) = 0.0 317 araft (:,:,:) = 0.0 318 319 ! Zero out categories with very small areas 320 CALL ice_var_zapsmall 321 322 ! Ice thickness needed for rafting 323 DO jl = 1, jpl 324 DO jj = 1, jpj 325 DO ji = 1, jpi 326 rswitch = MAX( 0._wp , SIGN( 1._wp, a_i(ji,jj,jl) - epsi20 ) ) 327 ht_i(ji,jj,jl) = v_i (ji,jj,jl) / MAX( a_i(ji,jj,jl) , epsi20 ) * rswitch 328 END DO 329 END DO 330 END DO 322 Gstari = 1._wp / rn_gstar 323 astari = 1._wp / rn_astar 324 aksum(:,:) = 0._wp 325 athorn(:,:,:) = 0._wp 326 aridge(:,:,:) = 0._wp 327 araft (:,:,:) = 0._wp 328 329 CALL ice_var_zapsmall ! Zero out categories with very small areas 330 331 ! DO jl = 1, jpl ! Ice thickness needed for rafting 332 ! DO jj = 1, jpj 333 ! DO ji = 1, jpi 334 !!gm rswitch = MAX( 0._wp , SIGN( 1._wp, a_i(ji,jj,jl) - epsi20 ) ) 335 !!gm ht_i(ji,jj,jl) = v_i (ji,jj,jl) / MAX( a_i(ji,jj,jl) , epsi20 ) * rswitch 336 ! IF( a_i(ji,jj,jl) >= epsi20 ) THEN ; ht_i(ji,jj,jl) = v_i (ji,jj,jl) / a_i(ji,jj,jl) 337 ! ELSE ; ht_i(ji,jj,jl) = 0._wp 338 ! ENDIF 339 ! END DO 340 ! END DO 341 ! END DO 342 !!gm or even better : 343 ! ! ! Ice thickness needed for rafting 344 WHERE( a_i(:,:,:) >= epsi20 ) ; ht_i(:,:,:) = v_i (:,:,:) / a_i(:,:,:) 345 ELSEWHERE ; ht_i(:,:,:) = 0._wp 346 END WHERE 347 !!gm end 331 348 332 349 !------------------------------------------------------------------------------! 333 350 ! 1) Participation function 334 351 !------------------------------------------------------------------------------! 335 352 ! 336 353 ! Compute total area of ice plus open water. 337 354 ! This is in general not equal to one because of divergence during transport 338 355 asum(:,:) = ato_i(:,:) + SUM( a_i, dim=3 ) 339 356 ! 340 357 ! Compute cumulative thickness distribution function 341 358 ! Compute the cumulative thickness distribution function Gsum, … … 348 365 Gsum(:,:,jl) = Gsum(:,:,jl-1) + a_i(:,:,jl) 349 366 END DO 350 367 ! 351 368 ! Normalize the cumulative distribution to 1 352 369 DO jl = 0, jpl … … 366 383 ! athorn is always >= 0 and SUM(athorn(0:jpl))=1 367 384 !----------------------------------------------------------------- 368 385 ! 369 386 IF( nn_partfun == 0 ) THEN !--- Linear formulation (Thorndike et al., 1975) 370 387 DO jl = 0, jpl … … 383 400 END DO 384 401 END DO 385 402 ! 386 403 ELSE !--- Exponential, more stable formulation (Lipscomb et al, 2007) 387 404 ! … … 396 413 ENDIF 397 414 398 ! --- Ridging and rafting participation concentrations --- ! 399 IF( ln_rafting .AND. ln_ridging ) THEN 400 ! 415 ! !--- Ridging and rafting participation concentrations 416 IF( ln_rafting .AND. ln_ridging ) THEN !- ridging & rafting 401 417 DO jl = 1, jpl 402 418 DO jj = 1, jpj … … 408 424 END DO 409 425 END DO 410 ! 411 ELSEIF( ln_ridging .AND. .NOT. ln_rafting ) THEN 412 ! 426 ELSEIF( ln_ridging .AND. .NOT.ln_rafting ) THEN !- ridging alone 413 427 DO jl = 1, jpl 414 428 aridge(:,:,jl) = athorn(:,:,jl) 415 429 END DO 416 ! 417 ELSEIF( ln_rafting .AND. .NOT. ln_ridging ) THEN 418 ! 430 ELSEIF( ln_rafting .AND. .NOT.ln_ridging ) THEN !- rafting alone 419 431 DO jl = 1, jpl 420 432 araft(:,:,jl) = athorn(:,:,jl) 421 433 END DO 422 !423 434 ENDIF 424 435 … … 454 465 DO jj = 1, jpj 455 466 DO ji = 1, jpi 456 457 IF( athorn(ji,jj,jl) > 0._wp ) THEN 467 IF ( athorn(ji,jj,jl) > 0._wp ) THEN 458 468 hrmean = MAX( SQRT( rn_hstar * ht_i(ji,jj,jl) ), ht_i(ji,jj,jl) * krdgmin ) 459 469 hrmin(ji,jj,jl) = MIN( 2._wp * ht_i(ji,jj,jl), 0.5_wp * ( hrmean + ht_i(ji,jj,jl) ) ) 460 470 hrmax(ji,jj,jl) = 2._wp * hrmean - hrmin(ji,jj,jl) 461 471 hraft(ji,jj,jl) = ht_i(ji,jj,jl) / kraft 462 krdg (ji,jj,jl)= ht_i(ji,jj,jl) / MAX( hrmean, epsi20 )463 472 krdg (ji,jj,jl) = ht_i(ji,jj,jl) / MAX( hrmean, epsi20 ) 473 ! 464 474 ! Normalization factor : aksum, ensures mass conservation 465 475 aksum(ji,jj) = aksum(ji,jj) + aridge(ji,jj,jl) * ( 1._wp - krdg(ji,jj,jl) ) & 466 476 & + araft (ji,jj,jl) * ( 1._wp - kraft ) 467 468 477 ELSE 469 478 hrmin(ji,jj,jl) = 0._wp … … 472 481 krdg (ji,jj,jl) = 1._wp 473 482 ENDIF 474 475 483 END DO 476 484 END DO 477 485 END DO 478 !479 486 ! 480 487 END SUBROUTINE ice_rdgrft_ridgeprep … … 493 500 REAL(wp), DIMENSION(jpi,jpj), INTENT(in ) :: closing_gross ! rate at which area removed, excluding area of new ridges 494 501 ! 495 CHARACTER (len=80) :: fieldid ! field identifier 502 CHARACTER (len=80) :: fieldid ! field identifier !!gm DOCTOR name wrong 496 503 ! 497 504 INTEGER :: ji, jj, jl, jl1, jl2, jk ! dummy loop indices … … 740 747 741 748 ! Compute the fraction of rafted ice area and volume going to thickness category jl2 742 IF( hraft(ji,jj,jl1) <= hi_max(jl2) .AND. hraft(ji,jj,jl1) > hi_max(jl2-1) ) THEN 743 zswitch(ij) = 1._wp 744 ELSE 745 zswitch(ij) = 0._wp 749 !!gm see above IF( hraft(ji,jj,jl1) <= hi_max(jl2) .AND. hraft(ji,jj,jl1) > hi_max(jl2-1) ) THEN 750 IF( hi_max(jl2-1) < hraft(ji,jj,jl1) .AND. hraft(ji,jj,jl1) <= hi_max(jl2) ) THEN ; zswitch(ij) = 1._wp 751 ELSE ; zswitch(ij) = 0._wp 746 752 ENDIF 747 753 ! 748 754 a_i (ji,jj ,jl2) = a_i (ji,jj ,jl2) + ( ardg2 (ij) * farea + arft2 (ij) * zswitch(ij) ) 749 755 oa_i (ji,jj ,jl2) = oa_i (ji,jj ,jl2) + ( oirdg2(ij) * farea + oirft2(ij) * zswitch(ij) ) … … 756 762 ! MV MP 2016 757 763 IF ( nn_pnd_scheme > 0 ) THEN 758 v_ip (ji,jj,jl2) = v_ip (ji,jj,jl2) + ( vprdg (ij) * rn_fpondrdg * fvol(ij) +&759 & vprft (ij) * rn_fpondrft * zswitch(ij))760 a_ip (ji,jj,jl2) = a_ip(ji,jj,jl2) + ( aprdg2(ij) * rn_fpondrdg * farea +&761 & aprft2(ij) * rn_fpondrft * zswitch(ji))764 v_ip (ji,jj,jl2) = v_ip(ji,jj,jl2) + ( vprdg (ij) * rn_fpondrdg * fvol (ij) & 765 & + vprft (ij) * rn_fpondrft * zswitch(ij) ) 766 a_ip (ji,jj,jl2) = a_ip(ji,jj,jl2) + ( aprdg2(ij) * rn_fpondrdg * farea & 767 & + aprft2(ij) * rn_fpondrft * zswitch(ji) ) 762 768 ENDIF 763 769 ! END MV MP 2016 764 765 770 END DO 766 771 … … 774 779 ! 775 780 END DO ! jl2 776 781 ! 777 782 END DO ! jl1 (deforming categories) 778 783 … … 782 787 ! 783 788 END SUBROUTINE ice_rdgrft_ridgeshift 789 784 790 785 791 SUBROUTINE ice_rdgrft_icestrength( kstrngth ) … … 798 804 !!---------------------------------------------------------------------- 799 805 INTEGER, INTENT(in) :: kstrngth ! = 1 for Rothrock formulation, 0 for Hibler (1979) 806 ! 800 807 INTEGER :: ji,jj, jl ! dummy loop indices 801 INTEGER :: ksmooth ! smoothing the resistance to deformation 802 INTEGER :: numts_rm ! number of time steps for the P smoothing 808 INTEGER :: ksmooth ! smoothing the resistance to deformation !!gm not DOCTOR : start with i !!! 809 INTEGER :: numts_rm ! number of time steps for the P smoothing !!gm not DOCTOR : start with i !!! 803 810 REAL(wp) :: zp, z1_3 ! local scalars 804 811 REAL(wp), DIMENSION(jpi,jpj) :: zworka ! temporary array used here … … 880 887 ! 6) Smoothing ice strength 881 888 !------------------------------------------------------------------------------! 882 ! 883 !------------------- 884 ! Spatial smoothing 885 !------------------- 886 IF ( ksmooth == 1 ) THEN 887 889 SELECT CASE( ksmooth ) 890 ! !------------------- 891 CASE( 1 ) ! Spatial smoothing 892 ! !------------------- 888 893 DO jj = 2, jpjm1 889 894 DO ji = 2, jpim1 … … 905 910 END DO 906 911 CALL lbc_lnk( strength, 'T', 1. ) 907 908 ENDIF 909 910 !-------------------- 911 ! Temporal smoothing 912 !-------------------- 913 IF ( ksmooth == 2 ) THEN 914 912 ! 913 ! !-------------------- 914 CASE( 2 ) ! Temporal smoothing 915 ! !-------------------- 915 916 IF ( kt_ice == nit000 ) THEN 916 917 zstrp1(:,:) = 0._wp 917 918 zstrp2(:,:) = 0._wp 918 919 ENDIF 919 920 ! 920 921 DO jj = 2, jpjm1 921 922 DO ji = 2, jpim1 … … 925 926 IF ( zstrp2(ji,jj) > 0._wp ) numts_rm = numts_rm + 1 926 927 zp = ( strength(ji,jj) + zstrp1(ji,jj) + zstrp2(ji,jj) ) / numts_rm 927 zstrp2 (ji,jj) = zstrp1(ji,jj)928 zstrp1 (ji,jj) = strength(ji,jj)928 zstrp2 (ji,jj) = zstrp1 (ji,jj) 929 zstrp1 (ji,jj) = strength(ji,jj) 929 930 strength(ji,jj) = zp 930 931 ENDIF 931 932 END DO 932 933 END DO 933 934 934 CALL lbc_lnk( strength, 'T', 1. ) ! Boundary conditions 935 936 END IF ! ksmooth935 ! 936 END SELECT 937 937 ! 938 938 END SUBROUTINE ice_rdgrft_icestrength 939 939 940 940 941 SUBROUTINE ice_rdgrft_init 941 942 !!------------------------------------------------------------------- 942 !! 943 !! *** ROUTINE ice_rdgrft_init *** 943 944 !! 944 945 !! ** Purpose : Physical constants and parameters linked … … 952 953 !!------------------------------------------------------------------- 953 954 INTEGER :: ios ! Local integer output status for namelist read 954 NAMELIST/namiceitdme/ rn_cs, nn_partfun, rn_gstar, rn_astar, & 955 & ln_ridging, rn_hstar, rn_por_rdg, rn_fsnowrdg, rn_fpondrdg, & 956 ln_rafting, rn_hraft, rn_craft, rn_fsnowrft, rn_fpondrft 955 !! 956 NAMELIST/namiceitdme/ rn_cs , nn_partfun, rn_gstar , rn_astar , & 957 & ln_ridging, rn_hstar , rn_por_rdg, rn_fsnowrdg, rn_fpondrdg, & 958 & ln_rafting, rn_hraft , rn_craft , rn_fsnowrft, rn_fpondrft 957 959 !!------------------------------------------------------------------- 958 960 ! … … 960 962 READ ( numnam_ice_ref, namiceitdme, IOSTAT = ios, ERR = 901) 961 963 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namiceitdme in reference namelist', lwp ) 962 964 ! 963 965 REWIND( numnam_ice_cfg ) ! Namelist namiceitdme in configuration namelist : Ice mechanical ice redistribution 964 966 READ ( numnam_ice_cfg, namiceitdme, IOSTAT = ios, ERR = 902 ) … … 992 994 !! Default option Empty module NO LIM-3 sea-ice model 993 995 !!---------------------------------------------------------------------- 994 CONTAINS995 SUBROUTINE ice_rdgrft ! Empty routines996 END SUBROUTINE ice_rdgrft997 SUBROUTINE ice_rdgrft_icestrength998 END SUBROUTINE ice_rdgrft_icestrength999 SUBROUTINE ice_rdgrft_init1000 END SUBROUTINE ice_rdgrft_init1001 996 #endif 997 1002 998 !!====================================================================== 1003 999 END MODULE icerdgrft -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icerhg.F90
r8426 r8486 10 10 #if defined key_lim3 11 11 !!---------------------------------------------------------------------- 12 !! 'key_lim3' :LIM3 sea-ice model12 !! 'key_lim3' LIM3 sea-ice model 13 13 !!---------------------------------------------------------------------- 14 14 !! ice_rhg : computes ice velocities 15 15 !! ice_rhg_init : initialization and namelist read 16 16 !!---------------------------------------------------------------------- 17 USE phycst 18 USE dom_oce 19 USE ice ! LIM-3variables20 USE icerhg_evp !EVP rheology21 USE icectl !control prints22 USE icevar 17 USE phycst ! physical constants 18 USE dom_oce ! ocean space and time domain 19 USE ice ! sea-ice: variables 20 USE icerhg_evp ! sea-ice: EVP rheology 21 USE icectl ! sea-ice: control prints 22 USE icevar ! sea-ice: operations 23 23 ! 24 USE lbclnk 25 USE lib_mpp 26 USE in_out_manager 27 USE lib_fortran 28 USE timing 24 USE lbclnk ! lateral boundary conditions - MPP exchanges 25 USE lib_mpp ! MPP library 26 USE in_out_manager ! I/O manager 27 USE lib_fortran ! glob_sum 28 USE timing ! Timing 29 29 30 30 IMPLICIT NONE … … 37 37 # include "vectopt_loop_substitute.h90" 38 38 !!---------------------------------------------------------------------- 39 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)39 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 40 40 !! $Id: icerhg.F90 8378 2017-07-26 13:55:59Z clem $ 41 41 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 53 53 !! - shear, divergence and delta (shear_i, divu_i, delta_i) 54 54 !!-------------------------------------------------------------------- 55 INTEGER, INTENT(in) :: kt ! number of iteration55 INTEGER, INTENT(in) :: kt ! ice time step 56 56 !! 57 INTEGER :: jl! dummy loop indices57 INTEGER :: jl ! dummy loop indices 58 58 REAL(wp) :: zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b 59 59 !!-------------------------------------------------------------------- 60 60 ! 61 61 IF( nn_timing == 1 ) CALL timing_start('icerhg') 62 62 ! 63 63 IF( kt == nit000 .AND. lwp ) THEN 64 64 WRITE(numout,*) 65 WRITE(numout,*)'ice rhg'66 WRITE(numout,*)'~~~~~~ '65 WRITE(numout,*)'ice_rhg : sea-ice rheology' 66 WRITE(numout,*)'~~~~~~~~' 67 67 ENDIF 68 68 69 CALL ice_var_agg(1) !aggregate ice categories69 CALL ice_var_agg(1) ! -- aggregate ice categories 70 70 ! 71 ! conservation test 72 IF( ln_limdiachk ) CALL ice_cons_hsm(0, 'icerhg', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 73 74 ! Landfast ice parameterization: define max bottom friction 75 tau_icebfr(:,:) = 0._wp 76 IF( ln_landfast ) THEN 71 ! ! -- conservation test 72 IF( ln_limdiachk ) CALL ice_cons_hsm(0, 'icerhg', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 73 ! 74 IF( ln_landfast ) THEN ! -- Landfast ice parameterization: define max bottom friction 77 75 DO jl = 1, jpl 78 WHERE( ht_i(:,:,jl) > ht_n(:,:) * rn_gamma ) tau_icebfr(:,:) = tau_icebfr(:,:) + a_i(:,:,jl) * rn_icebfr 76 WHERE( ht_i(:,:,jl) > ht_n(:,:) * rn_gamma ) ; tau_icebfr(:,:) = tau_icebfr(:,:) + a_i(:,:,jl) * rn_icebfr 77 ELSEWHERE ; tau_icebfr(:,:) = 0._wp 78 END WHERE 79 79 END DO 80 80 ENDIF … … 83 83 ! Rheology (ice dynamics) 84 84 ! ----------------------- 85 IF( nn_limdyn /= 0 ) THEN 86 85 IF( nn_limdyn /= 0 ) THEN ! -- Ice dynamics 86 ! 87 87 CALL ice_rhg_evp( stress1_i, stress2_i, stress12_i, u_ice, v_ice, shear_i, divu_i, delta_i ) 88 89 ELSE 90 91 u_ice(:,:) = rn_uice * umask(:,:,1) ! or prescribed velocity88 ! 89 ELSE ! -- prescribed uniform velocity 90 ! 91 u_ice(:,:) = rn_uice * umask(:,:,1) 92 92 v_ice(:,:) = rn_vice * vmask(:,:,1) 93 93 !!CALL RANDOM_NUMBER(u_ice(:,:)) 94 94 !!CALL RANDOM_NUMBER(v_ice(:,:)) 95 95 ! 96 96 ENDIF 97 97 ! 98 ! conservation test 99 IF( ln_limdiachk ) CALL ice_cons_hsm(1, 'icerhg', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 100 101 ! Control prints 102 IF( ln_ctl ) CALL ice_prt3D( 'icerhg' ) 98 ! !- conservation test 99 IF( ln_limdiachk ) CALL ice_cons_hsm(1, 'icerhg', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 100 IF( ln_ctl ) CALL ice_prt3D ('icerhg') !- Control prints 101 IF( nn_timing == 1 ) CALL timing_stop('icerhg') !- timing 103 102 ! 104 IF( nn_timing == 1 ) CALL timing_stop('icerhg')105 106 103 END SUBROUTINE ice_rhg 107 104 … … 119 116 !! ** input : Namelist namicedyn 120 117 !!------------------------------------------------------------------- 121 INTEGER :: ios ! Local integer output status for namelist read 122 NAMELIST/namicedyn/ nn_limadv, nn_limadv_ord, & 123 & nn_icestr, rn_pe_rdg, rn_pstar, rn_crhg, ln_icestr_bvf, & 124 & rn_ishlat, rn_cio, rn_creepl, rn_ecc, & 125 & nn_nevp, rn_relast, ln_landfast, rn_gamma, rn_icebfr, rn_lfrelax 118 INTEGER :: ios ! Local integer output status for namelist read 119 !! 120 NAMELIST/namicedyn/ nn_limadv , nn_limadv_ord, & 121 & nn_icestr , rn_pe_rdg, rn_pstar , rn_crhg, ln_icestr_bvf , & 122 & rn_ishlat , rn_cio , rn_creepl, rn_ecc , nn_nevp, rn_relast, & 123 & ln_landfast, rn_gamma , rn_icebfr, rn_lfrelax 126 124 !!------------------------------------------------------------------- 127 128 REWIND( numnam_ice_ref ) 125 ! 126 REWIND( numnam_ice_ref ) ! Namelist namicedyn in reference namelist : Ice dynamics 129 127 READ ( numnam_ice_ref, namicedyn, IOSTAT = ios, ERR = 901) 130 128 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicedyn in reference namelist', lwp ) 131 132 REWIND( numnam_ice_cfg ) 129 ! 130 REWIND( numnam_ice_cfg ) ! Namelist namicedyn in configuration namelist : Ice dynamics 133 131 READ ( numnam_ice_cfg, namicedyn, IOSTAT = ios, ERR = 902 ) 134 132 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicedyn in configuration namelist', lwp ) 135 133 IF(lwm) WRITE ( numoni, namicedyn ) 136 137 IF(lwp) THEN 134 ! 135 IF(lwp) THEN ! control print 138 136 WRITE(numout,*) 139 137 WRITE(numout,*) 'ice_rhg_init : ice parameters for ice dynamics ' 140 138 WRITE(numout,*) '~~~~~~~~~~~~' 141 ! limtrp 142 WRITE(numout,*)' choose the advection scheme (-1=Prather, 0=Ulimate-Macho) nn_limadv = ', nn_limadv 143 WRITE(numout,*)' choose the order of the scheme (if ultimate) nn_limadv_ord = ', nn_limadv_ord 144 ! icerdgrft 145 WRITE(numout,*)' ice strength parameterization (0=Hibler 1=Rothrock) nn_icestr = ', nn_icestr 146 WRITE(numout,*)' Ratio of ridging work to PotEner change in ridging rn_pe_rdg = ', rn_pe_rdg 147 WRITE(numout,*) ' first bulk-rheology parameter rn_pstar = ', rn_pstar 148 WRITE(numout,*) ' second bulk-rhelogy parameter rn_crhg = ', rn_crhg 149 WRITE(numout,*)' Including brine volume in ice strength comp. ln_icestr_bvf = ', ln_icestr_bvf 150 ! icerhg_evp 151 WRITE(numout,*) ' lateral boundary condition for sea ice dynamics rn_ishlat = ', rn_ishlat 152 WRITE(numout,*) ' drag coefficient for oceanic stress rn_cio = ', rn_cio 153 WRITE(numout,*) ' creep limit rn_creepl = ', rn_creepl 154 WRITE(numout,*) ' eccentricity of the elliptical yield curve rn_ecc = ', rn_ecc 155 WRITE(numout,*) ' number of iterations for subcycling nn_nevp = ', nn_nevp 156 WRITE(numout,*) ' ratio of elastic timescale over ice time step rn_relast = ', rn_relast 157 WRITE(numout,*) ' Landfast: param (T or F) ln_landfast = ', ln_landfast 158 WRITE(numout,*) ' T: fraction of ocean depth that ice must reach rn_gamma = ', rn_gamma 159 WRITE(numout,*) ' T: maximum bottom stress per unit area of contact rn_icebfr = ', rn_icebfr 160 WRITE(numout,*) ' T: relax time scale (s-1) to reach static friction rn_lfrelax = ', rn_lfrelax 139 WRITE(numout,*) ' Namelist namicedyn' 140 WRITE(numout,*) ' advection scheme for ice transport (limtrp)' 141 WRITE(numout,*) ' type of advection scheme (-1=Prather, 0=Ulimate-Macho) nn_limadv = ', nn_limadv 142 WRITE(numout,*) ' order of the scheme for Ultimate-Macho case nn_limadv_ord = ', nn_limadv_ord 143 WRITE(numout,*) ' ridging/rafting (icerdgrft)' 144 WRITE(numout,*) ' ice strength parameterization (0=Hibler 1=Rothrock) nn_icestr = ', nn_icestr 145 WRITE(numout,*) ' Ratio of ridging work to PotEner change in ridging rn_pe_rdg = ', rn_pe_rdg 146 WRITE(numout,*) ' 1st bulk-rheology parameter rn_pstar = ', rn_pstar 147 WRITE(numout,*) ' 2nd bulk-rhelogy parameter rn_crhg = ', rn_crhg 148 WRITE(numout,*) ' brine volume included in ice strength computation ln_icestr_bvf = ', ln_icestr_bvf 149 WRITE(numout,*) ' rheology EVP (icerhg_evp)' 150 WRITE(numout,*) ' lateral boundary condition for sea ice dynamics rn_ishlat = ', rn_ishlat 151 WRITE(numout,*) ' drag coefficient for oceanic stress rn_cio = ', rn_cio 152 WRITE(numout,*) ' creep limit rn_creepl = ', rn_creepl 153 WRITE(numout,*) ' eccentricity of the elliptical yield curve rn_ecc = ', rn_ecc 154 WRITE(numout,*) ' number of iterations for subcycling nn_nevp = ', nn_nevp 155 WRITE(numout,*) ' ratio of elastic timescale over ice time step rn_relast = ', rn_relast 156 WRITE(numout,*) ' Landfast: param (T or F) ln_landfast = ', ln_landfast 157 WRITE(numout,*) ' fraction of ocean depth that ice must reach rn_gamma = ', rn_gamma 158 WRITE(numout,*) ' maximum bottom stress per unit area of contact rn_icebfr = ', rn_icebfr 159 WRITE(numout,*) ' relax time scale (s-1) to reach static friction rn_lfrelax = ', rn_lfrelax 161 160 ENDIF 162 161 ! 163 IF ( rn_ishlat == 0. ) THEN ; IF(lwp) WRITE(numout,*) ' ice lateral free-slip'164 ELSEIF ( rn_ishlat == 2. ) THEN ; IF(lwp) WRITE(numout,*) ' ice lateral no-slip'165 ELSEIF ( 0. < rn_ishlat .AND. rn_ishlat < 2. ) THEN ; IF(lwp) WRITE(numout,*) ' ice lateral partial-slip'166 ELSEIF ( 2. < rn_ishlat ) THEN ; IF(lwp) WRITE(numout,*) ' ice lateral strong-slip'162 IF ( rn_ishlat == 0. ) THEN ; IF(lwp) WRITE(numout,*) ' ===>>> ice lateral free-slip' 163 ELSEIF ( rn_ishlat == 2. ) THEN ; IF(lwp) WRITE(numout,*) ' ===>>> ice lateral no-slip' 164 ELSEIF ( 0. < rn_ishlat .AND. rn_ishlat < 2. ) THEN ; IF(lwp) WRITE(numout,*) ' ===>>> ice lateral partial-slip' 165 ELSEIF ( 2. < rn_ishlat ) THEN ; IF(lwp) WRITE(numout,*) ' ===>>> ice lateral strong-slip' 167 166 ENDIF 167 ! 168 IF( .NOT. ln_landfast ) tau_icebfr(:,:) = 0._wp ! NO Landfast ice : set to zero one for all 168 169 ! 169 170 END SUBROUTINE ice_rhg_init 170 171 172 #else 173 !!---------------------------------------------------------------------- 174 !! Default option Empty module NO LIM-3 sea-ice model 175 !!---------------------------------------------------------------------- 171 176 #endif 172 177 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icerhg_evp.F90
r8409 r8486 45 45 # include "vectopt_loop_substitute.h90" 46 46 !!---------------------------------------------------------------------- 47 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)47 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 48 48 !! $Id: icerhg_evp.F90 8378 2017-07-26 13:55:59Z clem $ 49 49 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 386 386 DO jj = 2, jpjm1 387 387 DO ji = fs_2, fs_jpim1 388 389 ! U points 388 ! !--- U points 390 389 zfU(ji,jj) = 0.5_wp * ( ( zs1(ji+1,jj) - zs1(ji,jj) ) * e2u(ji,jj) & 391 390 & + ( zs2(ji+1,jj) * e2t(ji+1,jj) * e2t(ji+1,jj) - zs2(ji,jj) * e2t(ji,jj) * e2t(ji,jj) & … … 394 393 & ) * 2._wp * r1_e1u(ji,jj) & 395 394 & ) * r1_e1e2u(ji,jj) 396 397 !V points395 ! 396 ! !--- V points 398 397 zfV(ji,jj) = 0.5_wp * ( ( zs1(ji,jj+1) - zs1(ji,jj) ) * e1v(ji,jj) & 399 398 & - ( zs2(ji,jj+1) * e1t(ji,jj+1) * e1t(ji,jj+1) - zs2(ji,jj) * e1t(ji,jj) * e1t(ji,jj) & … … 402 401 & ) * 2._wp * r1_e2v(ji,jj) & 403 402 & ) * r1_e1e2v(ji,jj) 404 405 !u_ice at V point403 ! 404 ! !--- u_ice at V point 406 405 u_iceV(ji,jj) = 0.5_wp * ( ( u_ice(ji,jj ) + u_ice(ji-1,jj ) ) * e2t(ji,jj+1) & 407 406 & + ( u_ice(ji,jj+1) + u_ice(ji-1,jj+1) ) * e2t(ji,jj ) ) * z1_e2t0(ji,jj) * vmask(ji,jj,1) 408 409 !v_ice at U point407 ! 408 ! !--- v_ice at U point 410 409 v_iceU(ji,jj) = 0.5_wp * ( ( v_ice(ji ,jj) + v_ice(ji ,jj-1) ) * e1t(ji+1,jj) & 411 410 & + ( v_ice(ji+1,jj) + v_ice(ji+1,jj-1) ) * e1t(ji ,jj) ) * z1_e1t0(ji,jj) * umask(ji,jj,1) 412 411 ! 413 412 END DO 414 413 END DO … … 417 416 ! Bouillon et al. 2013 (eq 47-48) => unstable unless alpha, beta are chosen wisely and large nn_nevp 418 417 ! Bouillon et al. 2009 (eq 34-35) => stable 419 IF( MOD(jter,2) .EQ.0 ) THEN ! even iterations420 418 IF( MOD(jter,2) == 0 ) THEN ! even iterations 419 ! 421 420 DO jj = 2, jpjm1 422 421 DO ji = fs_2, fs_jpim1 423 424 ! tau_io/(v_oce - v_ice) 422 ! !--- tau_io/(v_oce - v_ice) 425 423 zTauO = zaV(ji,jj) * zrhoco * SQRT( ( v_ice (ji,jj) - v_oce (ji,jj) ) * ( v_ice (ji,jj) - v_oce (ji,jj) ) & 426 424 & + ( u_iceV(ji,jj) - u_oceV(ji,jj) ) * ( u_iceV(ji,jj) - u_oceV(ji,jj) ) ) 427 428 ! Ocean-to-Ice stress 425 ! !--- Ocean-to-Ice stress 429 426 ztauy_oi(ji,jj) = zTauO * ( v_oce(ji,jj) - v_ice(ji,jj) ) 430 431 !tau_bottom/v_ice427 ! 428 ! !--- tau_bottom/v_ice 432 429 zvel = MAX( zepsi, SQRT( v_ice(ji,jj) * v_ice(ji,jj) + u_iceV(ji,jj) * u_iceV(ji,jj) ) ) 433 430 zTauB = - tau_icebfr(ji,jj) / zvel 434 435 !Coriolis at V-points (energy conserving formulation)431 ! 432 ! !--- Coriolis at V-points (energy conserving formulation) 436 433 zCory(ji,jj) = - 0.25_wp * r1_e2v(ji,jj) * & 437 434 & ( zmf(ji,jj ) * ( e2u(ji,jj ) * u_ice(ji,jj ) + e2u(ji-1,jj ) * u_ice(ji-1,jj ) ) & 438 435 & + zmf(ji,jj+1) * ( e2u(ji,jj+1) * u_ice(ji,jj+1) + e2u(ji-1,jj+1) * u_ice(ji-1,jj+1) ) ) 439 440 !Sum of external forces (explicit solution) = F + tau_ia + Coriolis + spg + tau_io436 ! 437 ! !--- Sum of external forces (explicit solution) = F + tau_ia + Coriolis + spg + tau_io 441 438 zTauE = zfV(ji,jj) + zTauV_ia(ji,jj) + zCory(ji,jj) + zspgV(ji,jj) + ztauy_oi(ji,jj) 442 443 !landfast switch => 0 = static friction ; 1 = sliding friction439 ! 440 ! !--- landfast switch => 0 = static friction ; 1 = sliding friction 444 441 rswitch = 1._wp - MIN( 1._wp, ABS( SIGN( 1._wp, ztauE - tau_icebfr(ji,jj) ) - SIGN( 1._wp, zTauE ) ) ) 445 446 !ice velocity using implicit formulation (cf Madec doc & Bouillon 2009)442 ! 443 ! !--- ice velocity using implicit formulation (cf Madec doc & Bouillon 2009) 447 444 v_ice(ji,jj) = ( ( rswitch * ( zmV_t(ji,jj) * v_ice(ji,jj) & ! previous velocity 448 445 & + zTauE + zTauO * v_ice(ji,jj) & ! F + tau_ia + Coriolis + spg + tau_io(only ocean part) … … 451 448 & ) * zswitchV(ji,jj) + v_oce(ji,jj) * ( 1._wp - zswitchV(ji,jj) ) & ! v_ice = v_oce if mass < zmmin 452 449 & ) * zmaskV(ji,jj) 450 ! 453 451 ! Bouillon 2013 454 452 !!v_ice(ji,jj) = ( zmV_t(ji,jj) * ( zbeta * v_ice(ji,jj) + v_ice_b(ji,jj) ) & 455 453 !! & + zfV(ji,jj) + zCory(ji,jj) + zTauV_ia(ji,jj) + zTauO * v_oce(ji,jj) + zspgV(ji,jj) & 456 454 !! & ) / MAX( zmV_t(ji,jj) * ( zbeta + 1._wp ) + zTauO - zTauB, zepsi ) * zswitchV(ji,jj) 457 455 ! 458 456 END DO 459 457 END DO 460 458 CALL lbc_lnk( v_ice, 'V', -1. ) 461 459 ! 462 460 #if defined key_agrif 463 461 !! CALL agrif_interp_lim3( 'V', jter, nn_nevp ) … … 465 463 #endif 466 464 IF( ln_bdy ) CALL bdy_ice_dyn( 'V' ) 467 465 ! 468 466 DO jj = 2, jpjm1 469 467 DO ji = fs_2, fs_jpim1 … … 505 503 END DO 506 504 CALL lbc_lnk( u_ice, 'U', -1. ) 507 505 ! 508 506 #if defined key_agrif 509 507 !! CALL agrif_interp_lim3( 'U', jter, nn_nevp ) … … 511 509 #endif 512 510 IF( ln_bdy ) CALL bdy_ice_dyn( 'U' ) 513 511 ! 514 512 ELSE ! odd iterations 515 513 ! 516 514 DO jj = 2, jpjm1 517 515 DO ji = fs_2, fs_jpim1 … … 553 551 END DO 554 552 CALL lbc_lnk( u_ice, 'U', -1. ) 555 553 ! 556 554 #if defined key_agrif 557 555 !! CALL agrif_interp_lim3( 'U', jter, nn_nevp ) … … 559 557 #endif 560 558 IF( ln_bdy ) CALL bdy_ice_dyn( 'U' ) 561 559 ! 562 560 DO jj = 2, jpjm1 563 561 DO ji = fs_2, fs_jpim1 … … 599 597 END DO 600 598 CALL lbc_lnk( v_ice, 'V', -1. ) 601 599 ! 602 600 #if defined key_agrif 603 601 !! CALL agrif_interp_lim3( 'V', jter, nn_nevp ) … … 605 603 #endif 606 604 IF( ln_bdy ) CALL bdy_ice_dyn( 'V' ) 607 605 ! 608 606 ENDIF 609 607 … … 675 673 ! 5) SIMIP diagnostics 676 674 !------------------------------------------------------------------------------! 677 675 676 !!gm encapsulate with a flag (iom_use of the variable or better a flag defined one for all testing if one of the 677 !! diag is output. NB the diag_... are should only be ALLOCATED if the flag is true ! 678 678 679 DO jj = 2, jpjm1 679 680 DO ji = 2, jpim1 … … 714 715 715 716 CALL lbc_lnk_multi( diag_sig1 , 'T', 1., diag_sig2 , 'T', 1., & 716 &diag_dssh_dx, 'U', -1., diag_dssh_dy, 'V', -1., &717 &diag_corstrx, 'U', -1., diag_corstry, 'V', -1., &718 &diag_intstrx, 'U', -1., diag_intstry, 'V', -1. )717 & diag_dssh_dx, 'U', -1., diag_dssh_dy, 'V', -1., & 718 & diag_corstrx, 'U', -1., diag_corstry, 'V', -1., & 719 & diag_intstrx, 'U', -1., diag_intstry, 'V', -1. ) 719 720 720 721 CALL lbc_lnk_multi( diag_utau_oi, 'U', -1., diag_vtau_oi, 'V', -1. ) 721 722 722 CALL lbc_lnk_multi( diag_xmtrp_ice, 'U', -1., diag_xmtrp_snw, 'U', -1., &723 & diag_xatrp , 'U', -1., diag_ymtrp_ice, 'V', -1.,&724 & diag_ymtrp_snw, 'V', -1., diag_yatrp , 'V', -1.)723 CALL lbc_lnk_multi( diag_xmtrp_ice, 'U', -1., diag_xmtrp_snw, 'U', -1., & 724 & diag_xatrp , 'U', -1., diag_ymtrp_ice, 'V', -1., & 725 & diag_ymtrp_snw, 'V', -1., diag_yatrp , 'V', -1. ) 725 726 726 727 ! … … 734 735 CALL prt_ctl_info(charout) 735 736 CALL prt_ctl(tab2d_1=u_ice, clinfo1=' ice_rhg_evp : u_ice :', tab2d_2=v_ice, clinfo2=' v_ice :') 736 ENDIF 737 738 ! print charge ellipse 739 ! This can be desactivated once the user is sure that the stress state 740 ! lie on the charge ellipse. See Bouillon et al. 08 for more details 741 IF(ln_ctl) THEN 737 ! 738 ! print charge ellipse 739 ! This can be desactivated once the user is sure that the stress state 740 ! lie on the charge ellipse. See Bouillon et al. (2008) for more details 742 741 IF( MOD(kt_ice+nn_fsbc-1,nwrite) == 0 ) THEN 743 742 WRITE(charout,FMT="('ice_rhg_evp :', I4, I6, I1, I1, A10)") 1000, kt_ice, 0, 0, ' ch. ell. ' … … 760 759 END SUBROUTINE ice_rhg_evp 761 760 761 #else 762 !!---------------------------------------------------------------------- 763 !! Default option Empty module NO LIM-3 sea-ice model 764 !!---------------------------------------------------------------------- 762 765 #endif 763 766 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icerst.F90
r8413 r8486 4 4 !! Ice restart : write the ice restart file 5 5 !!====================================================================== 6 !! History: -! 2005-04 (M. Vancoppenolle) Original code7 !! 3.0! 2008-03 (C. Ethe) restart files in using IOM interface8 !! 4.0 ! 2011-02 (G. Madec) dynamical allocation6 !! History: 3.0 ! 2005-04 (M. Vancoppenolle) Original code 7 !! - ! 2008-03 (C. Ethe) restart files in using IOM interface 8 !! 4.0 ! 2011-02 (G. Madec) dynamical allocation 9 9 !!---------------------------------------------------------------------- 10 10 #if defined key_lim3 11 11 !!---------------------------------------------------------------------- 12 !! 'key_lim3' :LIM sea-ice model12 !! 'key_lim3' LIM sea-ice model 13 13 !!---------------------------------------------------------------------- 14 14 !! ice_rst_opn : open ice restart file … … 38 38 39 39 !!---------------------------------------------------------------------- 40 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)40 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 41 41 !! $Id: icerst.F90 8411 2017-08-07 16:09:12Z clem $ 42 42 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 123 123 CALL iom_rstput( iter, nitrst, numriw, 'kt_ice' , REAL( iter , wp ) ) ! date 124 124 125 !!gm It is possible and easy to define a 3D domain size (jpi,jpj,jpl) or use a SIZE( tab, DIM=3) in iom_rtput ) 126 !!gm ===>>> just a simple iom_rstput( iter, nitrst, numriw, 'v_i', v_i ) etc... 127 !!gm "just" ask Sebatien 128 129 125 130 ! Prognostic variables 126 131 DO jl = 1, jpl … … 639 644 !! Default option : Empty module NO LIM sea-ice model 640 645 !!---------------------------------------------------------------------- 641 CONTAINS642 SUBROUTINE ice_rst_read ! Empty routine643 END SUBROUTINE ice_rst_read644 SUBROUTINE ice_rst_write ! Empty routine645 END SUBROUTINE ice_rst_write646 646 #endif 647 647 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icestp.F90
r8426 r8486 17 17 #if defined key_lim3 18 18 !!---------------------------------------------------------------------- 19 !! 'key_lim3' : LIM 3.0 sea-ice model 20 !!---------------------------------------------------------------------- 21 !! ice_stp : sea-ice model time-stepping and update ocean sbc over ice-covered area 22 !!---------------------------------------------------------------------- 23 USE oce ! ocean dynamics and tracers 24 USE dom_oce ! ocean space and time domain 25 USE ice ! LIM-3: ice variables 26 USE ice1D ! LIM-3: thermodynamical variables 19 !! 'key_lim3' LIM 3.0 sea-ice model 20 !!---------------------------------------------------------------------- 21 !! ice_stp : sea-ice model time-stepping and update ocean surf. boundary cond. over ice-covered area 22 !! ice_init : 23 !! ice_run_init : 24 !!---------------------------------------------------------------------- 25 USE oce ! ocean dynamics and tracers 26 USE dom_oce ! ocean space and time domain 27 USE c1d ! 1D vertical configuration 28 USE ice ! sea-ice: variables 29 USE ice1D ! sea-ice: thermodynamical 1D variables 27 30 ! 28 USE sbc_oce 29 USE sbc_ice 30 USE iceforcing ! Surface boundary condition for sea ice31 USE sbc_oce ! Surface boundary condition: ocean fields 32 USE sbc_ice ! Surface boundary condition: ice fields 33 USE iceforcing ! sea-ice: Surface boundary condition !!gm why not icesbc module name 31 34 ! 32 USE phycst 33 USE eosbn2 34 USE icerhg ! Icerheology35 USE iceadv ! Iceadvection36 USE icethd ! Icethermodynamics37 USE icerdgrft ! Iceridging/rafting38 USE iceupdate ! sea surface boundary condition39 USE icedia ! Icebudget diagnostics40 USE icewri ! Iceoutputs41 USE icerst ! Icerestarts42 USE icecor ! Icecorrections43 USE icevar ! Ice variables switch44 USE icectl !35 USE phycst ! Define parameters for the routines 36 USE eosbn2 ! equation of state 37 USE icerhg ! sea-ice: rheology 38 USE iceadv ! sea-ice: advection 39 USE icethd ! sea-ice: thermodynamics 40 USE icerdgrft ! sea-ice: ridging/rafting 41 USE iceupdate ! sea-ice: sea surface boundary condition update 42 USE icedia ! sea-ice: budget diagnostics 43 USE icewri ! sea-ice: outputs 44 USE icerst ! sea-ice: restarts 45 USE icecor ! sea-ice: corrections 46 USE icevar ! sea-ice: operations 47 USE icectl ! sea-ice: control 45 48 ! MV MP 2016 46 USE limmp 49 USE limmp ! sea-ice: melt ponds 47 50 ! END MV MP 2016 48 USE iceist ! LIMinitial state49 USE icethd_sal ! LIM ice thermodynamics:salinity51 USE iceist ! sea-ice: initial state 52 USE icethd_sal ! sea-ice: thermodynamics and salinity 50 53 ! 51 USE c1d ! 1D vertical configuration 52 USE in_out_manager ! I/O manager 53 USE iom ! I/O manager library 54 USE prtctl ! Print control 55 USE lib_fortran ! 56 USE lbclnk ! lateral boundary condition - MPP link 57 USE lib_mpp ! MPP library 58 USE timing ! Timing 59 60 USE bdy_oce , ONLY: ln_bdy 61 USE bdyice ! unstructured open boundary data 54 USE bdy_oce , ONLY : ln_bdy ! flag for bdy 55 USE bdyice ! unstructured open boundary data for sea-ice 62 56 # if defined key_agrif 63 57 USE agrif_ice … … 65 59 USE agrif_lim3_interp 66 60 # endif 61 ! 62 USE in_out_manager ! I/O manager 63 USE iom ! I/O manager library 64 USE prtctl ! Print control 65 USE lib_fortran ! 66 USE lbclnk ! lateral boundary condition - MPP link 67 USE lib_mpp ! MPP library 68 USE timing ! Timing 67 69 68 70 IMPLICIT NONE 69 71 PRIVATE 70 72 71 PUBLIC ice_stp ! routine called by sbcmod.F90 72 PUBLIC ice_init ! routine called by sbcmod.F90 73 PUBLIC ice_stp ! called by sbcmod.F90 74 PUBLIC ice_init ! called by sbcmod.F90 75 76 INTEGER :: nice_dyn ! choice of the type of advection scheme 77 ! ! associated indices: 78 INTEGER, PARAMETER :: np_dynNO = 0 ! no ice dynamics and ice advection 79 INTEGER, PARAMETER :: np_dynFULL = 1 ! full ice dynamics (rheology + advection + ridging/rafting + correction) 80 INTEGER, PARAMETER :: np_dyn = 2 ! no ridging/rafting (rheology + advection + correction) 81 INTEGER, PARAMETER :: np_dynPURE = 3 ! pure dynamics (rheology + advection) 73 82 74 83 !! * Substitutions 75 84 # include "vectopt_loop_substitute.h90" 76 85 !!---------------------------------------------------------------------- 77 !! NEMO/ OPA 4.0 , UCL NEMO Consortium (2011)86 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 78 87 !! $Id: icestp.F90 8319 2017-07-11 15:00:44Z clem $ 79 88 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 85 94 !! *** ROUTINE ice_stp *** 86 95 !! 87 !! ** Purpose : update the ocean surface boundary condition via the88 !! Louvain la Neuve Sea Ice Model time stepping96 !! ** Purpose : sea-ice model time-stepping and update ocean surface 97 !! boundary condition over ice-covered area 89 98 !! 90 99 !! ** Method : ice model time stepping … … 102 111 !!--------------------------------------------------------------------- 103 112 INTEGER, INTENT(in) :: kt ! ocean time step 104 INTEGER, INTENT(in) :: ksbc ! type of sbc flux ( 1 = user defined formulation, 105 ! 3 = bulk formulation, 106 ! 4 = Pure Coupled formulation) 107 INTEGER :: jl ! dummy loop index 108 !!---------------------------------------------------------------------- 109 113 INTEGER, INTENT(in) :: ksbc ! flux formulation (user defined, bulk, or Pure Coupled) 114 ! 115 INTEGER :: jl ! dummy loop index 116 !!---------------------------------------------------------------------- 117 ! 110 118 IF( nn_timing == 1 ) CALL timing_start('ice_stp') 111 112 !-----------------------! 113 ! --- Ice time step --- ! 114 !-----------------------! 115 IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 116 117 ! Ice model time step 118 kt_ice = kt 119 119 ! 120 ! !-----------------------! 121 IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN ! --- Ice time step --- ! 122 ! !-----------------------! 123 ! 124 kt_ice = kt ! Ice model time step 125 ! 120 126 # if defined key_agrif 121 127 IF( .NOT. Agrif_Root() ) lim_nbstep = MOD( lim_nbstep, Agrif_irhot() * Agrif_Parent(nn_fsbc) / nn_fsbc ) + 1 122 128 # endif 123 129 124 ! mean surface ocean current at ice velocity point (C-grid dynamics : U- & V-points as the ocean)130 ! ! mean surface ocean current at ice velocity point 125 131 u_oce(:,:) = ssu_m(:,:) * umask(:,:,1) 126 132 v_oce(:,:) = ssv_m(:,:) * vmask(:,:,1) 127 128 ! masked sea surface freezing temperature [Kelvin] (set to rt0 over land) 133 !!gm the umask, vmask above is useless as ssu_m, ssv_m are build from masked un,vn (used t be here for B-grid sea-ice) 134 135 ! ! masked sea surface freezing temperature [Kelvin] (set to rt0 over land) 129 136 CALL eos_fzp( sss_m(:,:) , t_bo(:,:) ) 130 137 t_bo(:,:) = ( t_bo(:,:) + rt0 ) * tmask(:,:,1) + rt0 * ( 1._wp - tmask(:,:,1) ) 131 138 ! 132 CALL ice_bef ! Store previous ice values 139 CALL ice_bef ! Store previous ice values 140 ! 133 141 !------------------------------------------------! 134 142 ! --- Dynamical coupling with the atmosphere --- ! 135 143 !------------------------------------------------! 136 ! it provides:144 ! It provides the following fields used in sea ice model: 137 145 ! utau_ice, vtau_ice = surface ice stress [N/m2] 138 !------------------------------------------------ --139 146 !------------------------------------------------! 147 CALL ice_forcing_tau( kt, ksbc, utau_ice, vtau_ice ) 140 148 141 !-------------------------------------------------------! 142 ! --- ice dynamics and transport (except in 1D case) ---! 143 !-------------------------------------------------------! 144 CALL ice_diag0 ! set diag of mass, heat and salt fluxes to 0 145 CALL ice_rst_opn( kt ) ! Open Ice restart file 146 ! 147 ! --- zap this if no ice dynamics --- ! 148 IF( .NOT. lk_c1d .AND. ln_limdyn ) THEN 149 CALL ice_rhg( kt ) ! -- rheology 150 CALL ice_adv( kt ) ! -- advection 151 IF( nn_limdyn == 2 .AND. nn_monocat /= 2 ) & ! -- ridging/rafting 152 & CALL ice_rdgrft( kt ) 153 IF( nn_limdyn == 2 ) CALL ice_cor( kt , 1 ) ! -- Corrections 154 ! 155 ENDIF 156 ! --- 157 149 !-------------------------------------! 150 ! --- ice dynamics and advection --- ! 151 !-------------------------------------! 152 CALL ice_diag0 ! set diag of mass, heat and salt fluxes to 0 153 CALL ice_rst_opn( kt ) ! Open Ice restart file (if necessary) 154 ! 155 SELECT CASE( nice_dyn ) 156 CASE ( np_dynFULL ) !== all dynamical processes ==! 157 CALL ice_rhg ( kt ) ! -- rheology 158 CALL ice_adv ( kt ) ! -- advection of ice 159 CALL ice_rdgrft( kt ) ! -- ridging/rafting 160 CALL ice_cor ( kt , 1 ) ! -- Corrections 161 CASE ( np_dyn ) !== pure dynamics only ==! (no ridging/rafting) (nono cat. case 2) 162 CALL ice_rhg ( kt ) ! -- rheology 163 CALL ice_adv ( kt ) ! -- advection of ice 164 CALL ice_cor ( kt , 1 ) ! -- Corrections 165 CASE ( np_dynPURE ) !== pure dynamics only ==! (nn_limdyn= 0 or 1 ) 166 CALL ice_rhg ( kt ) ! -- rheology 167 CALL ice_adv ( kt ) ! -- advection of ice 168 END SELECT 169 ! 170 ! !== lateral boundary conditions ==! 158 171 #if defined key_agrif 159 IF( .NOT. Agrif_Root() ) CALL agrif_interp_lim3('T')172 IF( .NOT. Agrif_Root() ) CALL agrif_interp_lim3('T') ! -- AGRIF 160 173 #endif 161 IF( ln_limthd .AND. ln_bdy ) CALL bdy_ice( kt ) ! -- bdy ice thermo 162 ! previous lead fraction and ice volume for flux calculations 163 CALL ice_var_glo2eqv ! ht_i and ht_s for ice albedo calculation 164 CALL ice_var_agg(1) ! at_i for coupling 165 CALL ice_bef 174 IF( ln_limthd .AND. ln_bdy ) CALL bdy_ice( kt ) ! -- bdy ice thermo 175 ! 176 ! 177 ! !== previous lead fraction and ice volume for flux calculations 178 ! 179 CALL ice_var_glo2eqv ! ht_i and ht_s for ice albedo calculation 180 CALL ice_var_agg(1) ! at_i for coupling 181 CALL ice_bef ! Store previous ice values 166 182 167 183 !------------------------------------------------------! … … 169 185 !------------------------------------------------------! 170 186 ! It provides the following fields used in sea ice model: 171 ! fr1_i0 , fr2_i0 = 1sr & 2nd fraction of qsr penetration in ice [%] 172 ! emp_oce , emp_ice = E-P over ocean and sea ice [Kg/m2/s] 173 ! sprecip = solid precipitation [Kg/m2/s] 174 ! evap_ice = sublimation [Kg/m2/s] 175 ! qsr_tot , qns_tot = solar & non solar heat flux (total) [W/m2] 176 ! qsr_ice , qns_ice = solar & non solar heat flux over ice [W/m2] 177 ! dqns_ice = non solar heat sensistivity [W/m2] 178 ! qemp_oce, qemp_ice, qprec_ice, qevap_ice = sensible heat (associated with evap & precip) [W/m2] 179 !------------------------------------------------------------------------------------------------------ 180 CALL ice_forcing_flx( kt, ksbc ) 187 ! fr1_i0 , fr2_i0 = 1sr & 2nd fraction of qsr penetration in ice [%] 188 ! emp_oce , emp_ice = E-P over ocean and sea ice [Kg/m2/s] 189 ! sprecip = solid precipitation [Kg/m2/s] 190 ! evap_ice = sublimation [Kg/m2/s] 191 ! qsr_tot , qns_tot = solar & non solar heat flux (total) [W/m2] 192 ! qsr_ice , qns_ice = solar & non solar heat flux over ice [W/m2] 193 ! dqns_ice = non solar heat sensistivity [W/m2] 194 ! qemp_oce, qemp_ice, = sensible heat (associated with evap & precip) [W/m2] 195 ! qprec_ice, qevap_ice 196 !------------------------------------------------------! 197 CALL ice_forcing_flx( kt, ksbc ) 181 198 182 199 !----------------------------! 183 200 ! --- ice thermodynamics --- ! 184 201 !----------------------------! 185 ! --- zap this if no ice thermo --- ! 186 IF( ln_limthd ) CALL ice_thd( kt ) ! -- Ice thermodynamics 202 IF( ln_limthd ) CALL ice_thd( kt ) ! -- Ice thermodynamics 187 203 188 204 ! MV MP 2016 189 IF ( ln_pnd ) CALL lim_mp( kt )! -- Melt ponds205 IF ( ln_pnd ) CALL lim_mp( kt ) ! -- Melt ponds 190 206 ! END MV MP 2016 191 207 192 IF( ln_limthd ) CALL ice_cor( kt , 2 )! -- Corrections208 IF( ln_limthd ) CALL ice_cor( kt , 2 ) ! -- Corrections 193 209 ! --- 194 210 # if defined key_agrif 195 IF( .NOT. Agrif_Root() ) 211 IF( .NOT. Agrif_Root() ) CALL agrif_update_lim3( kt ) 196 212 # endif 197 CALL ice_var_glo2eqv! necessary calls (at least for coupling)198 CALL ice_var_agg( 2 )! necessary calls (at least for coupling)199 213 CALL ice_var_glo2eqv ! necessary calls (at least for coupling) 214 CALL ice_var_agg( 2 ) ! necessary calls (at least for coupling) 215 ! 200 216 !! clem: one should switch the calculation of the fluxes onto the parent grid but the following calls do not work 201 217 !! moreover it should only be called at the update frequency (as in agrif_lim3_update.F90) … … 203 219 !! IF( .NOT. Agrif_Root() ) CALL Agrif_ChildGrid_To_ParentGrid() 204 220 !!# endif 205 CALL ice_update_flx( kt ) ! -- Update surface oceanmass, heat and salt fluxes221 CALL ice_update_flx( kt ) ! -- Update ocean surface mass, heat and salt fluxes 206 222 !!# if defined key_agrif 207 223 !! IF( .NOT. Agrif_Root() ) CALL Agrif_ParentGrid_To_ChildGrid() 208 224 !!# endif 209 IF( ln_limdiahsb ) CALL ice_dia( kt ) ! -- Diagnostics and outputs225 IF( ln_limdiahsb ) CALL ice_dia( kt ) ! -- Diagnostics and outputs 210 226 ! 211 227 CALL ice_wri( 1 ) ! -- Ice outputs 212 228 ! 213 IF( kt == nit000 .AND. ln_rstart ) & 229 IF( kt == nit000 .AND. ln_rstart ) & !!gm I don't understand the ln_rstart, if needed, add a comment, please 214 230 & CALL iom_close( numrir ) ! close input ice restart file 215 231 ! … … 287 303 IF( ln_limdiahsb) CALL ice_dia_init ! initialization for diags 288 304 ! 289 fr_i (:,:)= at_i(:,:) ! initialisation of sea-ice fraction305 fr_i (:,:) = at_i(:,:) ! initialisation of sea-ice fraction 290 306 tn_ice(:,:,:) = t_su(:,:,:) ! initialisation of surface temp for coupled simu 291 307 ! 292 308 DO jj = 1, jpj 293 309 DO ji = 1, jpi 294 IF( gphit(ji,jj) > 0._wp ) THEN ;rn_amax_2d(ji,jj) = rn_amax_n ! NH295 ELSE ;rn_amax_2d(ji,jj) = rn_amax_s ! SH310 IF( gphit(ji,jj) > 0._wp ) THEN ; rn_amax_2d(ji,jj) = rn_amax_n ! NH 311 ELSE ; rn_amax_2d(ji,jj) = rn_amax_s ! SH 296 312 ENDIF 297 313 END DO … … 318 334 !!------------------------------------------------------------------- 319 335 ! 320 REWIND( numnam_ice_ref ) 336 REWIND( numnam_ice_ref ) ! Namelist namicerun in reference namelist : Parameters for ice 321 337 READ ( numnam_ice_ref, namicerun, IOSTAT = ios, ERR = 901) 322 338 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicerun in reference namelist', lwp ) 323 339 324 REWIND( numnam_ice_cfg ) 340 REWIND( numnam_ice_cfg ) ! Namelist namicerun in configuration namelist : Parameters for ice 325 341 READ ( numnam_ice_cfg, namicerun, IOSTAT = ios, ERR = 902 ) 326 342 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicerun in configuration namelist', lwp ) 327 343 IF(lwm) WRITE ( numoni, namicerun ) 328 344 ! 329 REWIND( numnam_ice_ref ) 345 REWIND( numnam_ice_ref ) ! Namelist namicediag in reference namelist : Parameters for ice 330 346 READ ( numnam_ice_ref, namicediag, IOSTAT = ios, ERR = 903) 331 347 903 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicediag in reference namelist', lwp ) 332 348 333 REWIND( numnam_ice_cfg ) 349 REWIND( numnam_ice_cfg ) ! Namelist namicediag in configuration namelist : Parameters for ice 334 350 READ ( numnam_ice_cfg, namicediag, IOSTAT = ios, ERR = 904 ) 335 351 904 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicediag in configuration namelist', lwp ) 336 352 IF(lwm) WRITE ( numoni, namicediag ) 337 353 ! 338 IF(lwp) THEN 354 IF(lwp) THEN ! control print 339 355 WRITE(numout,*) 340 356 WRITE(numout,*) 'ice_run_init : ice share parameters for dynamics/advection/thermo of sea-ice' 341 357 WRITE(numout,*) ' ~~~~~~' 342 WRITE(numout,*) ' number of ice categories jpl = ', jpl343 WRITE(numout,*) ' number of ice layers nlay_i = ', nlay_i344 WRITE(numout,*) ' number of snow layers nlay_s = ', nlay_s345 WRITE(numout,*) ' virtual ITD mono-category param (1-4) or not (0) nn_monocat = ', nn_monocat346 WRITE(numout,*) ' maximum ice concentration for NH = ', rn_amax_n347 WRITE(numout,*) ' maximum ice concentration for SH = ', rn_amax_s348 WRITE(numout,*) ' Ice thermodynamics (T) or not (F) ln_limthd = ', ln_limthd349 WRITE(numout,*) ' Ice dynamics (T) or not (F) ln_limdyn = ', ln_limdyn350 WRITE(numout,*) ' (ln_limdyn=T) Ice dynamics switch nn_limdyn = ', nn_limdyn351 WRITE(numout,*) ' 2: total'352 WRITE(numout,*) ' 1: advection only (no diffusion, no ridging/rafting)'353 WRITE(numout,*) ' 0: advection only (as 1 + prescribed velocity, bypass rheology)'354 WRITE(numout,*) ' (ln_limdyn=T) prescribed u-vel (case nn_limdyn=0) = ', rn_uice355 WRITE(numout,*) ' (ln_limdyn=T) prescribed v-vel (case nn_limdyn=0) = ', rn_vice358 WRITE(numout,*) ' Namelist namicerun : ' 359 WRITE(numout,*) ' number of ice categories jpl = ', jpl 360 WRITE(numout,*) ' number of ice layers nlay_i = ', nlay_i 361 WRITE(numout,*) ' number of snow layers nlay_s = ', nlay_s 362 WRITE(numout,*) ' virtual ITD mono-category param (1-4) or not (0) nn_monocat = ', nn_monocat 363 WRITE(numout,*) ' maximum ice concentration for NH = ', rn_amax_n 364 WRITE(numout,*) ' maximum ice concentration for SH = ', rn_amax_s 365 WRITE(numout,*) ' Ice thermodynamics (T) or not (F) ln_limthd = ', ln_limthd 366 WRITE(numout,*) ' Ice dynamics (T) or not (F) ln_limdyn = ', ln_limdyn 367 WRITE(numout,*) ' associated switch nn_limdyn = ', nn_limdyn 368 WRITE(numout,*) ' =2 all processes (default option)' 369 WRITE(numout,*) ' =1 advection only (no ridging/rafting)' 370 WRITE(numout,*) ' =0 advection only with prescribed velocity given by ' 371 WRITE(numout,*) ' a uniform field (u,v)_ice = (rn_uice,rn_vice) = (', rn_uice,',', rn_vice,')' 356 372 WRITE(numout,*) 357 WRITE(numout,*) '...and ice diagnostics' 358 WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~' 359 WRITE(numout,*) ' Diagnose online heat/mass/salt budget ln_limdiachk = ', ln_limdiachk 360 WRITE(numout,*) ' Output heat/mass/salt budget ln_limdiahsb = ', ln_limdiahsb 361 WRITE(numout,*) ' control prints in ocean.out for (i,j)=(iiceprt,jiceprt) = ', ln_limctl 362 WRITE(numout,*) ' i-index for control prints (ln_limctl=true) = ', iiceprt 363 WRITE(numout,*) ' j-index for control prints (ln_limctl=true) = ', jiceprt 373 WRITE(numout,*) ' Namelist namicediag : ' 374 WRITE(numout,*) ' Diagnose online heat/mass/salt budget ln_limdiachk = ', ln_limdiachk 375 WRITE(numout,*) ' Output heat/mass/salt budget ln_limdiahsb = ', ln_limdiahsb 376 WRITE(numout,*) ' control prints for a given grid point ln_limctl = ', ln_limctl 377 WRITE(numout,*) ' chosen grid point position (iiceprt,jiceprt) = (', iiceprt,',', jiceprt,')' 364 378 ENDIF 365 379 ! 366 IF ( ( jpl > 1 ) .AND. ( nn_monocat == 1 ) ) THEN 380 ! !--- check consistency 381 IF ( jpl > 1 .AND. nn_monocat == 1 ) THEN 367 382 nn_monocat = 0 368 383 IF(lwp) WRITE(numout,*) 369 384 IF(lwp) WRITE(numout,*) ' nn_monocat forced to 0 as jpl>1, i.e. multi-category case is chosen' 370 385 ENDIF 371 IF ( ( jpl == 1 ) .AND. ( nn_monocat == 0 )) THEN386 IF ( jpl == 1 .AND. nn_monocat == 0 ) THEN 372 387 CALL ctl_stop( 'STOP', 'ice_run_init : if jpl=1 then nn_monocat should be between 1 and 4' ) 373 388 ENDIF 374 389 ! 375 ! sea-ice timestep and inverse 376 rdt_ice = REAL(nn_fsbc) * rdt 377 r1_rdtice = 1._wp / rdt_ice 378 379 ! inverse of nlay_i and nlay_s 380 r1_nlay_i = 1._wp / REAL( nlay_i, wp ) 390 IF( ln_bdy .AND. ln_limdiachk ) CALL ctl_warn('ice_run_init: online conservation check does not work with BDY') 391 ! 392 ! ! set the choice of ice dynamics 393 IF( lk_c1d .OR. .NOT.ln_limdyn ) THEN 394 nice_dyn = np_dynNO !--- no dynamics 395 ELSE 396 SELECT CASE( nn_limdyn ) 397 CASE( 2 ) 398 IF( nn_monocat /= 2 ) THEN !--- full dynamics (rheology + advection + ridging/rafting + correction) 399 nice_dyn = np_dynFULL 400 ELSE 401 nice_dyn = np_dyn !--- dynamics without ridging/rafting 402 ENDIF 403 CASE( 0 , 1 ) !--- dynamics without ridging/rafting and correction 404 nice_dyn = np_dynPURE 405 END SELECT 406 ENDIF 407 ! !--- simple conservative piling, comparable with LIM2 408 l_piling = nn_limdyn == 1 .OR. ( nn_monocat == 2 .AND. jpl == 1 ) 409 ! 410 rdt_ice = REAL(nn_fsbc) * rdt !--- sea-ice timestep and inverse 411 r1_rdtice = 1._wp / rdt_ice 412 IF( lwp ) WRITE(numout,*) ' ice timestep rdt_ice = ', rdt_ice 413 ! 414 r1_nlay_i = 1._wp / REAL( nlay_i, wp ) !--- inverse of nlay_i and nlay_s 381 415 r1_nlay_s = 1._wp / REAL( nlay_s, wp ) 382 !383 IF( lwp .AND. ln_bdy .AND. ln_limdiachk ) &384 & CALL ctl_warn('online conservation check activated but it does not work with BDY')385 !386 IF( lwp ) WRITE(numout,*) ' ice timestep rdt_ice = ', rdt_ice387 416 ! 388 417 END SUBROUTINE ice_run_init … … 397 426 !! ** input : Namelist namiceitd 398 427 !!------------------------------------------------------------------- 399 INTEGER :: ios ! Local integer output status for namelist read 428 INTEGER :: jl ! dummy loop index 429 INTEGER :: ios ! Local integer output status for namelist read 430 REAL(wp) :: zc1, zc2, zc3, zx1 ! local scalars 431 REAL(wp) :: zhmax, znum, zden, zalpha ! - - 432 !! 400 433 NAMELIST/namiceitd/ rn_himean 401 !402 INTEGER :: jl ! dummy loop index403 REAL(wp) :: zc1, zc2, zc3, zx1 ! local scalars404 REAL(wp) :: zhmax, znum, zden, zalpha !405 434 !!------------------------------------------------------------------ 406 435 ! 407 REWIND( numnam_ice_ref ) 436 REWIND( numnam_ice_ref ) ! Namelist namiceitd in reference namelist : Parameters for ice 408 437 READ ( numnam_ice_ref, namiceitd, IOSTAT = ios, ERR = 905) 409 438 905 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namiceitd in reference namelist', lwp ) 410 439 411 REWIND( numnam_ice_cfg ) 440 REWIND( numnam_ice_cfg ) ! Namelist namiceitd in configuration namelist : Parameters for ice 412 441 READ ( numnam_ice_cfg, namiceitd, IOSTAT = ios, ERR = 906 ) 413 442 906 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namiceitd in configuration namelist', lwp ) 414 443 IF(lwm) WRITE ( numoni, namiceitd ) 415 444 ! 416 IF(lwp) THEN 445 IF(lwp) THEN ! control print 417 446 WRITE(numout,*) 418 447 WRITE(numout,*) 'ice_itd_init : Initialization of ice cat distribution ' 419 448 WRITE(numout,*) '~~~~~~~~~~~~' 420 WRITE(numout,*) ' mean ice thickness in the domain rn_himean = ', rn_himean 449 WRITE(numout,*) ' Namelist namicerun : ' 450 WRITE(numout,*) ' mean ice thickness in the domain rn_himean = ', rn_himean 421 451 ENDIF 422 452 ! 423 !---------------------------------- 424 !- Thickness categories boundaries 425 !---------------------------------- 426 ! 427 !== h^(-alpha) function ==! 428 zalpha = 0.05_wp 453 !-----------------------------------! 454 ! Thickness categories boundaries ! 455 !-----------------------------------! 456 ! 457 zalpha = 0.05_wp ! max of each category (from h^(-alpha) function) 429 458 zhmax = 3._wp * rn_himean 430 459 DO jl = 1, jpl … … 441 470 ! 442 471 IF(lwp) WRITE(numout,*) 443 IF(lwp) WRITE(numout,*) ' Thickness category boundaries'444 IF(lwp) WRITE(numout,*) ' hi_max', hi_max(0:jpl)472 IF(lwp) WRITE(numout,*) ' ===>>> resulting thickness category boundaries :' 473 IF(lwp) WRITE(numout,*) ' hi_max(:)= ', hi_max(0:jpl) 445 474 ! 446 475 END SUBROUTINE ice_itd_init 476 447 477 448 478 SUBROUTINE ice_bef … … 472 502 END DO 473 503 END DO 474 CALL lbc_lnk_multi( a_i_b, 'T', 1., v_i_b , 'T', 1., v_s_b , 'T', 1., smv_i_b, 'T', 1.,&475 & oa_i_b, 'T', 1., ht_i_b, 'T', 1., ht_s_b, 'T', 1. )504 CALL lbc_lnk_multi( a_i_b, 'T', 1., v_i_b , 'T', 1., ht_i_b, 'T', 1., smv_i_b, 'T', 1., & 505 & oa_i_b, 'T', 1., v_s_b , 'T', 1., ht_s_b, 'T', 1. ) 476 506 CALL lbc_lnk( e_i_b, 'T', 1. ) 477 507 CALL lbc_lnk( e_s_b, 'T', 1. ) 478 508 509 !!gm Question: here , a_i_b, u_ice and v_ice are defined over the whole domain, 510 !!gm so why not just a copy over the whole domain and no lbc_lnk ? 511 !!gm that is some thing like: 512 ! at_i_b(:,:) = SUM( a_i_b(:,:,:), dim=3 ) 513 ! u_ice_b(:,:) = u_ice(:,:) 514 ! v_ice_b(:,:) = v_ice(:,:) 515 ! idem for the loop above 516 !!gm 479 517 ! ice velocities & total concentration 480 518 DO jj = 2, jpjm1 … … 486 524 END DO 487 525 CALL lbc_lnk_multi( at_i_b, 'T', 1., u_ice_b , 'U', -1., v_ice_b , 'V', -1. ) 488 526 ! 489 527 END SUBROUTINE ice_bef 490 528 … … 552 590 !!---------------------------------------------------------------------- 553 591 CONTAINS 554 !555 592 SUBROUTINE ice_stp ( kt, ksbc ) ! Dummy routine 556 593 INTEGER, INTENT(in) :: kt, ksbc 557 594 WRITE(*,*) 'ice_stp: You should not have seen this print! error?', kt 558 595 END SUBROUTINE ice_stp 559 !560 596 SUBROUTINE ice_init ! Dummy routine 561 597 END SUBROUTINE ice_init -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icetab.F90
r8420 r8486 24 24 25 25 !!---------------------------------------------------------------------- 26 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2010)26 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 27 27 !! $Id: icetab.F90 8369 2017-07-25 14:38:38Z clem $ 28 28 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 29 29 !!---------------------------------------------------------------------- 30 30 CONTAINS 31 32 31 33 32 SUBROUTINE tab_3d_2d( ndim1d, tab_ind, tab1d, tab2d ) … … 51 50 END SUBROUTINE tab_3d_2d 52 51 52 53 53 SUBROUTINE tab_2d_1d( ndim1d, tab_ind, tab1d, tab2d ) 54 54 !!---------------------------------------------------------------------- … … 68 68 END DO 69 69 END SUBROUTINE tab_2d_1d 70 70 71 71 72 SUBROUTINE tab_2d_3d( ndim1d, tab_ind, tab1d, tab2d ) … … 89 90 END SUBROUTINE tab_2d_3d 90 91 92 91 93 SUBROUTINE tab_1d_2d( ndim1d, tab_ind, tab1d, tab2d ) 92 94 !!---------------------------------------------------------------------- … … 107 109 END SUBROUTINE tab_1d_2d 108 110 111 #else 112 !!---------------------------------------------------------------------- 113 !! Default option Dummy module NO LIM 3.0 sea-ice model 114 !!---------------------------------------------------------------------- 109 115 #endif 116 110 117 !!====================================================================== 111 118 END MODULE icetab -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd.F90
r8483 r8486 15 15 #if defined key_lim3 16 16 !!---------------------------------------------------------------------- 17 !! 'key_lim3' LIM3 sea-ice model17 !! 'key_lim3' LIM3 sea-ice model 18 18 !!---------------------------------------------------------------------- 19 19 !! ice_thd : thermodynamic of sea ice … … 23 23 USE dom_oce ! ocean space and time domain variables 24 24 USE ice ! sea-ice variables 25 !!gm list trop longue ==>>> why not passage en argument d'appel ? 25 26 USE sbc_oce , ONLY : sss_m, sst_m, e3t_m, utau, vtau, ssu_m, ssv_m, frq_m, qns_tot, qsr_tot, sprecip, ln_cpl 26 27 USE sbc_ice , ONLY : qsr_oce, qns_oce, qemp_oce, qsr_ice, qns_ice, dqns_ice, evap_ice, qprec_ice, qevap_ice, & … … 53 54 # include "vectopt_loop_substitute.h90" 54 55 !!---------------------------------------------------------------------- 55 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2010)56 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 56 57 !! $Id: icethd.F90 8420 2017-08-08 12:18:46Z clem $ 57 58 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 75 76 !! - call ice_thd_temp to retrieve temperature from ice enthalpy 76 77 !! - back to the geographic grid 77 !!78 !! ** References :79 78 !!--------------------------------------------------------------------- 80 79 INTEGER, INTENT(in) :: kt ! number of iteration … … 93 92 IF( kt == nit000 .AND. lwp ) THEN 94 93 WRITE(numout,*) 95 WRITE(numout,*)' icethd '96 WRITE(numout,*)' ~~~~~~~ '94 WRITE(numout,*)' icethd : sea-ice thermodynamics' 95 WRITE(numout,*)' ~~~~~~~~' 97 96 ENDIF 98 97 99 98 ! conservation test 100 IF( ln_limdiachk ) CALL ice_cons_hsm(0, 'icethd', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b)99 IF( ln_limdiachk ) CALL ice_cons_hsm( 0, 'icethd', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b ) 101 100 102 101 CALL ice_var_glo2eqv … … 231 230 dh_snowice(1:nidx) = 0._wp ; dh_i_sub (1:nidx) = 0._wp 232 231 ! 233 IF( ln_limdH ) CALL ice_thd_dif ! --- Ice/Snow Temperature profile--- !234 !235 IF( ln_limdH ) CALL ice_thd_dh ! --- Ice/Snow thickness --- !236 !237 IF( ln_limdH ) CALL ice_thd_ent( e_i_1d(1:nidx,:) ) ! --- Ice enthalpy remapping --- !232 IF( ln_limdH ) THEN ! --- growing/melting --- ! 233 CALL ice_thd_dif ! Ice/Snow Temperature profile 234 CALL ice_thd_dh ! Ice/Snow thickness 235 CALL ice_thd_ent( e_i_1d(1:nidx,:) ) ! Ice enthalpy remapping 236 ENDIF 238 237 ! 239 238 CALL ice_thd_sal ! --- Ice salinity --- ! … … 241 240 CALL ice_thd_temp ! --- temperature update --- ! 242 241 ! 242 !!gm please create a new logical (l_thd_lam or a better explicit name) set one for all in icestp.F90 module 243 !!gm l_thd_lam = ln_limdH .AND. ( ( nn_monocat == 1 .OR. nn_monocat == 4 ) .AND. jpl == 1 ) 244 !!gm by the way, the different options associated with nn_monocat =1 to 4 are quite impossible to identify 245 !!gm more comment to add when ready the namelist, with an explicit print in the ocean.output 243 246 IF( ln_limdH ) THEN 244 247 IF ( ( nn_monocat == 1 .OR. nn_monocat == 4 ) .AND. jpl == 1 ) THEN … … 259 262 oa_i(:,:,:) = o_i(:,:,:) * a_i(:,:,:) 260 263 261 IF( ln_limdiachk ) CALL ice_cons_hsm(1, 'icethd', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b)262 ! 263 CALL ice_var_zapsmall ! --- remove very small ice concentration (<1e-10) --- !264 ! ! & make sure at_i=SUM(a_i) & ato_i=1 where at_i=0264 IF( ln_limdiachk ) CALL ice_cons_hsm( 1, 'icethd', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b ) 265 ! 266 CALL ice_var_zapsmall ! --- remove very small ice concentration (<1e-10) --- ! 267 ! ! & make sure at_i=SUM(a_i) & ato_i=1 where at_i=0 265 268 ! 266 IF( jpl > 1 ) CALL ice_itd_rem( kt ) ! --- Transport ice between thickness categories --- !267 ! 268 IF( ln_limdO ) CALL ice_thd_lac ! --- frazil ice growing in leads --- !269 ! 270 IF( ln_limctl ) CALL ice_prt( kt, iiceprt, jiceprt, 1, ' - ice thermodyn. - ' ) ! control print271 IF( ln_ctl ) CALL ice_prt3D( 'icethd' ) ! Control print269 IF( jpl > 1 ) CALL ice_itd_rem( kt ) ! --- Transport ice between thickness categories --- ! 270 ! 271 IF( ln_limdO ) CALL ice_thd_lac ! --- frazil ice growing in leads --- ! 272 ! 273 IF( ln_limctl ) CALL ice_prt( kt, iiceprt, jiceprt, 1, ' - ice thermodyn. - ' ) ! control print 274 IF( ln_ctl ) CALL ice_prt3D( 'icethd' ) ! Control print 272 275 ! 273 276 IF( nn_timing == 1 ) CALL timing_stop('icethd') 274 277 ! 275 278 END SUBROUTINE ice_thd 276 279 … … 341 344 342 345 343 SUBROUTINE ice_thd_1d2d( jl, kn )346 SUBROUTINE ice_thd_1d2d( kl, kn ) 344 347 !!----------------------------------------------------------------------- 345 348 !! *** ROUTINE ice_thd_1d2d *** … … 347 350 !! ** Purpose : move arrays from 1d to 2d and the reverse 348 351 !!----------------------------------------------------------------------- 349 INTEGER, INTENT(in) :: jl ! ice cat350 INTEGER, INTENT(in) :: kn 351 ! 352 INTEGER :: jk! dummy loop indices352 INTEGER, INTENT(in) :: kl ! index of the ice category 353 INTEGER, INTENT(in) :: kn ! 1= from 2D to 1D ; 2= from 1D to 2D 354 ! 355 INTEGER :: jk ! dummy loop indices 353 356 !!----------------------------------------------------------------------- 354 357 ! 355 358 SELECT CASE( kn ) 356 ! 357 CASE( 1 ) ! from 2D to 1D358 ! 359 ! !---------------------! 360 CASE( 1 ) !== from 2D to 1D ==! 361 ! !---------------------! 359 362 CALL tab_2d_1d( nidx, idxice(1:nidx), at_i_1d(1:nidx), at_i ) 360 CALL tab_2d_1d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i (:,:,jl))361 CALL tab_2d_1d( nidx, idxice(1:nidx), ht_i_1d(1:nidx), ht_i(:,:, jl) )362 CALL tab_2d_1d( nidx, idxice(1:nidx), ht_s_1d(1:nidx), ht_s(:,:, jl) )363 CALL tab_2d_1d( nidx, idxice(1:nidx), t_su_1d(1:nidx), t_su(:,:, jl) )364 CALL tab_2d_1d( nidx, idxice(1:nidx), sm_i_1d(1:nidx), sm_i(:,:, jl) )363 CALL tab_2d_1d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i (:,:,kl) ) 364 CALL tab_2d_1d( nidx, idxice(1:nidx), ht_i_1d(1:nidx), ht_i(:,:,kl) ) 365 CALL tab_2d_1d( nidx, idxice(1:nidx), ht_s_1d(1:nidx), ht_s(:,:,kl) ) 366 CALL tab_2d_1d( nidx, idxice(1:nidx), t_su_1d(1:nidx), t_su(:,:,kl) ) 367 CALL tab_2d_1d( nidx, idxice(1:nidx), sm_i_1d(1:nidx), sm_i(:,:,kl) ) 365 368 DO jk = 1, nlay_s 366 CALL tab_2d_1d( nidx, idxice(1:nidx), t_s_1d(1:nidx,jk), t_s(:,:,jk, jl) )367 CALL tab_2d_1d( nidx, idxice(1:nidx), e_s_1d(1:nidx,jk), e_s(:,:,jk, jl) )369 CALL tab_2d_1d( nidx, idxice(1:nidx), t_s_1d(1:nidx,jk), t_s(:,:,jk,kl) ) 370 CALL tab_2d_1d( nidx, idxice(1:nidx), e_s_1d(1:nidx,jk), e_s(:,:,jk,kl) ) 368 371 END DO 369 372 DO jk = 1, nlay_i 370 CALL tab_2d_1d( nidx, idxice(1:nidx), t_i_1d(1:nidx,jk), t_i(:,:,jk, jl) )371 CALL tab_2d_1d( nidx, idxice(1:nidx), e_i_1d(1:nidx,jk), e_i(:,:,jk, jl) )372 CALL tab_2d_1d( nidx, idxice(1:nidx), s_i_1d(1:nidx,jk), s_i(:,:,jk, jl) )373 CALL tab_2d_1d( nidx, idxice(1:nidx), t_i_1d(1:nidx,jk), t_i(:,:,jk,kl) ) 374 CALL tab_2d_1d( nidx, idxice(1:nidx), e_i_1d(1:nidx,jk), e_i(:,:,jk,kl) ) 375 CALL tab_2d_1d( nidx, idxice(1:nidx), s_i_1d(1:nidx,jk), s_i(:,:,jk,kl) ) 373 376 END DO 374 377 ! 375 378 CALL tab_2d_1d( nidx, idxice(1:nidx), qprec_ice_1d(1:nidx), qprec_ice ) 376 CALL tab_2d_1d( nidx, idxice(1:nidx), qsr_ice_1d (1:nidx), qsr_ice (:,:,jl))379 CALL tab_2d_1d( nidx, idxice(1:nidx), qsr_ice_1d (1:nidx), qsr_ice (:,:,kl) ) 377 380 CALL tab_2d_1d( nidx, idxice(1:nidx), fr1_i0_1d (1:nidx), fr1_i0 ) 378 381 CALL tab_2d_1d( nidx, idxice(1:nidx), fr2_i0_1d (1:nidx), fr2_i0 ) 379 CALL tab_2d_1d( nidx, idxice(1:nidx), qns_ice_1d (1:nidx), qns_ice (:,:,jl))380 CALL tab_2d_1d( nidx, idxice(1:nidx), ftr_ice_1d (1:nidx), ftr_ice (:,:,jl))381 CALL tab_2d_1d( nidx, idxice(1:nidx), evap_ice_1d (1:nidx), evap_ice(:,:, jl) )382 CALL tab_2d_1d( nidx, idxice(1:nidx), dqns_ice_1d (1:nidx), dqns_ice(:,:, jl) )382 CALL tab_2d_1d( nidx, idxice(1:nidx), qns_ice_1d (1:nidx), qns_ice (:,:,kl) ) 383 CALL tab_2d_1d( nidx, idxice(1:nidx), ftr_ice_1d (1:nidx), ftr_ice (:,:,kl) ) 384 CALL tab_2d_1d( nidx, idxice(1:nidx), evap_ice_1d (1:nidx), evap_ice(:,:,kl) ) 385 CALL tab_2d_1d( nidx, idxice(1:nidx), dqns_ice_1d (1:nidx), dqns_ice(:,:,kl) ) 383 386 CALL tab_2d_1d( nidx, idxice(1:nidx), t_bo_1d (1:nidx), t_bo ) 384 387 CALL tab_2d_1d( nidx, idxice(1:nidx), sprecip_1d (1:nidx), sprecip ) … … 435 438 DO jk = 1, nlay_i 436 439 WHERE( ht_i_1d(1:nidx)>0._wp ) e_i_1d(1:nidx,jk) = e_i_1d(1:nidx,jk) / (ht_i_1d(1:nidx) * a_i_1d(1:nidx)) * nlay_i 437 END DO440 END DO 438 441 DO jk = 1, nlay_s 439 442 WHERE( ht_s_1d(1:nidx)>0._wp ) e_s_1d(1:nidx,jk) = e_s_1d(1:nidx,jk) / (ht_s_1d(1:nidx) * a_i_1d(1:nidx)) * nlay_s 440 ENDDO 441 ! 442 CASE( 2 ) ! from 1D to 2D 443 ! 443 END DO 444 ! 445 ! !---------------------! 446 CASE( 2 ) !== from 1D to 2D ==! 447 ! !---------------------! 444 448 ! --- Change units of e_i, e_s from J/m3 to J/m2 --- ! 445 449 DO jk = 1, nlay_i 446 450 e_i_1d(1:nidx,jk) = e_i_1d(1:nidx,jk) * ht_i_1d(1:nidx) * a_i_1d(1:nidx) * r1_nlay_i 447 END DO451 END DO 448 452 DO jk = 1, nlay_s 449 453 e_s_1d(1:nidx,jk) = e_s_1d(1:nidx,jk) * ht_s_1d(1:nidx) * a_i_1d(1:nidx) * r1_nlay_s 450 END DO454 END DO 451 455 ! 452 456 ! Change thickness to volume … … 456 460 457 461 CALL tab_1d_2d( nidx, idxice(1:nidx), at_i_1d(1:nidx), at_i ) 458 CALL tab_1d_2d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i (:,:,jl))459 CALL tab_1d_2d( nidx, idxice(1:nidx), ht_i_1d(1:nidx), ht_i(:,:, jl) )460 CALL tab_1d_2d( nidx, idxice(1:nidx), ht_s_1d(1:nidx), ht_s(:,:, jl) )461 CALL tab_1d_2d( nidx, idxice(1:nidx), t_su_1d(1:nidx), t_su(:,:, jl) )462 CALL tab_1d_2d( nidx, idxice(1:nidx), sm_i_1d(1:nidx), sm_i(:,:, jl) )462 CALL tab_1d_2d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i (:,:,kl) ) 463 CALL tab_1d_2d( nidx, idxice(1:nidx), ht_i_1d(1:nidx), ht_i(:,:,kl) ) 464 CALL tab_1d_2d( nidx, idxice(1:nidx), ht_s_1d(1:nidx), ht_s(:,:,kl) ) 465 CALL tab_1d_2d( nidx, idxice(1:nidx), t_su_1d(1:nidx), t_su(:,:,kl) ) 466 CALL tab_1d_2d( nidx, idxice(1:nidx), sm_i_1d(1:nidx), sm_i(:,:,kl) ) 463 467 DO jk = 1, nlay_s 464 CALL tab_1d_2d( nidx, idxice(1:nidx), t_s_1d(1:nidx,jk), t_s(:,:,jk, jl))465 CALL tab_1d_2d( nidx, idxice(1:nidx), e_s_1d(1:nidx,jk), e_s(:,:,jk, jl))468 CALL tab_1d_2d( nidx, idxice(1:nidx), t_s_1d(1:nidx,jk), t_s(:,:,jk,kl) ) 469 CALL tab_1d_2d( nidx, idxice(1:nidx), e_s_1d(1:nidx,jk), e_s(:,:,jk,kl) ) 466 470 END DO 467 471 DO jk = 1, nlay_i 468 CALL tab_1d_2d( nidx, idxice(1:nidx), t_i_1d(1:nidx,jk), t_i(:,:,jk, jl))469 CALL tab_1d_2d( nidx, idxice(1:nidx), e_i_1d(1:nidx,jk), e_i(:,:,jk, jl))470 CALL tab_1d_2d( nidx, idxice(1:nidx), s_i_1d(1:nidx,jk), s_i(:,:,jk, jl))471 END DO 472 ! 473 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_snw_sni_1d(1:nidx), wfx_snw_sni 474 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_snw_sum_1d(1:nidx), wfx_snw_sum 475 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_sub_1d (1:nidx), wfx_sub 476 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_snw_sub_1d(1:nidx), wfx_snw_sub 477 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_ice_sub_1d(1:nidx), wfx_ice_sub 478 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_err_sub_1d(1:nidx), wfx_err_sub 479 ! 480 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_bog_1d (1:nidx), wfx_bog 481 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_bom_1d (1:nidx), wfx_bom 482 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_sum_1d (1:nidx), wfx_sum 483 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_sni_1d (1:nidx), wfx_sni 484 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_res_1d (1:nidx), wfx_res 485 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_spr_1d (1:nidx), wfx_spr 486 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_lam_1d (1:nidx), wfx_lam 487 ! 488 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_bog_1d (1:nidx), sfx_bog 489 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_bom_1d (1:nidx), sfx_bom 490 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_sum_1d (1:nidx), sfx_sum 491 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_sni_1d (1:nidx), sfx_sni 492 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_bri_1d (1:nidx), sfx_bri 493 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_res_1d (1:nidx), sfx_res 494 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_sub_1d (1:nidx), sfx_sub 495 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_lam_1d (1:nidx), sfx_lam 496 ! 497 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_thd_1d (1:nidx), hfx_thd 498 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_spr_1d (1:nidx), hfx_spr 499 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_sum_1d (1:nidx), hfx_sum 500 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_bom_1d (1:nidx), hfx_bom 501 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_bog_1d (1:nidx), hfx_bog 502 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_dif_1d (1:nidx), hfx_dif 503 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_opw_1d (1:nidx), hfx_opw 504 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_snw_1d (1:nidx), hfx_snw 505 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_sub_1d (1:nidx), hfx_sub 506 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_err_1d (1:nidx), hfx_err 507 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_res_1d (1:nidx), hfx_res 508 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_err_dif_1d(1:nidx), hfx_err_dif 509 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_err_rem_1d(1:nidx), hfx_err_rem 510 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_out_1d (1:nidx), hfx_out 511 ! 512 CALL tab_1d_2d( nidx, idxice(1:nidx), qns_ice_1d (1:nidx), qns_ice(:,:,jl))513 CALL tab_1d_2d( nidx, idxice(1:nidx), ftr_ice_1d (1:nidx), ftr_ice(:,:,jl))472 CALL tab_1d_2d( nidx, idxice(1:nidx), t_i_1d(1:nidx,jk), t_i(:,:,jk,kl) ) 473 CALL tab_1d_2d( nidx, idxice(1:nidx), e_i_1d(1:nidx,jk), e_i(:,:,jk,kl) ) 474 CALL tab_1d_2d( nidx, idxice(1:nidx), s_i_1d(1:nidx,jk), s_i(:,:,jk,kl) ) 475 END DO 476 ! 477 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_snw_sni_1d(1:nidx), wfx_snw_sni ) 478 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_snw_sum_1d(1:nidx), wfx_snw_sum ) 479 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_sub_1d (1:nidx), wfx_sub ) 480 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_snw_sub_1d(1:nidx), wfx_snw_sub ) 481 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_ice_sub_1d(1:nidx), wfx_ice_sub ) 482 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_err_sub_1d(1:nidx), wfx_err_sub ) 483 ! 484 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_bog_1d (1:nidx), wfx_bog ) 485 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_bom_1d (1:nidx), wfx_bom ) 486 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_sum_1d (1:nidx), wfx_sum ) 487 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_sni_1d (1:nidx), wfx_sni ) 488 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_res_1d (1:nidx), wfx_res ) 489 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_spr_1d (1:nidx), wfx_spr ) 490 CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_lam_1d (1:nidx), wfx_lam ) 491 ! 492 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_bog_1d (1:nidx), sfx_bog ) 493 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_bom_1d (1:nidx), sfx_bom ) 494 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_sum_1d (1:nidx), sfx_sum ) 495 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_sni_1d (1:nidx), sfx_sni ) 496 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_bri_1d (1:nidx), sfx_bri ) 497 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_res_1d (1:nidx), sfx_res ) 498 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_sub_1d (1:nidx), sfx_sub ) 499 CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_lam_1d (1:nidx), sfx_lam ) 500 ! 501 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_thd_1d (1:nidx), hfx_thd ) 502 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_spr_1d (1:nidx), hfx_spr ) 503 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_sum_1d (1:nidx), hfx_sum ) 504 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_bom_1d (1:nidx), hfx_bom ) 505 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_bog_1d (1:nidx), hfx_bog ) 506 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_dif_1d (1:nidx), hfx_dif ) 507 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_opw_1d (1:nidx), hfx_opw ) 508 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_snw_1d (1:nidx), hfx_snw ) 509 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_sub_1d (1:nidx), hfx_sub ) 510 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_err_1d (1:nidx), hfx_err ) 511 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_res_1d (1:nidx), hfx_res ) 512 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_err_dif_1d(1:nidx), hfx_err_dif ) 513 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_err_rem_1d(1:nidx), hfx_err_rem ) 514 CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_out_1d (1:nidx), hfx_out ) 515 ! 516 CALL tab_1d_2d( nidx, idxice(1:nidx), qns_ice_1d(1:nidx), qns_ice(:,:,kl) ) 517 CALL tab_1d_2d( nidx, idxice(1:nidx), ftr_ice_1d(1:nidx), ftr_ice(:,:,kl) ) 514 518 ! 515 519 ! SIMIP diagnostics 516 CALL tab_1d_2d( nidx, idxice(1:nidx), t_si_1d (1:nidx), t_si(:,:, jl))517 CALL tab_1d_2d( nidx, idxice(1:nidx), diag_fc_bo_1d(1:nidx), diag_fc_bo 518 CALL tab_1d_2d( nidx, idxice(1:nidx), diag_fc_su_1d(1:nidx), diag_fc_su 520 CALL tab_1d_2d( nidx, idxice(1:nidx), t_si_1d (1:nidx), t_si(:,:,kl) ) 521 CALL tab_1d_2d( nidx, idxice(1:nidx), diag_fc_bo_1d(1:nidx), diag_fc_bo ) 522 CALL tab_1d_2d( nidx, idxice(1:nidx), diag_fc_su_1d(1:nidx), diag_fc_su ) 519 523 ! extensive variables 520 CALL tab_1d_2d( nidx, idxice(1:nidx), v_i_1d (1:nidx), v_i (:,:,jl) ) 521 CALL tab_1d_2d( nidx, idxice(1:nidx), v_s_1d (1:nidx), v_s (:,:,jl) ) 522 CALL tab_1d_2d( nidx, idxice(1:nidx), smv_i_1d(1:nidx), smv_i(:,:,jl) ) 524 CALL tab_1d_2d( nidx, idxice(1:nidx), v_i_1d (1:nidx), v_i (:,:,kl) ) 525 CALL tab_1d_2d( nidx, idxice(1:nidx), v_s_1d (1:nidx), v_s (:,:,kl) ) 526 CALL tab_1d_2d( nidx, idxice(1:nidx), smv_i_1d(1:nidx), smv_i(:,:,kl) ) 527 ! 523 528 END SELECT 524 529 ! … … 538 543 !! ** input : Namelist namicether 539 544 !!------------------------------------------------------------------- 540 INTEGER :: ios ! Local integer output status for namelist read 545 INTEGER :: ios ! Local integer output status for namelist read 546 !! 541 547 NAMELIST/namicethd/ rn_kappa_i, nn_ice_thcon, ln_dqnsice, rn_cdsn, & 542 548 & ln_limdH, rn_betas, & … … 559 565 WRITE(numout,*) 'ice_thd_init : Ice Thermodynamics' 560 566 WRITE(numout,*) '~~~~~~~~~~~~~' 567 WRITE(numout,*)' Namelist namicethd' 561 568 WRITE(numout,*)' -- icethd_dif --' 562 569 WRITE(numout,*)' extinction radiation parameter in sea ice rn_kappa_i = ', rn_kappa_i … … 573 580 WRITE(numout,*)' -- icethd_lac --' 574 581 WRITE(numout,*)' activate ice growth in open-water (T) or not (F) ln_limdO = ', ln_limdO 575 WRITE(numout,*)' ice thick . for lateral accretionrn_hnewice = ', rn_hnewice582 WRITE(numout,*)' ice thickness for lateral accretion rn_hnewice = ', rn_hnewice 576 583 WRITE(numout,*)' Frazil ice thickness as a function of wind or not ln_frazil = ', ln_frazil 577 584 WRITE(numout,*)' Maximum proportion of frazil ice collecting at bottom rn_maxfrazb = ', rn_maxfrazb 578 WRITE(numout,*)' Thres old relative drift speed for collection of frazilrn_vfrazb = ', rn_vfrazb585 WRITE(numout,*)' Threshold relative drift speed for collection of frazil rn_vfrazb = ', rn_vfrazb 579 586 WRITE(numout,*)' Squeezing coefficient for collection of frazil rn_Cfrazb = ', rn_Cfrazb 580 587 WRITE(numout,*)' -- iceitd --' … … 588 595 IF(lwp) WRITE(numout,*) 589 596 SELECT CASE( nn_limflx ) ! LIM3 Multi-category heat flux formulation 590 CASE ( -1)597 CASE( -1 ) 591 598 IF(lwp) WRITE(numout,*) ' LIM3: use per-category fluxes (nn_limflx = -1) ' 592 IF( ln_cpl ) CALL ctl_stop( ' sbc_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' )593 CASE (0 )599 IF( ln_cpl ) CALL ctl_stop( 'ice_thd_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 600 CASE( 0 ) 594 601 IF(lwp) WRITE(numout,*) ' LIM3: use average per-category fluxes (nn_limflx = 0) ' 595 CASE (1 )602 CASE( 1 ) 596 603 IF(lwp) WRITE(numout,*) ' LIM3: use average then redistribute per-category fluxes (nn_limflx = 1) ' 597 IF( ln_cpl ) CALL ctl_stop( ' sbc_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' )598 CASE (2 )604 IF( ln_cpl ) CALL ctl_stop( 'ice_thd_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 605 CASE( 2 ) 599 606 IF(lwp) WRITE(numout,*) ' LIM3: Redistribute a single flux over categories (nn_limflx = 2) ' 600 IF( .NOT. ln_cpl ) CALL ctl_stop( ' sbc_init : the chosen nn_limflx for LIM3 in forced mode cannot be 2' )607 IF( .NOT. ln_cpl ) CALL ctl_stop( 'ice_thd_init : the chosen nn_limflx for LIM3 in forced mode cannot be 2' ) 601 608 CASE DEFAULT 602 CALL ctl_stop( ' sbcmod: LIM3 option, nn_limflx, should be between -1 and 2' )609 CALL ctl_stop( 'ice_thd_init: LIM3 option, nn_limflx, should be between -1 and 2' ) 603 610 END SELECT 604 611 ! -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_da.F90
r8422 r8486 4 4 !! LIM-3 sea-ice : computation of lateral melting in the ice 5 5 !!====================================================================== 6 !! History : 4.0 ! 2016-03 (C. Rousset)original code6 !! History : 4.0 ! 2016-03 (C. Rousset) original code 7 7 !!--------------------------------------------------------------------- 8 8 #if defined key_lim3 … … 10 10 !! 'key_lim3' LIM-3 sea-ice model 11 11 !!---------------------------------------------------------------------- 12 !! ice_thd_da : sea ice lateral melting12 !! ice_thd_da : sea ice lateral melting 13 13 !!---------------------------------------------------------------------- 14 14 USE par_oce ! ocean parameters 15 15 USE phycst ! physical constants (ocean directory) 16 USE ice ! LIMvariables17 USE ice1D ! thermodynamic sea-icevariables16 USE ice ! sea-ice: variables 17 USE ice1D ! sea-ice: thermodynamic 1D variables 18 18 ! 19 19 USE lib_mpp ! MPP library … … 23 23 PRIVATE 24 24 25 PUBLIC ice_thd_da ! called by icethd module25 PUBLIC ice_thd_da ! called by icethd.F90 26 26 27 27 !!---------------------------------------------------------------------- 28 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)28 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 29 29 !! $Id: icethd_da.F90 5123 2015-03-04 16:06:03Z clem $ 30 30 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 32 32 CONTAINS 33 33 34 !!gm even comment line of more than 130 character may cause compilation errors 35 !!gm ===>>> reformat the text 34 36 SUBROUTINE ice_thd_da 35 37 !!------------------------------------------------------------------- … … 106 108 REAL(wp), DIMENSION(jpij) :: zda_tot 107 109 !!--------------------------------------------------------------------- 108 109 !------------------------------------------------------------! 110 !------------------------------------------------------------! 110 ! 111 111 zastar = 1._wp / ( 1._wp - (rn_dmin / zdmax)**(1._wp/rn_beta) ) 112 112 DO ji = 1, nidx … … 136 136 ! new concentration 137 137 a_i_1d(ji) = a_i_1d(ji) - zda 138 138 139 139 ! ensure that ht_i = 0 where a_i = 0 140 140 IF( a_i_1d(ji) == 0._wp ) THEN … … 151 151 !! Default option Dummy Module No LIM-3 sea-ice model 152 152 !!---------------------------------------------------------------------- 153 CONTAINS154 SUBROUTINE ice_thd_da ! Empty routine155 END SUBROUTINE ice_thd_da156 153 #endif 154 157 155 !!====================================================================== 158 156 END MODULE icethd_da -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_dh.F90
r8422 r8486 12 12 #if defined key_lim3 13 13 !!---------------------------------------------------------------------- 14 !! 'key_lim3' LIM3 sea-ice model14 !! 'key_lim3' LIM3 sea-ice model 15 15 !!---------------------------------------------------------------------- 16 16 !! ice_thd_dh : vertical accr./abl. and lateral ablation of sea ice … … 36 36 37 37 !!---------------------------------------------------------------------- 38 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2010)38 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 39 39 !! $Id: icethd_dh.F90 8420 2017-08-08 12:18:46Z clem $ 40 40 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 66 66 !! Vancoppenolle et al.,2009, Ocean Modelling 67 67 !!------------------------------------------------------------------ 68 INTEGER :: ji , jk! dummy loop indices69 INTEGER :: iter 70 71 REAL(wp) :: ztmelts 68 INTEGER :: ji, jk ! dummy loop indices 69 INTEGER :: iter ! local integer 70 71 REAL(wp) :: ztmelts ! local scalar 72 72 REAL(wp) :: zdum 73 73 REAL(wp) :: zfracs ! fractionation coefficient for bottom salt entrapment … … 104 104 REAL(wp) :: zswitch_sal 105 105 106 ! Heat conservation 107 INTEGER :: num_iter_max 106 INTEGER :: num_iter_max ! Heat conservation 108 107 !!------------------------------------------------------------------ 109 108 110 109 ! Discriminate between varying salinity (nn_icesal=2) and prescribed cases (other values) 111 110 SELECT CASE( nn_icesal ) ! varying salinity or not 112 CASE( 1, 3 ) ; zswitch_sal = 0._wp ! prescribed salinity profile113 CASE( 2 ) ; zswitch_sal = 1._wp ! varying salinity profile111 CASE( 1, 3 ) ; zswitch_sal = 0._wp ! prescribed salinity profile 112 CASE( 2 ) ; zswitch_sal = 1._wp ! varying salinity profile 114 113 END SELECT 115 114 … … 127 126 h_i_old (ji,jk) = ht_i_1d(ji) * r1_nlay_i 128 127 eh_i_old(ji,jk) = e_i_1d(ji,jk) * h_i_old(ji,jk) 129 END DO130 END DO128 END DO 129 END DO 131 130 ! 132 131 !------------------------------------------------------------------------------! … … 142 141 END DO 143 142 144 !145 143 !------------------------------------------------------------------------------! 146 144 ! If snow temperature is above freezing point, then snow melts … … 163 161 ! 2) Computing layer thicknesses and enthalpies. ! 164 162 !------------------------------------------------------------! 165 !166 163 DO jk = 1, nlay_i 167 164 DO ji = 1, nidx … … 170 167 END DO 171 168 END DO 172 ! 169 173 170 !------------------------------------------------------------------------------| 174 171 ! 3) Surface ablation and sublimation | … … 389 386 END DO 390 387 391 ! 388 392 389 !------------------------------------------------------------------------------! 393 390 ! 4) Basal growth / melt ! … … 664 661 !! ** Purpose : Compute distribution of precip over the ice 665 662 !!-------------------------------------------------------------------------- 663 !!gm I think it can be usefull to set this as a FUNCTION, not a SUBROUTINE.... 666 664 SUBROUTINE ice_thd_snwblow_2d( pin, pout ) 667 665 REAL(wp), DIMENSION(:,:), INTENT(in ) :: pin ! previous fraction lead ( 1. - a_i_b ) … … 676 674 END SUBROUTINE ice_thd_snwblow_1d 677 675 678 679 676 #else 680 677 !!---------------------------------------------------------------------- 681 678 !! Default option NO LIM3 sea-ice model 682 679 !!---------------------------------------------------------------------- 683 CONTAINS684 SUBROUTINE ice_thd_dh ! Empty routine685 END SUBROUTINE ice_thd_dh686 680 #endif 687 681 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_dif.F90
r8422 r8486 18 18 USE par_oce ! ocean parameters 19 19 USE phycst ! physical constants (ocean directory) 20 USE ice ! LIM-3variables21 USE ice1D ! LIM-3: thermodynamics20 USE ice ! sea-ice: variables 21 USE ice1D ! sea-ice: thermodynamics 22 22 ! 23 23 USE in_out_manager ! I/O manager … … 31 31 32 32 !!---------------------------------------------------------------------- 33 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)33 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 34 34 !! $Id: icethd_dif.F90 8420 2017-08-08 12:18:46Z clem $ 35 35 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 67 67 !! of temperature 68 68 !! 69 !!70 69 !! ** Inputs / Ouputs : (global commons) 71 70 !! surface temperature : t_su_1d … … 75 74 !! profile of the ice/snow layers : z_i, z_s 76 75 !! total ice/snow thickness : ht_i_1d, ht_s_1d 77 !!78 !! ** External :79 !!80 !! ** References :81 !!82 !! ** History :83 !! (02-2003) Martin Vancoppenolle, Louvain-la-Neuve, Belgium84 !! (06-2005) Martin Vancoppenolle, 3d version85 !! (11-2006) Vectorized by Xavier Fettweis (UCL-ASTR)86 !! (04-2007) Energy conservation tested by M. Vancoppenolle87 76 !!------------------------------------------------------------------ 88 !! * Local variables89 77 INTEGER :: ji ! spatial loop index 90 78 INTEGER :: ii, ij ! temporary dummy loop index … … 796 784 END SUBROUTINE ice_thd_dif 797 785 786 798 787 SUBROUTINE ice_thd_enmelt 799 788 !!----------------------------------------------------------------------- … … 830 819 !! Dummy Module No LIM-3 sea-ice model 831 820 !!---------------------------------------------------------------------- 832 CONTAINS833 SUBROUTINE ice_thd_dif ! Empty routine834 END SUBROUTINE ice_thd_dif835 821 #endif 822 836 823 !!====================================================================== 837 824 END MODULE icethd_dif -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_ent.F90
r8424 r8486 15 15 #if defined key_lim3 16 16 !!---------------------------------------------------------------------- 17 !! 'key_lim3' LIM3 sea-ice model17 !! 'key_lim3' LIM3 sea-ice model 18 18 !!---------------------------------------------------------------------- 19 19 !! ice_thd_ent : ice redistribution of enthalpy … … 36 36 37 37 !!---------------------------------------------------------------------- 38 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)38 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 39 39 !! $Id: icethd_ent.F90 8420 2017-08-08 12:18:46Z clem $ 40 40 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 86 86 zeh_cum0(ji,jk0) = zeh_cum0(ji,jk0-1) + eh_i_old(ji,jk0-1) 87 87 zh_cum0 (ji,jk0) = zh_cum0 (ji,jk0-1) + h_i_old (ji,jk0-1) 88 END DO89 END DO88 END DO 89 END DO 90 90 91 91 !------------------------------------ … … 95 95 DO ji = 1, nidx 96 96 zhnew(ji) = SUM( h_i_old(ji,0:nlay_i+1) ) * r1_nlay_i 97 END DO97 END DO 98 98 99 99 ! new layers interfaces … … 102 102 DO ji = 1, nidx 103 103 zh_cum1(ji,jk1) = zh_cum1(ji,jk1-1) + zhnew(ji) 104 END DO105 END DO104 END DO 105 END DO 106 106 107 107 zeh_cum1(:,0:nlay_i) = 0._wp … … 115 115 & / ( zh_cum0(ji,jk0) - zh_cum0(ji,jk0-1) ) 116 116 ENDIF 117 END DO118 END DO119 END DO117 END DO 118 END DO 119 END DO 120 120 ! to ensure that total heat content is strictly conserved, set: 121 121 zeh_cum1(:,nlay_i) = zeh_cum0(:,nlay_i+2) … … 126 126 rswitch = MAX( 0._wp , SIGN( 1._wp , zhnew(ji) - epsi20 ) ) 127 127 qnew(ji,jk1) = rswitch * ( zeh_cum1(ji,jk1) - zeh_cum1(ji,jk1-1) ) / MAX( zhnew(ji), epsi20 ) 128 END DO129 END DO128 END DO 129 END DO 130 130 131 131 ! --- diag error on heat remapping --- ! … … 143 143 !! Default option NO LIM3 sea-ice model 144 144 !!---------------------------------------------------------------------- 145 CONTAINS146 SUBROUTINE ice_thd_ent ! Empty routine147 END SUBROUTINE ice_thd_ent148 145 #endif 149 146 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_lac.F90
r8426 r8486 11 11 #if defined key_lim3 12 12 !!---------------------------------------------------------------------- 13 !! 'key_lim3' LIM3 sea-ice model13 !! 'key_lim3' LIM3 sea-ice model 14 14 !!---------------------------------------------------------------------- 15 15 !! lim_lat_acr : lateral accretion of ice … … 20 20 USE sbc_oce , ONLY : sss_m 21 21 USE sbc_ice , ONLY : utau_ice, vtau_ice 22 USE ice1D ! LIMthermodynamics23 USE ice ! LIMvariables24 USE icetab ! LIM2D <==> 1D25 USE icectl ! LIMconservation26 USE icethd_ent 27 USE icevar 22 USE ice1D ! sea-ice: thermodynamics 23 USE ice ! sea-ice: variables 24 USE icetab ! sea-ice: 2D <==> 1D 25 USE icectl ! sea-ice: conservation 26 USE icethd_ent ! sea-ice: thermodynamics, enthalpy 27 USE icevar ! sea-ice: operations 28 28 ! 29 29 USE in_out_manager ! I/O manager … … 35 35 PRIVATE 36 36 37 PUBLIC ice_thd_lac! called by ice_thd38 39 !!---------------------------------------------------------------------- 40 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)37 PUBLIC ice_thd_lac ! called by ice_thd 38 39 !!---------------------------------------------------------------------- 40 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 41 41 !! $Id: icethd_lac.F90 8420 2017-08-08 12:18:46Z clem $ 42 42 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 133 133 134 134 ! Default new ice thickness 135 WHERE( qlead(:,:) < 0._wp ) ;hicol(:,:) = rn_hnewice136 ELSEWHERE ;hicol(:,:) = 0._wp135 WHERE( qlead(:,:) < 0._wp ) ; hicol(:,:) = rn_hnewice 136 ELSEWHERE ; hicol(:,:) = 0._wp 137 137 END WHERE 138 138 … … 486 486 !! Default option NO LIM3 sea-ice model 487 487 !!---------------------------------------------------------------------- 488 CONTAINS489 SUBROUTINE ice_thd_lac ! Empty routine490 END SUBROUTINE ice_thd_lac491 488 #endif 492 489 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_sal.F90
r8424 r8486 31 31 32 32 !!---------------------------------------------------------------------- 33 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)33 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 34 34 !! $Id: icethd_sal.F90 8420 2017-08-08 12:18:46Z clem $ 35 35 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 102 102 !------------------------------------------------------------------------------| 103 103 IF( nn_icesal == 3 ) CALL ice_var_salprof1d 104 105 104 ! 106 105 END SUBROUTINE ice_thd_sal … … 119 118 !!------------------------------------------------------------------- 120 119 INTEGER :: ios ! Local integer output status for namelist read 121 NAMELIST/namicesal/ ln_limdS, nn_icesal, rn_icesal, rn_sal_gd, rn_time_gd, & 122 & rn_sal_fl, rn_time_fl, rn_simax, rn_simin 120 !! 121 NAMELIST/namicesal/ ln_limdS , nn_icesal , rn_icesal, rn_sal_gd, rn_time_gd, & 122 & rn_sal_fl, rn_time_fl, rn_simax , rn_simin 123 123 !!------------------------------------------------------------------- 124 124 ! … … 126 126 READ ( numnam_ice_ref, namicesal, IOSTAT = ios, ERR = 901) 127 127 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicesal in reference namelist', lwp ) 128 128 ! 129 129 REWIND( numnam_ice_cfg ) ! Namelist namicesal in configuration namelist : Ice salinity 130 130 READ ( numnam_ice_cfg, namicesal, IOSTAT = ios, ERR = 902 ) … … 154 154 !!---------------------------------------------------------------------- 155 155 #endif 156 156 157 !!====================================================================== 157 158 END MODULE icethd_sal -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceupdate.F90
r8426 r8486 2 2 !!====================================================================== 3 3 !! *** MODULE iceupdate *** 4 !! 4 !! Sea-ice : computation of the flux at the sea ice/ocean interface 5 5 !!====================================================================== 6 6 !! History : - ! 2006-07 (M. Vancoppelle) LIM3 original code … … 27 27 USE phycst ! physical constants 28 28 USE dom_oce ! ocean domain 29 USE ice ! LIM sea-ice variables 30 USE sbc_ice , ONLY : emp_oce, qns_oce, qsr_oce, qemp_oce, emp_ice, qsr_ice, qemp_ice, qevap_ice, alb_ice, tn_ice, cldf_ice, & 29 USE ice ! sea-ice: variables 30 !!gm It should be probably better to pass these variable in argument of the routine, 31 !!gm rather than having this long list in USE. This will also highlight what is updated, and what is just use. 32 USE sbc_ice , ONLY : emp_oce, qns_oce, qsr_oce , qemp_oce , & 33 & emp_ice, qsr_ice, qemp_ice, qevap_ice, alb_ice, tn_ice, cldf_ice, & 31 34 & snwice_mass, snwice_mass_b, snwice_fmass 32 35 USE sbc_oce , ONLY : nn_fsbc, ln_ice_embd, sfx, fr_i, qsr_tot, qns, qsr, fmmflx, emp, taum, utau, vtau 36 !!gm end 33 37 USE sbccpl ! Surface boundary condition: coupled interface 34 38 USE icealb ! albedo parameters 35 39 USE traqsr ! add penetration of solar flux in the calculation of heat budget 36 40 USE domvvl ! Variable volume 37 USE icectl ! 38 USE bdy_oce , ONLY: ln_bdy41 USE icectl ! ??? 42 USE bdy_oce , ONLY : ln_bdy 39 43 ! 40 44 USE in_out_manager ! I/O manager … … 59 63 # include "vectopt_loop_substitute.h90" 60 64 !!---------------------------------------------------------------------- 61 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)65 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 62 66 !! $Id: iceupdate.F90 8411 2017-08-07 16:09:12Z clem $ 63 67 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 72 76 & sice_0(jpi,jpj) , vtau_oce(jpi,jpj) , tmod_io(jpi,jpj), STAT=ice_update_alloc) 73 77 ! 74 IF( lk_mpp ) CALL mpp_sum( ice_update_alloc )78 IF( lk_mpp ) CALL mpp_sum( ice_update_alloc ) 75 79 IF( ice_update_alloc /= 0 ) CALL ctl_warn('ice_update_alloc: failed to allocate arrays') 76 80 END FUNCTION ice_update_alloc … … 138 142 zqsr = zqsr - a_i_b(ji,jj,jl) * ( qsr_ice(ji,jj,jl) - ftr_ice(ji,jj,jl) ) 139 143 END DO 144 !!gm why not like almost everywhere else : 145 !!gm zqsr = qsr_tot(ji,jj) - SUM( a_i_b(ji,jj,:) * ( qsr_ice(ji,jj,:) - ftr_ice(ji,jj,:) ) 140 146 141 147 ! Total heat flux reaching the ocean = hfx_out (W.m-2) … … 170 176 ! mass flux from ice/ocean 171 177 wfx_ice(ji,jj) = wfx_bog(ji,jj) + wfx_bom(ji,jj) + wfx_sum(ji,jj) + wfx_sni(ji,jj) & 172 178 & + wfx_opw(ji,jj) + wfx_dyn(ji,jj) + wfx_res(ji,jj) + wfx_lam(ji,jj) 173 179 174 180 IF ( ln_pnd_fw ) wfx_ice(ji,jj) = wfx_ice(ji,jj) + wfx_pnd(ji,jj) … … 189 195 ! Mass of snow and ice per unit area 190 196 !---------------------------------------- 191 ! save mass from the previous ice time step 192 snwice_mass_b(ji,jj) = snwice_mass(ji,jj) 193 ! new mass per unit area 197 snwice_mass_b(ji,jj) = snwice_mass(ji,jj) ! save mass from the previous ice time step 198 ! ! new mass per unit area 194 199 snwice_mass (ji,jj) = tmask(ji,jj,1) * ( rhosn * vt_s(ji,jj) + rhoic * vt_i(ji,jj) ) 195 ! time evolution of snow+ice mass200 ! ! time evolution of snow+ice mass 196 201 snwice_fmass (ji,jj) = ( snwice_mass(ji,jj) - snwice_mass_b(ji,jj) ) * r1_rdtice 197 202 … … 209 214 !------------------------------------------------------------------------! 210 215 CALL ice_alb( t_su, ht_i, ht_s, a_ip_frac, h_ip, ln_pnd_rad, zalb_cs, zalb_os ) ! cloud-sky and overcast-sky ice albedos 211 212 alb_ice(:,:,:) = ( 1. - cldf_ice ) * zalb_cs(:,:,:) + cldf_ice * zalb_os(:,:,:) 213 214 ! conservation test 215 IF( ln_limdiachk .AND. .NOT. ln_bdy) CALL ice_cons_final( 'iceupdate' ) 216 217 ! control prints 216 ! 217 alb_ice(:,:,:) = ( 1._wp - cldf_ice ) * zalb_cs(:,:,:) + cldf_ice * zalb_os(:,:,:) 218 219 ! ! conservation test 220 IF( ln_limdiachk .AND. .NOT. ln_bdy) CALL ice_cons_final( 'iceupdate' ) 221 ! ! control prints 218 222 IF( ln_limctl ) CALL ice_prt( kt, iiceprt, jiceprt, 3, ' - Final state ice_update - ' ) 219 IF( ln_ctl )CALL ice_prt3D( 'iceupdate' )220 221 IF( nn_timing == 1 ) CALL timing_stop('ice_update_flx')222 223 IF( ln_ctl ) CALL ice_prt3D( 'iceupdate' ) 224 ! 225 IF( nn_timing == 1 ) CALL timing_stop('ice_update_flx') 226 ! 223 227 END SUBROUTINE ice_update_flx 224 228 225 229 226 SUBROUTINE ice_update_tau( kt 230 SUBROUTINE ice_update_tau( kt, pu_oce, pv_oce ) 227 231 !!------------------------------------------------------------------- 228 232 !! *** ROUTINE ice_update_tau *** … … 312 316 !! *** ROUTINE ice_update_init *** 313 317 !! 314 !! ** Purpose : Preparation of the file ice_evolu for the output of 315 !! the temporal evolution of key variables 318 !! ** Purpose : ??? 316 319 !! 317 !! ** input : Namelist namicedia318 320 !!------------------------------------------------------------------- 319 321 INTEGER :: ji, jj, jk ! dummy loop indices … … 322 324 ! 323 325 IF(lwp) WRITE(numout,*) 324 IF(lwp) WRITE(numout,*) 'ice_update_init : LIM-3 sea-ice - surface boundary condition'326 IF(lwp) WRITE(numout,*) 'ice_update_init : sea-ice ????' 325 327 IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~ ' 326 328 … … 328 330 IF( ice_update_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'ice_update_init : unable to allocate standard arrays' ) 329 331 ! 330 soce_0(:,:) = soce ! constant SSS and ice salinity used in levitating sea-ice case332 soce_0(:,:) = soce ! constant SSS and ice salinity used in levitating case 0 (i.e. virtual salt flux) 331 333 sice_0(:,:) = sice 332 ! ! decrease ocean & ice reference salinities in the Baltic Sea area 333 WHERE( 14._wp <= glamt(:,:) .AND. glamt(:,:) <= 32._wp .AND. & 334 WHERE( 14._wp <= glamt(:,:) .AND. glamt(:,:) <= 32._wp .AND. & ! reduced values in the Baltic Sea area 334 335 & 54._wp <= gphit(:,:) .AND. gphit(:,:) <= 66._wp ) 335 336 soce_0(:,:) = 4._wp … … 337 338 END WHERE 338 339 ! 339 IF( .NOT. ln_rstart ) THEN340 IF( .NOT.ln_rstart ) THEN ! set 340 341 ! 341 342 snwice_mass (:,:) = tmask(:,:,1) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:) ) ! snow+ice mass … … 350 351 IF( .NOT.ln_linssh ) THEN 351 352 DO jk = 1,jpkm1 ! adjust initial vertical scale factors 352 e3t_n(:,:,jk) = e3t_0(:,:,jk) *( 1._wp + sshn(:,:)*tmask(:,:,1)/(ht_0(:,:) + 1.0 - tmask(:,:,1)))353 e3t_b(:,:,jk) = e3t_0(:,:,jk) *( 1._wp + sshb(:,:)*tmask(:,:,1)/(ht_0(:,:) + 1.0 - tmask(:,:,1)))353 e3t_n(:,:,jk) = e3t_0(:,:,jk) * ( 1._wp + sshn(:,:)*tmask(:,:,1) / (ht_0(:,:) + 1._wp - tmask(:,:,1) ) ) 354 e3t_b(:,:,jk) = e3t_0(:,:,jk) * ( 1._wp + sshb(:,:)*tmask(:,:,1) / (ht_0(:,:) + 1._wp - tmask(:,:,1) ) ) 354 355 END DO 355 356 e3t_a(:,:,:) = e3t_b(:,:,:) 357 !!gm we are in no-restart case, so sshn=sshb ==>> faster calculation: 358 !! REAL(wp) :: ze3t ! local scalar 359 !! REAL(wp), DIMENSION(jpi,jpj) :: z2d ! workspace 360 !! 361 !! WHERE( ht_0(:,:) > 0 ) ; z2d(:,:) = 1._wp + sshn(:,:)*tmask(:,:,1) / ht_0(:,:) 362 !! ELSEWHERE ; z2d(:,:) = 1._wp 363 !! END WHERE 364 !! DO jk = 1,jpkm1 ! adjust initial vertical scale factors 365 !! ze3t = e3t_0(:,:,jk) * z2d(:,:) 366 !! e3t_n(:,:,jk) = ze3t 367 !! e3t_b(:,:,jk) = ze3t 368 !! e3t_a(:,:,jk) = ze3t 369 !! END DO 370 !!gm but since it is only done at the initialisation.... just the following can be acceptable: 371 ! DO jk = 1,jpkm1 ! adjust initial vertical scale factors 372 ! e3t_n(:,:,jk) = e3t_0(:,:,jk) * ( 1._wp + sshn(:,:)*tmask(:,:,1) / (ht_0(:,:) + 1._wp - tmask(:,:,1)) ) 373 ! END DO 374 ! e3t_b(:,:,:) = e3t_n(:,:,:) 375 ! e3t_a(:,:,:) = e3t_n(:,:,:) 376 !!gm end 356 377 ! Reconstruction of all vertical scale factors at now and before time-steps 357 378 ! ========================================================================= … … 377 398 gde3w_n(:,:,1) = gdept_n(:,:,1) - sshn(:,:) 378 399 DO jk = 2, jpk 379 gdept_n(:,:,jk) = gdept_n(:,:,jk-1) + e3w_n(:,:,jk )400 gdept_n(:,:,jk) = gdept_n(:,:,jk-1) + e3w_n(:,:,jk ) 380 401 gdepw_n(:,:,jk) = gdepw_n(:,:,jk-1) + e3t_n(:,:,jk-1) 381 gde3w_n(:,:,jk) = gdept_n(:,:,jk ) - sshn 402 gde3w_n(:,:,jk) = gdept_n(:,:,jk ) - sshn (:,:) 382 403 END DO 383 404 ENDIF … … 387 408 END SUBROUTINE ice_update_init 388 409 410 #else 411 !!---------------------------------------------------------------------- 412 !! Default option Dummy module NO LIM3 sea-ice model 413 !!---------------------------------------------------------------------- 389 414 #endif 390 415 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icevar.F90
r8426 r8486 31 31 !! History : - ! 2006-01 (M. Vancoppenolle) Original code 32 32 !! 3.4 ! 2011-02 (G. Madec) dynamical allocation 33 !! 3.5 ! 2012 (M. Vancoppenolle) add ice_var_itd 34 !! 3.6 ! 2014-01 (C. Rousset) add ice_var_zapsmall, rewrite ice_var_itd 33 35 !!---------------------------------------------------------------------- 34 36 #if defined key_lim3 35 37 !!---------------------------------------------------------------------- 36 38 !! 'key_lim3' LIM3 sea-ice model 39 !!---------------------------------------------------------------------- 40 !! ice_var_agg : integrate variables over layers and categories 41 !! ice_var_glo2eqv : transform from VGLO to VEQV 42 !! ice_var_eqv2glo : transform from VEQV to VGLO 43 !! ice_var_salprof : salinity profile in the ice 44 !! ice_var_bv : brine volume 45 !! ice_var_salprof1d : salinity profile in the ice 1D 46 !! ice_var_zapsmall : remove very small area and volume 47 !! ice_var_itd : convert 1-cat to multiple cat 37 48 !!---------------------------------------------------------------------- 38 49 USE par_oce ! ocean parameters … … 59 70 60 71 !!---------------------------------------------------------------------- 61 !! NEMO/ LIM3 3.5 , UCL - NEMO Consortium (2011)72 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 62 73 !! $Id: icevar.F90 8422 2017-08-08 13:58:05Z clem $ 63 74 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 69 80 !! *** ROUTINE ice_var_agg *** 70 81 !! 71 !! ** Purpose : aggregates ice-thickness-category variables to all-ice variables 72 !! i.e. it turns VGLO into VAGG 73 !! ** Method : 74 !! 75 !! ** Arguments : n = 1, at_i vt_i only 76 !! n = 2 everything 77 !! 78 !! note : you could add an argument when you need only at_i, vt_i 79 !! and when you need everything 80 !!------------------------------------------------------------------ 81 INTEGER, INTENT( in ) :: kn ! =1 at_i & vt only ; = what is needed 82 ! 83 INTEGER :: ji, jj, jk, jl ! dummy loop indices 84 !!------------------------------------------------------------------ 85 86 ! integrated values 87 vt_i (:,:) = SUM( v_i, dim=3 ) 88 vt_s (:,:) = SUM( v_s, dim=3 ) 89 at_i (:,:) = SUM( a_i, dim=3 ) 82 !! ** Purpose : aggregates ice-thickness-category variables to 83 !! all-ice variables, i.e. it turns VGLO into VAGG 84 !!------------------------------------------------------------------ 85 INTEGER, INTENT( in ) :: kn ! =1 state variables only 86 ! ! >1 state variables + others 87 ! 88 INTEGER :: ji, jj, jk, jl ! dummy loop indices 89 REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z1_at_i, z1_vt_i 90 !!------------------------------------------------------------------ 91 ! 92 ! ! integrated values 93 vt_i(:,:) = SUM( v_i(:,:,:) , dim=3 ) 94 vt_s(:,:) = SUM( v_s(:,:,:) , dim=3 ) 95 at_i(:,:) = SUM( a_i(:,:,:) , dim=3 ) 90 96 et_s(:,:) = SUM( SUM( e_s(:,:,:,:), dim=4 ), dim=3 ) 91 97 et_i(:,:) = SUM( SUM( e_i(:,:,:,:), dim=4 ), dim=3 ) 92 98 93 99 ! MV MP 2016 94 IF ( ln_pnd ) THEN 95 at_ip(:,:) = SUM( a_ip , dim=3 )96 vt_ip(:,:) = SUM( v_ip , dim=3 )100 IF ( ln_pnd ) THEN ! Melt pond 101 at_ip(:,:) = SUM( a_ip(:,:,:), dim=3 ) 102 vt_ip(:,:) = SUM( v_ip(:,:,:), dim=3 ) 97 103 ENDIF 98 104 ! END MP 2016 99 105 100 ! open water fraction 101 DO jj = 1, jpj 106 DO jj = 1, jpj ! open water fraction 102 107 DO ji = 1, jpi 103 108 ato_i(ji,jj) = MAX( 1._wp - at_i(ji,jj), 0._wp ) 104 109 END DO 105 110 END DO 111 !!gm I think this should do the work : 112 ! ato_i(:,:) = MAX( 1._wp - at_i(:,:), 0._wp ) 113 !!gm end 106 114 107 115 IF( kn > 1 ) THEN 108 109 ! mean ice/snow thickness 110 DO jj = 1, jpj 111 DO ji = 1, jpi 112 rswitch = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi10 ) ) 113 htm_i(ji,jj) = vt_i(ji,jj) / MAX( at_i(ji,jj) , epsi10 ) * rswitch 114 htm_s(ji,jj) = vt_s(ji,jj) / MAX( at_i(ji,jj) , epsi10 ) * rswitch 115 ENDDO 116 ENDDO 117 118 ! mean temperature (K), salinity and age 119 smt_i(:,:) = 0._wp 120 tm_i(:,:) = 0._wp 121 tm_su(:,:) = 0._wp 122 tm_si(:,:) = 0._wp 123 om_i (:,:) = 0._wp 124 DO jl = 1, jpl 125 126 DO jj = 1, jpj 127 DO ji = 1, jpi 128 rswitch = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi10 ) ) 129 tm_su(ji,jj) = tm_su(ji,jj) + rswitch * ( t_su(ji,jj,jl) - rt0 ) * a_i(ji,jj,jl) / MAX( at_i(ji,jj) , epsi10 ) 130 tm_si(ji,jj) = tm_si(ji,jj) + rswitch * ( t_si(ji,jj,jl) - rt0 ) * a_i(ji,jj,jl) / MAX( at_i(ji,jj) , epsi10 ) 131 om_i (ji,jj) = om_i (ji,jj) + rswitch * oa_i(ji,jj,jl) / MAX( at_i(ji,jj) , epsi06 ) 132 END DO 133 END DO 134 135 DO jk = 1, nlay_i 136 DO jj = 1, jpj 137 DO ji = 1, jpi 138 rswitch = MAX( 0._wp , SIGN( 1._wp , vt_i(ji,jj) - epsi10 ) ) 139 tm_i(ji,jj) = tm_i(ji,jj) + r1_nlay_i * rswitch * ( t_i(ji,jj,jk,jl) - rt0 ) * v_i(ji,jj,jl) & 140 & / MAX( vt_i(ji,jj) , epsi10 ) 141 smt_i(ji,jj) = smt_i(ji,jj) + r1_nlay_i * rswitch * s_i(ji,jj,jk,jl) * v_i(ji,jj,jl) & 142 & / MAX( vt_i(ji,jj) , epsi10 ) 143 END DO 144 END DO 145 END DO 146 END DO 147 tm_i = tm_i + rt0 148 tm_su = tm_su + rt0 149 tm_si = tm_si + rt0 150 ! 116 ! 117 ALLOCATE( z1_at_i(jpi,jpj) , z1_vt_i(jpi,jpj) ) 118 WHERE( at_i(:,:) > epsi10 ) ; z1_at_i(:,:) = 1._wp / at_i(:,:) 119 ELSEWHERE ; z1_at_i(:,:) = 0._wp 120 END WHERE 121 WHERE( vt_i(:,:) > epsi10 ) ; z1_vt_i(:,:) = 1._wp / vt_i(:,:) 122 ELSEWHERE ; z1_vt_i(:,:) = 0._wp 123 END WHERE 124 ! 125 ! ! mean ice/snow thickness 126 htm_i(:,:) = vt_i(:,:) * z1_at_i(:,:) 127 htm_s(:,:) = vt_s(:,:) * z1_at_i(:,:) 128 ! 129 ! ! mean temperature (K), salinity and age 130 tm_su(:,:) = SUM( t_su(:,:,:) * a_i(:,:,:) , dim=3 ) * z1_at_i(ji,jj) 131 tm_si(:,:) = SUM( t_si(:,:,:) * a_i(:,:,:) , dim=3 ) * z1_at_i(ji,jj) 132 om_i (:,:) = SUM( oa_i(:,:,:) , dim=3 ) * z1_at_i(ji,jj) 133 ! 134 tm_i (:,:) = r1_nlay_i * SUM( SUM( t_i(:,:,:,:) * v_i(:,:,:), dim=4 ) , dim=3 ) * z1_vt_i(:,:) 135 smt_i(:,:) = r1_nlay_i * SUM( SUM( s_i(:,:,:,:) * v_i(:,:,:), dim=4 ) , dim=3 ) * z1_vt_i(:,:) 136 ! 137 !!gm QUESTION 1 : why salinity is named smt_i and not just sm_i ? since the 4D field is named s_i. (NB for temp: tm_i, t_i) 138 ! 139 DEALLOCATE( z1_at_i , z1_vt_i ) 151 140 ENDIF 152 141 ! … … 158 147 !! *** ROUTINE ice_var_glo2eqv *** 159 148 !! 160 !! ** Purpose : computes equivalent variables as function of global variables161 !! i.e. it turns VGLO into VEQV149 !! ** Purpose : computes equivalent variables as function of 150 !! global variables, i.e. it turns VGLO into VEQV 162 151 !!------------------------------------------------------------------ 163 152 INTEGER :: ji, jj, jk, jl ! dummy loop indices 164 REAL(wp) :: ze_i, zaaa, zbbb, zccc, zdiscrim ! local scalars 165 REAL(wp) :: ztmelts, ze_s, zfac1, zfac2 ! - - 166 !!------------------------------------------------------------------ 153 REAL(wp) :: ze_i, z1_CpR, zdiscrim, zaaa, z1_2aaa ! local scalars 154 REAL(wp) :: ze_s, zL_Cp , ztmelts , zbbb, zccc ! - - 155 REAL(wp) :: zhmax, z1_zhmax, zsm_i, zcpMcpic, zt_i ! - - 156 REAL(wp) :: zlay_i, zlay_s ! - - 157 REAL(wp), DIMENSION(jpi,jpj,jpl) :: z1_a_i, z1_v_i 158 !!------------------------------------------------------------------ 159 160 !!gm Question 1: here use epsi20 , in ice_var_agg it is epsi10 which is used... why ?? 161 162 !!gm Question 2: It is possible to define existence of sea-ice in a common way between 163 !! ice area and ice volume ? 164 !! the idea is to be able to define one for all at the begining of this routine 165 !! a criteria for icy area (i.e. a_i > epsi20 and v_i > epsi20 ) 167 166 168 167 !------------------------------------------------------- 169 168 ! Ice thickness, snow thickness, ice salinity, ice age 170 169 !------------------------------------------------------- 171 DO jl = 1, jpl 172 DO jj = 1, jpj 173 DO ji = 1, jpi 174 rswitch = MAX( 0._wp , SIGN( 1._wp, a_i(ji,jj,jl) - epsi20 ) ) !0 if no ice and 1 if yes 175 ht_i(ji,jj,jl) = v_i (ji,jj,jl) / MAX( a_i(ji,jj,jl) , epsi20 ) * rswitch 176 END DO 177 END DO 178 END DO 179 ! Force the upper limit of ht_i to always be < hi_max (99 m). 180 DO jj = 1, jpj 181 DO ji = 1, jpi 182 rswitch = MAX( 0._wp , SIGN( 1._wp, ht_i(ji,jj,jpl) - epsi20 ) ) 183 ht_i(ji,jj,jpl) = MIN( ht_i(ji,jj,jpl) , hi_max(jpl) ) 184 a_i (ji,jj,jpl) = v_i(ji,jj,jpl) / MAX( ht_i(ji,jj,jpl) , epsi20 ) * rswitch 185 END DO 186 END DO 187 188 DO jl = 1, jpl 189 DO jj = 1, jpj 190 DO ji = 1, jpi 191 rswitch = MAX( 0._wp , SIGN( 1._wp, a_i(ji,jj,jl) - epsi20 ) ) !0 if no ice and 1 if yes 192 ht_s(ji,jj,jl) = v_s (ji,jj,jl) / MAX( a_i(ji,jj,jl) , epsi20 ) * rswitch 193 o_i(ji,jj,jl) = oa_i(ji,jj,jl) / MAX( a_i(ji,jj,jl) , epsi20 ) * rswitch 194 END DO 195 END DO 196 END DO 170 ! !--- inverse of the ice area 171 WHERE( a_i(:,:,:) > epsi20 ) ; z1_a_i(:,:,:) = 1._wp / a_i(:,:,:) 172 ELSEWHERE ; z1_a_i(:,:,:) = 0._wp 173 END WHERE 174 ! 175 ht_i(:,:,:) = v_i (:,:,:) * z1_a_i(:,:,:) !--- ice thickness 176 177 zhmax = hi_max(jpl) 178 z1_zhmax = 1._wp / hi_max(jpl) 179 WHERE( ht_i(:,:,jpl) > zhmax ) !--- bound ht_i by hi_max (i.e. 99 m) with associated update of ice area 180 ht_i (:,:,jpl) = zhmax 181 a_i (:,:,jpl) = v_i(:,:,jpl) * z1_zhmax 182 z1_a_i(:,:,jpl) = zhmax / v_i(:,:,jpl) ! NB: v_i always /=0 as ht_i > hi_max 183 END WHERE 184 185 ht_s(:,:,:) = v_s (:,:,:) * z1_a_i(:,:,:) !--- snow thickness 197 186 198 IF( nn_icesal == 2 )THEN 199 DO jl = 1, jpl 200 DO jj = 1, jpj 201 DO ji = 1, jpi 202 rswitch = MAX( 0._wp , SIGN( 1._wp, v_i(ji,jj,jl) - epsi20 ) ) !0 if no ice and 1 if yes 203 sm_i(ji,jj,jl) = smv_i(ji,jj,jl) / MAX( v_i(ji,jj,jl) , epsi20 ) * rswitch 204 ! ! bounding salinity 205 sm_i(ji,jj,jl) = MAX( sm_i(ji,jj,jl), rn_simin ) 206 END DO 207 END DO 208 END DO 187 o_i(:,:,:) = oa_i(:,:,:) * z1_a_i(:,:,:) !--- ice age 188 189 IF( nn_icesal == 2 )THEN !--- salinity (with a minimum value imposed everywhere) 190 WHERE( v_i(:,:,:) > epsi20 ) ; sm_i(:,:,:) = MAX( rn_simin , smv_i(:,:,:) / v_i(:,:,:) ) 191 ELSEWHERE ; sm_i(:,:,:) = rn_simin 192 END WHERE 209 193 ENDIF 210 194 … … 212 196 213 197 !------------------- 214 ! Ice temperature s198 ! Ice temperature [K] (with a minimum value (rt0 - 100.) imposed everywhere) 215 199 !------------------- 200 zlay_i = REAL( nlay_i , wp ) ! number of layers 201 zaaa = cpic ! Conversion q(S,T) -> T (second order equation) 202 z1_2aaa = 1._wp / 2._wp *zaaa 203 zcpMcpic = rcp - cpic 216 204 DO jl = 1, jpl 217 205 DO jk = 1, nlay_i 218 206 DO jj = 1, jpj 219 207 DO ji = 1, jpi 220 ! ! Energy of melting e(S,T) [J.m-3] 221 rswitch = MAX( 0.0 , SIGN( 1.0 , v_i(ji,jj,jl) - epsi20 ) ) ! rswitch = 0 if no ice and 1 if yes 222 ze_i = rswitch * e_i(ji,jj,jk,jl) / MAX( v_i(ji,jj,jl) , epsi20 ) * REAL(nlay_i,wp) 223 ztmelts = -tmut * s_i(ji,jj,jk,jl) + rt0 ! Ice layer melt temperature 224 ! 225 zaaa = cpic ! Conversion q(S,T) -> T (second order equation) 226 zbbb = ( rcp - cpic ) * ( ztmelts - rt0 ) + ze_i * r1_rhoic - lfus 227 zccc = lfus * (ztmelts-rt0) 228 zdiscrim = SQRT( MAX(zbbb*zbbb - 4._wp*zaaa*zccc , 0._wp) ) 229 t_i(ji,jj,jk,jl) = rt0 + rswitch *( - zbbb - zdiscrim ) / ( 2.0 *zaaa ) 230 t_i(ji,jj,jk,jl) = MIN( ztmelts, MAX( rt0 - 100._wp, t_i(ji,jj,jk,jl) ) ) ! -100 < t_i < ztmelts 208 IF ( v_i(ji,jj,jl) > epsi20 ) THEN !--- icy area 209 ! 210 ze_i = e_i(ji,jj,jk,jl) / v_i(ji,jj,jl) * zlay_i ! Energy of melting e(S,T) [J.m-3] 211 ztmelts = - s_i(ji,jj,jk,jl) * tmut ! Ice layer melt temperature [C] 212 ! 213 zbbb = zcpMcpic * ztmelts + ze_i * r1_rhoic - lfus 214 zccc = lfus * ztmelts 215 zdiscrim = SQRT( MAX( zbbb*zbbb - 4._wp*zaaa*zccc , 0._wp) ) 216 zt_i = - ( zbbb + zdiscrim ) * z1_2aaa ! [C] 217 t_i(ji,jj,jk,jl) = MAX( -100._wp , MIN( zt_i , ztmelts ) ) + rt0 ! [K] with bounds: -100 < zt_i < ztmelts 218 ! 219 ELSE !--- no ice 220 t_i(ji,jj,jk,jl) = rt0 - 100._wp ! impose 173.15 K (i.e. -100 C) 221 !!clem: I think we should impose rt0 instead 222 ENDIF 231 223 END DO 232 224 END DO … … 235 227 236 228 !-------------------- 237 ! Snow temperature s229 ! Snow temperature [K] (with a minimum value (rt0 - 100.) imposed everywhere) 238 230 !-------------------- 239 zfac1 = 1._wp / ( rhosn * cpic ) 240 zfac2 = lfus / cpic 241 DO jl = 1, jpl 242 DO jk = 1, nlay_s 243 DO jj = 1, jpj 244 DO ji = 1, jpi 245 !Energy of melting q(S,T) [J.m-3] 246 rswitch = MAX( 0._wp , SIGN( 1._wp , v_s(ji,jj,jl) - epsi20 ) ) ! rswitch = 0 if no ice and 1 if yes 247 ze_s = rswitch * e_s(ji,jj,jk,jl) / MAX( v_s(ji,jj,jl) , epsi20 ) * REAL(nlay_s,wp) 248 ! 249 t_s(ji,jj,jk,jl) = rt0 + rswitch * ( - zfac1 * ze_s + zfac2 ) 250 t_s(ji,jj,jk,jl) = MIN( rt0, MAX( rt0 - 100._wp , t_s(ji,jj,jk,jl) ) ) ! -100 < t_s < rt0 251 END DO 252 END DO 253 END DO 231 z1_CpR = 1._wp / ( cpic * rhosn ) 232 zL_Cp = lfus / cpic 233 zlay_s = REAL( nlay_s , wp ) 234 DO jk = 1, nlay_s 235 WHERE( v_s(:,:,:) > epsi20 ) !--- icy area 236 t_s(:,:,jk,:) = MAX( -100._wp , MIN( - z1_CpR * ( e_s(:,:,jk,:)/v_s(:,:,:)*zlay_s ) + zL_Cp , 0._wp ) ) + rt0 237 ELSEWHERE !--- no ice 238 t_s(:,:,jk,:) = rt0 - 100._wp ! impose 173.15 K (i.e. -100 C) 239 END WHERE 254 240 END DO 241 !!gm perhaps better like this (?) : (if this compile, yes! one test instead of nlay_s tests) 242 ! WHERE( v_s(:,:,:) > epsi20 ) !--- icy area 243 ! DO jk = 1, nlay_s 244 ! t_s(:,:,jk,:) = MAX( -100._wp , MIN( - z1_CpR * ( e_s(:,:,jk,:)/v_s(:,:,:)*zlay_s ) + zL_Cp , 0._wp ) ) + rt0 245 ! END DO 246 ! ELSEWHERE !--- no ice 247 ! DO jk = 1, nlay_s 248 ! t_s(:,:,jk,:) = rt0 - 100._wp ! impose 173.15 K (i.e. -100 C) 249 ! END DO 250 ! END WHERE 251 !!gm end better ? 255 252 256 253 ! integrated values … … 259 256 at_i (:,:) = SUM( a_i, dim=3 ) 260 257 261 262 258 ! MV MP 2016 259 ! probably should resum for melt ponds ??? 263 260 264 261 ! … … 270 267 !! *** ROUTINE ice_var_eqv2glo *** 271 268 !! 272 !! ** Purpose : computes global variables as function of equivalent variables 273 !! i.e. it turns VEQV into VGLO 274 !! ** Method : 275 !! 276 !! ** History : (01-2006) Martin Vancoppenolle, UCL-ASTR 277 !!------------------------------------------------------------------ 278 ! 279 v_i(:,:,:) = ht_i(:,:,:) * a_i(:,:,:) 280 v_s(:,:,:) = ht_s(:,:,:) * a_i(:,:,:) 269 !! ** Purpose : computes global variables as function of 270 !! equivalent variables, i.e. it turns VEQV into VGLO 271 !!------------------------------------------------------------------ 272 ! 273 v_i (:,:,:) = ht_i(:,:,:) * a_i(:,:,:) 274 v_s (:,:,:) = ht_s(:,:,:) * a_i(:,:,:) 281 275 smv_i(:,:,:) = sm_i(:,:,:) * v_i(:,:,:) 282 276 ! … … 300 294 !!------------------------------------------------------------------ 301 295 INTEGER :: ji, jj, jk, jl ! dummy loop index 302 REAL(wp) :: z fac0, zfac1, zsal303 REAL(wp) :: z swi0, zswi01, zargtemp , zs_zero304 REAL(wp), DIMENSION(jpi,jpj,jpl) :: z_slope_s, zalpha296 REAL(wp) :: zsal, z1_dS 297 REAL(wp) :: zargtemp , zs0, zs 298 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: z_slope_s, zalpha ! case 2 only 305 299 REAL(wp), PARAMETER :: zsi0 = 3.5_wp 306 300 REAL(wp), PARAMETER :: zsi1 = 4.5_wp 307 301 !!------------------------------------------------------------------ 308 302 309 !--------------------------------------- 310 ! Vertically constant, constant in time 311 !--------------------------------------- 312 IF( nn_icesal == 1 ) THEN 303 !!gm much much more secure to defined when reading nn_icesal in the namelist integers =1, 2, 3 with explicit names 304 !! for example np_Scst_noProfile = 1 ; np_Svar_linProfile = 2 ; np_Scst_fixProfile 305 306 !!gm Question: Remove the option 3 ? How many years since it last use ? 307 308 SELECT CASE ( nn_icesal ) 309 ! 310 ! !---------------------------------------! 311 CASE( 1 ) ! constant salinity in time and space ! 312 ! !---------------------------------------! 313 313 s_i (:,:,:,:) = rn_icesal 314 314 sm_i(:,:,:) = rn_icesal 315 ENDIF316 317 !-----------------------------------318 ! Salinity profile, varying in time319 !-----------------------------------320 IF( nn_icesal == 2 ) THEN315 ! 316 ! !---------------------------------------------! 317 CASE( 2 ) ! time varying salinity with linear profile ! 318 ! !---------------------------------------------! 319 ! 320 ALLOCATE( z_slope_s(jpi,jpj,jpl) , zalpha(jpi,jpj,jpl) ) 321 321 ! 322 322 DO jk = 1, nlay_i 323 323 s_i(:,:,jk,:) = sm_i(:,:,:) 324 324 END DO 325 ! 326 DO jl = 1, jpl ! Slope of the linear profile 327 DO jj = 1, jpj 328 DO ji = 1, jpi 329 rswitch = MAX( 0._wp , SIGN( 1._wp , ht_i(ji,jj,jl) - epsi20 ) ) 330 z_slope_s(ji,jj,jl) = rswitch * 2._wp * sm_i(ji,jj,jl) / MAX( epsi20 , ht_i(ji,jj,jl) ) 331 END DO 332 END DO 333 END DO 334 ! 335 zfac0 = 1._wp / ( zsi0 - zsi1 ) ! Weighting factor between zs_zero and zs_inf 336 zfac1 = zsi1 / ( zsi1 - zsi0 ) 337 ! 338 zalpha(:,:,:) = 0._wp 325 ! ! Slope of the linear profile 326 WHERE( ht_i(:,:,:) > epsi20 ) ; z_slope_s(:,:,:) = 2._wp * sm_i(:,:,:) / ht_i(:,:,:) 327 ELSEWHERE ; z_slope_s(:,:,:) = 0._wp 328 END WHERE 329 ! 330 z1_dS = 1._wp / ( zsi1 - zsi0 ) 339 331 DO jl = 1, jpl 340 332 DO jj = 1, jpj 341 333 DO ji = 1, jpi 342 ! zswi0 = 1 if sm_i le zsi0 and 0 otherwise 343 zswi0 = MAX( 0._wp , SIGN( 1._wp , zsi0 - sm_i(ji,jj,jl) ) ) 344 ! zswi01 = 1 if sm_i is between zsi0 and zsi1 and 0 othws 345 zswi01 = ( 1._wp - zswi0 ) * MAX( 0._wp , SIGN( 1._wp , zsi1 - sm_i(ji,jj,jl) ) ) 346 ! If 2.sm_i GE sss_m then rswitch = 1 347 ! this is to force a constant salinity profile in the Baltic Sea 348 rswitch = MAX( 0._wp , SIGN( 1._wp , 2._wp * sm_i(ji,jj,jl) - sss_m(ji,jj) ) ) 349 zalpha(ji,jj,jl) = zswi0 + zswi01 * ( sm_i(ji,jj,jl) * zfac0 + zfac1 ) 350 zalpha(ji,jj,jl) = zalpha(ji,jj,jl) * ( 1._wp - rswitch ) 334 zalpha(ji,jj,jl) = MAX( 0._wp , MIN( ( zsi1 - sm_i(ji,jj,jl) ) * z1_dS , 1._wp ) ) 335 ! ! force a constant profile when SSS too low (Baltic Sea) 336 IF( 2._wp * sm_i(ji,jj,jl) >= sss_m(ji,jj) ) zalpha(ji,jj,jl) = 0._wp 351 337 END DO 352 338 END DO … … 358 344 DO jj = 1, jpj 359 345 DO ji = 1, jpi 360 ! ! linear profile with 0 at the surface 361 zs_zero = z_slope_s(ji,jj,jl) * ( REAL(jk,wp) - 0.5_wp ) * ht_i(ji,jj,jl) * r1_nlay_i 362 ! ! weighting the profile 363 s_i(ji,jj,jk,jl) = zalpha(ji,jj,jl) * zs_zero + ( 1._wp - zalpha(ji,jj,jl) ) * sm_i(ji,jj,jl) 364 ! ! bounding salinity 365 s_i(ji,jj,jk,jl) = MIN( rn_simax, MAX( s_i(ji,jj,jk,jl), rn_simin ) ) 346 ! ! linear profile with 0 surface value 347 zs0 = z_slope_s(ji,jj,jl) * ( REAL(jk,wp) - 0.5_wp ) * ht_i(ji,jj,jl) * r1_nlay_i 348 zs = zalpha(ji,jj,jl) * zs0 + ( 1._wp - zalpha(ji,jj,jl) ) * sm_i(ji,jj,jl) ! weighting the profile 349 s_i(ji,jj,jk,jl) = MIN( rn_simax, MAX( zs, rn_simin ) ) 366 350 END DO 367 351 END DO … … 369 353 END DO 370 354 ! 371 ENDIF ! nn_icesal 372 373 !------------------------------------------------------- 374 ! Vertically varying salinity profile, constant in time 375 !------------------------------------------------------- 376 377 IF( nn_icesal == 3 ) THEN ! Schwarzacher (1959) multiyear salinity profile (mean = 2.30) 355 DEALLOCATE( z_slope_s , zalpha ) 356 ! 357 ! !-------------------------------------------! 358 CASE( 3 ) ! constant salinity with a fix profile ! (Schwarzacher (1959) multiyear salinity profile 359 ! !-------------------------------------------! (mean = 2.30) 378 360 ! 379 361 sm_i(:,:,:) = 2.30_wp 362 !!gm Remark: if we keep the case 3, then compute an store one for all time-step 363 !! a array S_prof(1:nlay_i) containing the calculation and just do: 364 ! DO jk = 1, nlay_i 365 ! s_i(:,:,jk,:) = S_prof(jk) 366 ! END DO 367 !!gm end 380 368 ! 381 369 DO jl = 1, jpl 382 370 DO jk = 1, nlay_i 383 371 zargtemp = ( REAL(jk,wp) - 0.5_wp ) * r1_nlay_i 384 zsal = 1.6_wp * ( 1._wp - COS( rpi * zargtemp**(0.407_wp/(0.573_wp+zargtemp)) ) ) 385 s_i(:,:,jk,jl) = zsal 386 END DO 387 END DO 388 ! 389 ENDIF ! nn_icesal 372 s_i(:,:,jk,jl) = 1.6_wp * ( 1._wp - COS( rpi * zargtemp**(0.407_wp/(0.573_wp+zargtemp)) ) ) 373 END DO 374 END DO 375 ! 376 END SELECT 390 377 ! 391 378 END SUBROUTINE ice_var_salprof … … 405 392 !!------------------------------------------------------------------ 406 393 ! 407 bvm_i(:,:) = 0._wp 394 !!gm I prefere to use WHERE / ELSEWHERE to set it to zero only where needed <<<=== to be done 395 !! instead of setting everything to zero as just below 408 396 bv_i (:,:,:) = 0._wp 409 397 DO jl = 1, jpl 410 398 DO jk = 1, nlay_i 411 DO jj = 1, jpj 412 DO ji = 1, jpi 413 rswitch = ( 1._wp - MAX( 0._wp , SIGN( 1._wp , (t_i(ji,jj,jk,jl) - rt0) + epsi10 ) ) ) 414 bv_i(ji,jj,jl) = bv_i(ji,jj,jl) - rswitch * tmut * s_i(ji,jj,jk,jl) * r1_nlay_i & 415 & / MIN( t_i(ji,jj,jk,jl) - rt0, - epsi10 ) 416 END DO 417 END DO 418 END DO 419 420 DO jj = 1, jpj 421 DO ji = 1, jpi 422 rswitch = MAX( 0._wp , SIGN( 1._wp , vt_i(ji,jj) - epsi10 ) ) 423 bvm_i(ji,jj) = bvm_i(ji,jj) + rswitch * bv_i(ji,jj,jl) * v_i(ji,jj,jl) / MAX( vt_i(ji,jj), epsi10 ) 424 END DO 399 WHERE( t_i(:,:,jk,jl) < rt0 - epsi10 ) 400 bv_i(:,:,jl) = bv_i(:,:,jl) - tmut * s_i(:,:,jk,jl) * r1_nlay_i / ( t_i(:,:,jk,jl) - rt0 ) 401 END WHERE 425 402 END DO 426 403 END DO 427 ! 404 WHERE( vt_i(:,:) > epsi20 ) bvm_i(:,:) = SUM( bv_i(:,:,:) * v_i(:,:,:) , dim=3 ) / vt_i(:,:) 405 ELSEWHERE bvm_i(:,:) = 0._wp 406 END WHERE 407 ! 428 408 END SUBROUTINE ice_var_bv 429 409 … … 437 417 !!------------------------------------------------------------------- 438 418 INTEGER :: ji, jk ! dummy loop indices 439 REAL(wp) :: z fac0, zfac1, zargtemp, zsal! local scalars440 REAL(wp) :: zalpha, zs wi0, zswi01, zs_zero! - -441 ! 442 REAL(wp), DIMENSION(jpij) :: z_slope_s419 REAL(wp) :: zargtemp, zsal, z1_dS ! local scalars 420 REAL(wp) :: zalpha, zs, zs0 ! - - 421 ! 422 REAL(wp), ALLOCATABLE, DIMENSION(:) :: z_slope_s ! 443 423 REAL(wp), PARAMETER :: zsi0 = 3.5_wp 444 424 REAL(wp), PARAMETER :: zsi1 = 4.5_wp 445 425 !!--------------------------------------------------------------------- 446 447 !--------------------------------------- 448 ! Vertically constant, constant in time 449 !--------------------------------------- 450 IF( nn_icesal == 1 ) s_i_1d(:,:) = rn_icesal 451 452 !------------------------------------------------------ 453 ! Vertically varying salinity profile, varying in time 454 !------------------------------------------------------ 455 456 IF( nn_icesal == 2 ) THEN 457 ! 458 DO ji = 1, nidx ! Slope of the linear profile zs_zero 426 ! 427 SELECT CASE ( nn_icesal ) 428 ! 429 ! !---------------------------------------! 430 CASE( 1 ) ! constant salinity in time and space ! 431 ! !---------------------------------------! 432 s_i_1d(:,:) = rn_icesal 433 ! 434 ! !---------------------------------------------! 435 CASE( 2 ) ! time varying salinity with linear profile ! 436 ! !---------------------------------------------! 437 ! 438 ALLOCATE( z_slope_s(jpij) ) 439 ! 440 DO ji = 1, nidx ! Slope of the linear profile 459 441 rswitch = MAX( 0._wp , SIGN( 1._wp , ht_i_1d(ji) - epsi20 ) ) 460 442 z_slope_s(ji) = rswitch * 2._wp * sm_i_1d(ji) / MAX( epsi20 , ht_i_1d(ji) ) 461 443 END DO 462 444 463 ! Weighting factor between zs_zero and zs_inf 464 !--------------------------------------------- 465 zfac0 = 1._wp / ( zsi0 - zsi1 ) 466 zfac1 = zsi1 / ( zsi1 - zsi0 ) 445 z1_dS = 1._wp / ( zsi1 - zsi0 ) 467 446 DO jk = 1, nlay_i 468 447 DO ji = 1, nidx 469 ! zswi0 = 1 if sm_i le zsi0 and 0 otherwise 470 zswi0 = MAX( 0._wp , SIGN( 1._wp , zsi0 - sm_i_1d(ji) ) ) 471 ! zswi01 = 1 if sm_i is between zsi0 and zsi1 and 0 othws 472 zswi01 = ( 1._wp - zswi0 ) * MAX( 0._wp , SIGN( 1._wp , zsi1 - sm_i_1d(ji) ) ) 473 ! if 2.sm_i GE sss_m then rswitch = 1 474 ! this is to force a constant salinity profile in the Baltic Sea 475 rswitch = MAX( 0._wp , SIGN( 1._wp , 2._wp * sm_i_1d(ji) - sss_1d(ji) ) ) 448 zalpha = MAX( 0._wp , MIN( ( zsi1 - sm_i_1d(ji) ) * z1_dS , 1._wp ) ) 449 IF( 2._wp * sm_i_1d(ji) >= sss_1d(ji) ) zalpha = 0._wp ! cst profile when SSS too low (Baltic Sea) 476 450 ! 477 zalpha = ( zswi0 + zswi01 * ( sm_i_1d(ji) * zfac0 + zfac1 ) ) * ( 1._wp - rswitch ) 478 ! 479 zs_zero = z_slope_s(ji) * ( REAL(jk,wp) - 0.5_wp ) * ht_i_1d(ji) * r1_nlay_i 480 ! weighting the profile 481 s_i_1d(ji,jk) = zalpha * zs_zero + ( 1._wp - zalpha ) * sm_i_1d(ji) 482 ! bounding salinity 483 s_i_1d(ji,jk) = MIN( rn_simax, MAX( s_i_1d(ji,jk), rn_simin ) ) 484 END DO 485 END DO 486 487 ENDIF 488 489 !------------------------------------------------------- 490 ! Vertically varying salinity profile, constant in time 491 !------------------------------------------------------- 492 493 IF( nn_icesal == 3 ) THEN ! Schwarzacher (1959) multiyear salinity profile (mean = 2.30) 451 zs0 = z_slope_s(ji) * ( REAL(jk,wp) - 0.5_wp ) * ht_i_1d(ji) * r1_nlay_i ! linear profile with 0 surface value 452 zs = zalpha * zs0 + ( 1._wp - zalpha ) * sm_i_1d(ji) ! weighting the profile 453 s_i_1d(ji,jk) = MIN( rn_simax , MAX( zs , rn_simin ) ) ! bounding salinity 454 END DO 455 END DO 456 ! 457 DEALLOCATE( z_slope_s ) 458 459 ! !-------------------------------------------! 460 CASE( 3 ) ! constant salinity with a fix profile ! (Schwarzacher (1959) multiyear salinity profile 461 ! !-------------------------------------------! (mean = 2.30) 494 462 ! 495 463 sm_i_1d(:) = 2.30_wp 496 464 ! 465 !!gm cf remark in ice_var_salprof routine, CASE( 3 ) 497 466 DO jk = 1, nlay_i 498 467 zargtemp = ( REAL(jk,wp) - 0.5_wp ) * r1_nlay_i … … 503 472 END DO 504 473 ! 505 END IF474 END SELECT 506 475 ! 507 476 END SUBROUTINE ice_var_salprof1d 477 508 478 509 479 SUBROUTINE ice_var_zapsmall … … 512 482 !! 513 483 !! ** Purpose : Remove too small sea ice areas and correct fluxes 514 !!515 !! history : LIM3.5 - 01-2014 (C. Rousset) original code516 484 !!------------------------------------------------------------------- 517 485 INTEGER :: ji, jj, jl, jk ! dummy loop indices 518 486 REAL(wp) :: zsal, zvi, zvs, zei, zes, zvp 519 487 !!------------------------------------------------------------------- 520 DO jl = 1, jpl 521 488 ! 489 DO jl = 1, jpl !== loop over the categories ==! 490 ! 522 491 !----------------------------------------------------------------- 523 492 ! Zap ice energy and use ocean heat to melt ice … … 526 495 DO jj = 1 , jpj 527 496 DO ji = 1 , jpi 497 !!gm I think we can do better/faster : to be discussed 528 498 rswitch = MAX( 0._wp , SIGN( 1._wp, a_i(ji,jj,jl) - epsi10 ) ) 529 499 rswitch = MAX( 0._wp , SIGN( 1._wp, v_i(ji,jj,jl) - epsi10 ) ) * rswitch … … 588 558 589 559 ! to be sure that at_i is the sum of a_i(jl) 590 at_i (:,:) = 0._wp 591 DO jl = 1, jpl 560 at_i (:,:) = a_i(:,:,1) 561 vt_i (:,:) = v_i(:,:,1) 562 DO jl = 2, jpl 592 563 at_i(:,:) = at_i(:,:) + a_i(:,:,jl) 564 vt_i(:,:) = vt_i(:,:) + v_i(:,:,jl) 593 565 END DO 594 566 595 ! open water = 1 if at_i=0 567 ! open water = 1 if at_i=0 (no re-calculation of ato_i here) 596 568 DO jj = 1, jpj 597 569 DO ji = 1, jpi … … 600 572 END DO 601 573 END DO 602 603 574 ! 604 575 END SUBROUTINE ice_var_zapsmall 576 605 577 606 578 SUBROUTINE ice_var_itd( zhti, zhts, zai, zht_i, zht_s, za_i ) … … 633 605 !! 634 606 !! (Example of application: BDY forcings when input are cell averaged) 635 !!636 607 !!------------------------------------------------------------------- 637 !! History : LIM3.5 - 2012 (M. Vancoppenolle) Original code638 !! 2014 (C. Rousset) Rewriting639 !!-------------------------------------------------------------------640 !! Local variables641 608 INTEGER :: ji, jk, jl ! dummy loop indices 642 609 INTEGER :: ijpij, i_fill, jl0 … … 645 612 REAL(wp), DIMENSION(:,:), INTENT(inout) :: zht_i, zht_s, za_i ! output ice/snow variables 646 613 INTEGER , DIMENSION(4) :: itest 647 614 !!------------------------------------------------------------------- 615 648 616 !-------------------------------------------------------------------- 649 617 ! initialisation of variables 650 618 !-------------------------------------------------------------------- 651 ijpij = SIZE( zhti,1)619 ijpij = SIZE( zhti , 1 ) 652 620 zht_i(1:ijpij,1:jpl) = 0._wp 653 621 zht_s(1:ijpij,1:jpl) = 0._wp … … 766 734 zht_s(ji,jl) = MAX( 0._wp, zht_s(ji,jl) - zdh * rhoic * r1_rhosn ) 767 735 ENDIF 768 END DO769 END DO736 END DO 737 END DO 770 738 ! 771 739 END SUBROUTINE ice_var_itd 772 773 740 774 741 #else … … 776 743 !! Default option Dummy module NO LIM3 sea-ice model 777 744 !!---------------------------------------------------------------------- 778 CONTAINS779 SUBROUTINE ice_var_itd780 END SUBROUTINE ice_var_itd781 745 #endif 782 746 -
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icewri.F90
r8424 r8486 8 8 !! 'key_lim3' LIM3 sea-ice model 9 9 !!---------------------------------------------------------------------- 10 !! ice_wri : write of the diagnostics variables in ouput file10 !! ice_wri : write of the diagnostics variables in ouput file 11 11 !! ice_wri_state : write for initial state or/and abandon 12 12 !!---------------------------------------------------------------------- 13 USE ioipsl 14 USE dianam ! build name of file (routine) 15 USE phycst 16 USE dom_oce 17 USE sbc_oce 18 USE sbc_ice ! Surface boundary condition: ice fields 19 USE ice 20 USE icevar 13 USE dianam ! build name of file (routine) 14 USE phycst ! physical constant 15 USE dom_oce ! domain: ocean 16 USE sbc_oce ! surf. boundary cond.: ocean 17 USE sbc_ice ! Surface boundary condition: ice fields 18 USE ice ! sea-ice: variables 19 USE icevar ! sea-ice: operations 21 20 ! 22 USE in_out_manager 23 USE lbclnk 24 USE lib_mpp ! MPP library 25 USE iom 26 USE timing ! Timing 27 USE lib_fortran ! Fortran utilities 21 USE ioipsl ! 22 USE in_out_manager ! 23 USE lbclnk ! 24 USE lib_mpp ! MPP library 25 USE iom ! 26 USE timing ! Timing 27 USE lib_fortran ! Fortran utilities 28 28 29 29 IMPLICIT NONE 30 30 PRIVATE 31 31 32 PUBLIC ice_wri ! routine called by lim_step.F9032 PUBLIC ice_wri ! called by ice_stp 33 33 PUBLIC ice_wri_state ! called by dia_wri_state 34 34 35 35 !!---------------------------------------------------------------------- 36 !! NEMO/ LIM3 4.0 , UCL - NEMO Consortium (2011)36 !! NEMO/ICE 4.0 , NEMO Consortium (2017) 37 37 !! $Id: icewri.F90 8409 2017-08-07 15:29:21Z clem $ 38 38 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) … … 55 55 REAL(wp) :: z2da, z2db, ztmp, zrho1, zrho2, zmiss_val 56 56 REAL(wp) :: zs12, zshear 57 REAL(wp), DIMENSION(jpi,jpj) :: z2d, zswi, zmiss ! 2D workspace 58 REAL(wp), DIMENSION(jpi,jpj) :: zfb ! ice freeboard 59 REAL(wp), DIMENSION(jpi,jpj) :: zamask, zamask15 ! 15% concentration mask 60 REAL(wp), DIMENSION(jpi,jpj) :: zsig1, zsig2, zsig3 57 61 REAL(wp), DIMENSION(jpi,jpj,jpl) :: zswi2, zmiss2 58 REAL(wp), DIMENSION(jpi,jpj) :: z2d, zswi, zmiss ! 2D workspace 59 REAL(wp), DIMENSION(jpi,jpj) :: zfb ! ice freeboard 60 REAL(wp), DIMENSION(jpi,jpj) :: zamask, zamask15 ! 15% concentration mask 61 REAL(wp), DIMENSION(jpi,jpj) :: zsig1, zsig2, zsig3 62 62 ! 63 63 ! Global ice diagnostics (SIMIP) 64 REAL(wp) :: zdiag_area_nh, & ! area, extent, volume 65 & zdiag_extt_nh, & 66 & zdiag_area_sh, & 67 & zdiag_extt_sh, & 68 & zdiag_volu_nh, & 69 & zdiag_volu_sh 70 64 REAL(wp) :: zdiag_area_nh, zdiag_extt_nh, zdiag_volu_nh ! area, extent, volume 65 REAL(wp) :: zdiag_area_sh, zdiag_extt_sh, zdiag_volu_sh 71 66 !!------------------------------------------------------------------- 72 67 73 IF( nn_timing == 1 ) CALL timing_start('icewri')68 IF( nn_timing == 1 ) CALL timing_start('icewri') 74 69 75 70 !---------------------------------------- … … 77 72 !---------------------------------------- 78 73 79 ! brine volume 80 CALL ice_var_bv 74 CALL ice_var_bv ! brine volume 81 75 82 76 ! tresholds for outputs … … 96 90 END DO 97 91 98 zmiss_val = 1. 0e2099 zmiss (:,:) = zmiss_val * ( 1. - zswi(:,:) )100 zmiss2(:,:,:) = zmiss_val * ( 1. - zswi2(:,:,:) )92 zmiss_val = 1.e20_wp 93 zmiss (:,:) = zmiss_val * ( 1._wp - zswi (:,:) ) 94 zmiss2(:,:,:) = zmiss_val * ( 1._wp - zswi2(:,:,:) ) 101 95 102 96 !---------------------------------------- … … 112 106 IF( iom_use('qt_ice' ) ) CALL iom_put( "qt_ice" , SUM( ( qns_ice(:,:,:) + qsr_ice(:,:,:) ) & 113 107 & * a_i_b(:,:,:), dim=3 ) + qemp_ice(:,:) ) 108 !!gm I don't understand the variable below.... why not multiplied by a_i_b or (1-a_i_b) ??? 114 109 IF( iom_use('qemp_oce') ) CALL iom_put( "qemp_oce" , qemp_oce(:,:) ) 115 110 IF( iom_use('qemp_ice') ) CALL iom_put( "qemp_ice" , qemp_ice(:,:) ) 116 IF( iom_use('emp_oce' ) ) CALL iom_put( "emp_oce" , emp_oce (:,:) ) ! emp over ocean (taking into account the snow blown away from the ice)117 IF( iom_use('emp_ice' ) ) CALL iom_put( "emp_ice" , emp_ice (:,:) ) ! emp over ice (taking into account the snow blown away from the ice)111 IF( iom_use('emp_oce' ) ) CALL iom_put( "emp_oce" , emp_oce (:,:) ) ! emp over ocean (taking into account the snow blown away from the ice) 112 IF( iom_use('emp_ice' ) ) CALL iom_put( "emp_ice" , emp_ice (:,:) ) ! emp over ice (taking into account the snow blown away from the ice) 118 113 119 114 ! velocity 120 IF ( iom_use('uice_ipa') ) CALL iom_put( "uice_ipa" , u_ice )! ice velocity u component121 IF ( iom_use('vice_ipa') ) CALL iom_put( "vice_ipa" , v_ice )! ice velocity v component122 123 IF ( ( iom_use( "icevel" ) ) .OR. ( iom_use( "icevel_mv" )) ) THEN115 IF( iom_use('uice_ipa') ) CALL iom_put( "uice_ipa" , u_ice ) ! ice velocity u component 116 IF( iom_use('vice_ipa') ) CALL iom_put( "vice_ipa" , v_ice ) ! ice velocity v component 117 118 IF( iom_use('icevel') .OR. iom_use('icevel_mv') ) THEN 124 119 DO jj = 2 , jpjm1 125 120 DO ji = 2 , jpim1 126 z2da = ( u_ice(ji,jj) * umask(ji,jj,1) + u_ice(ji-1,jj) * umask(ji-1,jj,1) ) * 0.5_wp127 z2db = ( v_ice(ji,jj) * vmask(ji,jj,1) + v_ice(ji,jj-1) * vmask(ji,jj-1,1) ) * 0.5_wp128 z2d(ji,jj) = SQRT( z2da * z2da + z2db * z2db )121 z2da = ( u_ice(ji,jj) + u_ice(ji-1,jj) ) 122 z2db = ( v_ice(ji,jj) + v_ice(ji,jj-1) ) 123 z2d(ji,jj) = O.5_wp * SQRT( z2da * z2da + z2db * z2db ) 129 124 END DO 130 125 END DO 131 126 CALL lbc_lnk( z2d, 'T', 1. ) 132 IF ( iom_use( "icevel" ) ) CALL iom_put( "icevel" , z2d )! ice velocity module133 IF ( iom_use( "icevel_mv" ) ) CALL iom_put( "icevel_mv" , z2d(:,:) * zswi(:,:) + zmiss(:,:) )! ice velocity module (missing value)134 ENDIF 135 136 IF ( iom_use( "tau_icebfr" ) )CALL iom_put( "tau_icebfr" , tau_icebfr ) ! ice friction with ocean bottom (landfast ice)137 ! 138 IF ( iom_use( "miceage" )) CALL iom_put( "miceage" , om_i * zswi * zamask15 ) ! mean ice age139 IF ( iom_use( "micet" ) )CALL iom_put( "micet" , ( tm_i - rt0 ) * zswi ) ! ice mean temperature140 IF ( iom_use( "icest" ) )CALL iom_put( "icest" , ( tm_su - rt0 ) * zswi ) ! ice surface temperature141 IF ( iom_use( "icecolf" )) CALL iom_put( "icecolf" , hicol ) ! frazil ice collection thickness127 IF( iom_use('icevel' ) ) CALL iom_put( "icevel" , z2d ) ! ice velocity module 128 IF( iom_use('icevel_mv') ) CALL iom_put( "icevel_mv" , z2d(:,:) * zswi(:,:) + zmiss(:,:) ) ! ice velocity module (missing value) 129 ENDIF 130 131 IF( iom_use('tau_icebfr') ) CALL iom_put( "tau_icebfr" , tau_icebfr ) ! ice friction with ocean bottom (landfast ice) 132 ! 133 IF( iom_use('miceage') ) CALL iom_put( "miceage" , om_i * zswi * zamask15 ) ! mean ice age 134 IF( iom_use('micet') ) CALL iom_put( "micet" , ( tm_i - rt0 ) * zswi ) ! ice mean temperature 135 IF( iom_use('icest') ) CALL iom_put( "icest" , ( tm_su - rt0 ) * zswi ) ! ice surface temperature 136 IF( iom_use('icecolf') ) CALL iom_put( "icecolf" , hicol ) ! frazil ice collection thickness 142 137 ! 143 138 CALL iom_put( "isst" , sst_m ) ! sea surface temperature … … 149 144 CALL iom_put( "isnowhc" , et_s * zswi ) ! snow total heat content 150 145 CALL iom_put( "ibrinv" , bvm_i * zswi * 100. ) ! brine volume 151 CALL iom_put( "snowpre" , sprecip * 86400. ) ! snow precipitation 146 CALL iom_put( "snowpre" , sprecip * 86400. ) ! snow precipitation [m/day] 152 147 CALL iom_put( "micesalt" , smt_i * zswi ) ! mean ice salinity 153 148 CALL iom_put( "snowvol" , vt_s * zswi ) ! snow volume … … 224 219 CALL iom_put ('hfxspr' , hfx_spr(:,:) ) ! Heat content of snow precip 225 220 221 !!gm ====>>>>> THIS should be moved in icerhg_evp (generalize this everywhere it is possible and logic...) 226 222 ! specific outputs for EVP rheology 227 IF( iom_use( "isig1" ) .OR. iom_use( "isig2" ) .OR. iom_use( "isig3") ) THEN223 IF( iom_use('isig1') .OR. iom_use('isig2') .OR. iom_use('isig3') ) THEN 228 224 zsig1(:,:) = 0._wp; zsig2(:,:) = 0._wp; zsig3(:,:) = 0._wp; 229 225 DO jj = 2, jpjm1 … … 251 247 CALL iom_put( "isig3" , zsig3 ) 252 248 ENDIF 253 249 !!gm <<<<<<======= end 250 251 !!gm ====>>>>> THIS should be moved where at_ip, vt_ip are computed fro the last time in the time-step (limmpd) 254 252 ! MV MP 2016 255 253 IF ( ln_pnd ) THEN … … 258 256 ENDIF 259 257 ! END MV MP 2016 258 !!gm <<<<<<======= end 260 259 261 260 !---------------------------------- 262 261 ! Output category-dependent fields 263 262 !---------------------------------- 264 IF ( iom_use( "iceconc_cat" ) ) CALL iom_put( "iceconc_cat" , a_i * zswi2 ) ! area for categories 265 IF ( iom_use( "icethic_cat" ) ) CALL iom_put( "icethic_cat" , ht_i * zswi2 ) ! thickness for categories 266 IF ( iom_use( "snowthic_cat" ) ) CALL iom_put( "snowthic_cat" , ht_s * zswi2 ) ! snow depth for categories 267 IF ( iom_use( "salinity_cat" ) ) CALL iom_put( "salinity_cat" , sm_i * zswi2 ) ! salinity for categories 268 ! ice temperature 269 IF ( iom_use( "icetemp_cat" ) ) CALL iom_put( "icetemp_cat", ( SUM( t_i(:,:,:,:), dim=3 ) * r1_nlay_i - rt0 ) * zswi2 ) 270 ! snow temperature 271 IF ( iom_use( "snwtemp_cat" ) ) CALL iom_put( "snwtemp_cat", ( SUM( t_s(:,:,:,:), dim=3 ) * r1_nlay_s - rt0 ) * zswi2 ) 272 ! ice age 273 IF ( iom_use( "iceage_cat" ) ) CALL iom_put( "iceage_cat" , o_i * zswi2 ) 274 ! brine volume 275 IF ( iom_use( "brinevol_cat" ) ) CALL iom_put( "brinevol_cat", bv_i * 100. * zswi2 ) 263 IF ( iom_use('iceconc_cat' ) ) CALL iom_put( "iceconc_cat" , a_i * zswi2 ) ! area for categories 264 IF ( iom_use('icethic_cat' ) ) CALL iom_put( "icethic_cat" , ht_i * zswi2 ) ! thickness for categories 265 IF ( iom_use('snowthic_cat') ) CALL iom_put( "snowthic_cat" , ht_s * zswi2 ) ! snow depth for categories 266 IF ( iom_use('salinity_cat') ) CALL iom_put( "salinity_cat" , sm_i * zswi2 ) ! salinity for categories 267 IF ( iom_use('icetemp_cat' ) ) CALL iom_put( "icetemp_cat", ( SUM( t_i(:,:,:,:), dim=3 ) * r1_nlay_i - rt0 ) * zswi2 ) ! ice temperature 268 IF ( iom_use('snwtemp_cat' ) ) CALL iom_put( "snwtemp_cat", ( SUM( t_s(:,:,:,:), dim=3 ) * r1_nlay_s - rt0 ) * zswi2 ) ! snow temperature 269 IF ( iom_use('iceage_cat' ) ) CALL iom_put( "iceage_cat" , o_i * zswi2 ) ! ice age 270 IF ( iom_use('brinevol_cat') ) CALL iom_put( "brinevol_cat", bv_i * 100. * zswi2 ) ! brine volume 276 271 277 272 ! MV MP 2016 278 273 IF ( ln_pnd ) THEN 279 IF ( iom_use( "iceamp_cat") ) CALL iom_put( "iceamp_cat" , a_ip * zswi2 ) ! melt pond frac for categories280 IF ( iom_use( "icevmp_cat") ) CALL iom_put( "icevmp_cat" , v_ip * zswi2 ) ! melt pond frac for categories281 IF ( iom_use( "icehmp_cat") ) CALL iom_put( "icehmp_cat" , h_ip * zswi2 ) ! melt pond frac for categories282 IF ( iom_use( "iceafp_cat") ) CALL iom_put( "iceafp_cat" , a_ip_frac * zswi2 ) ! melt pond frac for categories274 IF ( iom_use('iceamp_cat') ) CALL iom_put( "iceamp_cat" , a_ip * zswi2 ) ! melt pond frac for categories 275 IF ( iom_use('icevmp_cat') ) CALL iom_put( "icevmp_cat" , v_ip * zswi2 ) ! melt pond frac for categories 276 IF ( iom_use('icehmp_cat') ) CALL iom_put( "icehmp_cat" , h_ip * zswi2 ) ! melt pond frac for categories 277 IF ( iom_use('iceafp_cat') ) CALL iom_put( "iceafp_cat" , a_ip_frac * zswi2 ) ! melt pond frac for categories 283 278 ENDIF 284 279 ! END MV MP 2016 … … 289 284 zrho1 = ( rau0 - rhoic ) / rau0; zrho2 = rhosn / rau0 290 285 291 IF 292 IF 293 IF 294 IF 295 IF 296 297 IF 298 IF 299 IF 300 301 IF 302 IF 303 IF 304 IF 305 IF 306 IF 307 308 IF 286 IF ( iom_use( "icepres" ) ) CALL iom_put( "icepres" , zswi(:,:) ) ! Ice presence (1 or 0) 287 IF ( iom_use( "icemass" ) ) CALL iom_put( "icemass" , rhoic * vt_i(:,:) * zswi(:,:) ) ! Ice mass per cell area 288 IF ( iom_use( "icethic" ) ) CALL iom_put( "icethic" , htm_i(:,:) * zamask(:,:) + ( 1. - zamask(:,:) ) * zmiss_val ) ! Ice thickness 289 IF ( iom_use( "snomass" ) ) CALL iom_put( "snomass" , rhosn * vt_s(:,:) * zswi(:,:) + zmiss(:,:) ) ! Snow mass per cell area 290 IF ( iom_use( "snothic" ) ) CALL iom_put( "snothic" , htm_s(:,:) * zamask(:,:) + ( 1. - zamask(:,:) ) * zmiss_val ) ! Snow thickness 291 292 IF ( iom_use( "iceconc_cat_mv" ) ) CALL iom_put( "iceconc_cat_mv" , a_i(:,:,:) * zswi2(:,:,:) + zmiss2(:,:,:) ) ! Area for categories 293 IF ( iom_use( "icethic_cat_mv" ) ) CALL iom_put( "icethic_cat_mv" , ht_i(:,:,:) * zswi2(:,:,:) + zmiss2(:,:,:) ) ! Thickness for categories 294 IF ( iom_use( "snowthic_cat_mv" ) ) CALL iom_put( "snowthic_cat_mv", ht_s(:,:,:) * zswi2(:,:,:) + zmiss2(:,:,:) ) ! Snow depth for categories 295 296 IF ( iom_use( "icestK" ) ) CALL iom_put( "icestK" , tm_su(:,:) * zswi(:,:) + zmiss(:,:) ) ! Ice surface temperature 297 IF ( iom_use( "icesntK" ) ) CALL iom_put( "icesntK" , tm_si(:,:) * zswi(:,:) + zmiss(:,:) ) ! Snow-ice interface temperature 298 IF ( iom_use( "icebotK" ) ) CALL iom_put( "icebotK" , t_bo(:,:) * zswi(:,:) + zmiss(:,:) ) ! Ice bottom temperature 299 IF ( iom_use( "iceage" ) ) CALL iom_put( "iceage" , om_i(:,:) * zamask15(:,:) + ( 1. - zamask15(:,:) ) * zmiss_val ) ! Ice age 300 IF ( iom_use( "icesmass" ) ) CALL iom_put( "icesmass" , SUM( smv_i, DIM = 3 ) * rhoic * 1.0e-3 * zswi(:,:) ) ! Mass of salt in sea ice per cell area 301 IF ( iom_use( "icesal" ) ) CALL iom_put( "icesal" , smt_i(:,:) * zswi(:,:) + zmiss(:,:) ) ! Ice salinity 302 303 IF ( iom_use( "icefb" ) ) THEN 309 304 zfb(:,:) = ( zrho1 * htm_i(:,:) - zrho2 * htm_s(:,:) ) 310 305 WHERE( zfb < 0._wp ) ; zfb = 0._wp ; END WHERE 311 312 ENDIF 313 314 IF 315 316 IF 317 & - wfx_sni - wfx_opw - wfx_res )318 IF 319 IF 320 IF 321 IF 322 IF 323 IF 324 325 IF 326 IF 327 IF 328 329 IF 330 IF 331 332 IF 333 IF 334 335 IF 336 IF 337 IF 338 339 IF 340 IF 341 IF 342 343 IF 344 IF 306 CALL iom_put( "icefb" , zfb(:,:) * zswi(:,:) + zmiss(:,:) ) ! Ice freeboard 307 ENDIF 308 309 IF ( iom_use( "isnhcneg" ) ) CALL iom_put( "isnhcneg" , - et_s(:,:) * zswi(:,:) + zmiss(:,:) ) ! Snow total heat content 310 311 IF ( iom_use( "dmithd" ) ) CALL iom_put( "dmithd" , - wfx_bog - wfx_bom - wfx_sum & ! Sea-ice mass change from thermodynamics 312 & - wfx_sni - wfx_opw - wfx_res ) 313 IF ( iom_use( "dmidyn" ) ) CALL iom_put( "dmidyn" , diag_dmi_dyn ) ! Sea-ice mass change from dynamics 314 IF ( iom_use( "dmiopw" ) ) CALL iom_put( "dmiopw" , - wfx_opw ) ! Sea-ice mass change through growth in open water 315 IF ( iom_use( "dmibog" ) ) CALL iom_put( "dmibog" , - wfx_bog ) ! Sea-ice mass change through basal growth 316 IF ( iom_use( "dmisni" ) ) CALL iom_put( "dmisni" , - wfx_sni ) ! Sea-ice mass change through snow-to-ice conversion 317 IF ( iom_use( "dmisum" ) ) CALL iom_put( "dmisum" , - wfx_sum ) ! Sea-ice mass change through surface melting 318 IF ( iom_use( "dmibom" ) ) CALL iom_put( "dmibom" , - wfx_bom ) ! Sea-ice mass change through bottom melting 319 320 IF ( iom_use( "dmtsub" ) ) CALL iom_put( "dmtsub" , - wfx_sub ) ! Sea-ice mass change through evaporation and sublimation 321 IF ( iom_use( "dmssub" ) ) CALL iom_put( "dmssub" , - wfx_snw_sub ) ! Snow mass change through sublimation 322 IF ( iom_use( "dmisub" ) ) CALL iom_put( "dmisub" , - wfx_ice_sub ) ! Sea-ice mass change through sublimation 323 324 IF ( iom_use( "dmsspr" ) ) CALL iom_put( "dmsspr" , - wfx_spr ) ! Snow mass change through snow fall 325 IF ( iom_use( "dmsssi" ) ) CALL iom_put( "dmsssi" , wfx_sni*rhosn/rhoic ) ! Snow mass change through snow-to-ice conversion 326 327 IF ( iom_use( "dmsmel" ) ) CALL iom_put( "dmsmel" , - wfx_snw_sum ) ! Snow mass change through melt 328 IF ( iom_use( "dmsdyn" ) ) CALL iom_put( "dmsdyn" , diag_dms_dyn ) ! Snow mass change through dynamics 329 330 IF ( iom_use( "hfxsenso" ) ) CALL iom_put( "hfxsenso" , -fhtur(:,:) * zswi(:,:) + zmiss(:,:) ) ! Sensible oceanic heat flux 331 IF ( iom_use( "hfxconbo" ) ) CALL iom_put( "hfxconbo" , diag_fc_bo * zswi(:,:) + zmiss(:,:) ) ! Bottom conduction flux 332 IF ( iom_use( "hfxconsu" ) ) CALL iom_put( "hfxconsu" , diag_fc_su * zswi(:,:) + zmiss(:,:) ) ! Surface conduction flux 333 334 IF ( iom_use( "wfxtot" ) ) CALL iom_put( "wfxtot" , wfx_ice(:,:) * zswi(:,:) + zmiss(:,:) ) ! Total freshwater flux from sea ice 335 IF ( iom_use( "wfxsum" ) ) CALL iom_put( "wfxsum" , wfx_sum(:,:) * zswi(:,:) + zmiss(:,:) ) ! Freshwater flux from sea-ice surface 336 IF ( iom_use( "sfx_mv" ) ) CALL iom_put( "sfx_mv" , sfx(:,:) * 0.001 * zswi(:,:) + zmiss(:,:) ) ! Total salt flux 337 338 IF ( iom_use( "uice_mv" ) ) CALL iom_put( "uice_mv" , u_ice(:,:) * zswi(:,:) + zmiss(:,:) ) ! ice velocity u component 339 IF ( iom_use( "vice_mv" ) ) CALL iom_put( "vice_mv" , v_ice(:,:) * zswi(:,:) + zmiss(:,:) ) ! ice velocity v component 345 340 346 IF 347 IF 348 349 IF 350 IF 351 352 IF 353 IF 354 355 IF 356 IF 357 358 IF 359 IF 360 361 IF 362 363 IF 364 IF 365 366 IF 367 IF 368 369 IF 370 IF 371 372 IF 373 IF 341 IF ( iom_use( "xmtrpice" ) ) CALL iom_put( "xmtrpice" , diag_xmtrp_ice(:,:) ) ! X-component of sea-ice mass transport (kg/s) 342 IF ( iom_use( "ymtrpice" ) ) CALL iom_put( "ymtrpice" , diag_ymtrp_ice(:,:) ) ! Y-component of sea-ice mass transport 343 344 IF ( iom_use( "xmtrpsnw" ) ) CALL iom_put( "xmtrpsnw" , diag_xmtrp_snw(:,:) ) ! X-component of snow mass transport (kg/s) 345 IF ( iom_use( "ymtrpsnw" ) ) CALL iom_put( "ymtrpsnw" , diag_ymtrp_snw(:,:) ) ! Y-component of snow mass transport 346 347 IF ( iom_use( "xatrp" ) ) CALL iom_put( "xatrp" , diag_xatrp(:,:) ) ! X-component of ice area transport 348 IF ( iom_use( "yatrp" ) ) CALL iom_put( "yatrp" , diag_yatrp(:,:) ) ! Y-component of ice area transport 349 350 IF ( iom_use( "utau_ice" ) ) CALL iom_put( "utau_ice" , utau_ice(:,:) * zswi(:,:) + zmiss(:,:) ) ! Wind stress term in force balance (x) 351 IF ( iom_use( "vtau_ice" ) ) CALL iom_put( "vtau_ice" , vtau_ice(:,:) * zswi(:,:) + zmiss(:,:) ) ! Wind stress term in force balance (y) 352 353 IF ( iom_use( "utau_oi" ) ) CALL iom_put( "utau_oi" , diag_utau_oi(:,:) * zswi(:,:) + zmiss(:,:) ) ! Ocean stress term in force balance (x) 354 IF ( iom_use( "vtau_oi" ) ) CALL iom_put( "vtau_oi" , diag_vtau_oi(:,:) * zswi(:,:) + zmiss(:,:) ) ! Ocean stress term in force balance (y) 355 356 IF ( iom_use( "icestr" ) ) CALL iom_put( "icestr" , strength(:,:) * zswi(:,:) + zmiss(:,:) ) ! Ice strength 357 358 IF ( iom_use( "dssh_dx" ) ) CALL iom_put( "dssh_dx" , diag_dssh_dx(:,:) * zswi(:,:) + zmiss(:,:) ) ! Sea-surface tilt term in force balance (x) 359 IF ( iom_use( "dssh_dy" ) ) CALL iom_put( "dssh_dy" , diag_dssh_dy(:,:) * zswi(:,:) + zmiss(:,:) ) ! Sea-surface tilt term in force balance (y) 360 361 IF ( iom_use( "corstrx" ) ) CALL iom_put( "corstrx" , diag_corstrx(:,:) * zswi(:,:) + zmiss(:,:) ) ! Coriolis force term in force balance (x) 362 IF ( iom_use( "corstry" ) ) CALL iom_put( "corstry" , diag_corstry(:,:) * zswi(:,:) + zmiss(:,:) ) ! Coriolis force term in force balance (y) 363 364 IF ( iom_use( "intstrx" ) ) CALL iom_put( "intstrx" , diag_intstrx(:,:) * zswi(:,:) + zmiss(:,:) ) ! Internal force term in force balance (x) 365 IF ( iom_use( "intstry" ) ) CALL iom_put( "intstry" , diag_intstry(:,:) * zswi(:,:) + zmiss(:,:) ) ! Internal force term in force balance (y) 366 367 IF ( iom_use( "normstr" ) ) CALL iom_put( "normstr" , diag_sig1(:,:) * zswi(:,:) + zmiss(:,:) ) ! Normal stress 368 IF ( iom_use( "sheastr" ) ) CALL iom_put( "sheastr" , diag_sig2(:,:) * zswi(:,:) + zmiss(:,:) ) ! Shear stress 374 369 375 370 !-------------------------------- 376 371 ! Global ice diagnostics (SIMIP) 377 372 !-------------------------------- 378 379 IF ( iom_use( "NH_icearea" ) .OR. iom_use( "NH_icevolu" ) .OR. iom_use( "NH_iceextt" ) ) THEN ! NH integrateddiagnostics380 381 WHERE( ff_t > 0._wp ) ;zswi(:,:) = 1.0e-12382 ELSEWHERE ;zswi(:,:) = 0.373 ! 374 IF ( iom_use( "NH_icearea" ) .OR. iom_use( "NH_icevolu" ) .OR. iom_use( "NH_iceextt" ) ) THEN ! NH diagnostics 375 ! 376 WHERE( ff_t > 0._wp ) ; zswi(:,:) = 1.0e-12 377 ELSEWHERE ; zswi(:,:) = 0. 383 378 END WHERE 384 385 379 zdiag_area_nh = glob_sum( at_i(:,:) * zswi(:,:) * e1e2t(:,:) ) 386 380 zdiag_volu_nh = glob_sum( vt_i(:,:) * zswi(:,:) * e1e2t(:,:) ) 387 388 WHERE( ff_t > 0._wp .AND. at_i > 0.15 ) ; zswi(:,:) = 1.0e-12389 ELSEWHERE ; zswi(:,:) = 0.381 ! 382 WHERE( ff_t > 0._wp .AND. at_i > 0.15 ) ; zswi(:,:) = 1.0e-12 383 ELSEWHERE ; zswi(:,:) = 0. 390 384 END WHERE 391 392 385 zdiag_extt_nh = glob_sum( zswi(:,:) * e1e2t(:,:) ) 393 394 IF ( iom_use( "NH_icearea" ) ) CALL iom_put( "NH_icearea" , zdiag_area_nh )395 IF ( iom_use( "NH_icevolu" ) ) CALL iom_put( "NH_icevolu" , zdiag_volu_nh )396 IF ( iom_use( "NH_iceextt" ) ) CALL iom_put( "NH_iceextt" , zdiag_extt_nh )397 398 ENDIF 399 400 IF ( iom_use( "SH_icearea" ) .OR. iom_use( "SH_icevolu" ) .OR. iom_use( "SH_iceextt" ) ) THEN ! SH integrateddiagnostics401 386 ! 387 IF ( iom_use( "NH_icearea" ) ) CALL iom_put( "NH_icearea" , zdiag_area_nh ) 388 IF ( iom_use( "NH_icevolu" ) ) CALL iom_put( "NH_icevolu" , zdiag_volu_nh ) 389 IF ( iom_use( "NH_iceextt" ) ) CALL iom_put( "NH_iceextt" , zdiag_extt_nh ) 390 ! 391 ENDIF 392 ! 393 IF ( iom_use( "SH_icearea" ) .OR. iom_use( "SH_icevolu" ) .OR. iom_use( "SH_iceextt" ) ) THEN ! SH diagnostics 394 ! 402 395 WHERE( ff_t < 0._wp ); zswi(:,:) = 1.0e-12; 403 396 ELSEWHERE ; zswi(:,:) = 0. 404 397 END WHERE 405 406 398 zdiag_area_sh = glob_sum( at_i(:,:) * zswi(:,:) * e1e2t(:,:) ) 407 399 zdiag_volu_sh = glob_sum( vt_i(:,:) * zswi(:,:) * e1e2t(:,:) ) 408 400 ! 409 401 WHERE( ff_t < 0._wp .AND. at_i > 0.15 ); zswi(:,:) = 1.0e-12 410 402 ELSEWHERE ; zswi(:,:) = 0. 411 403 END WHERE 412 413 404 zdiag_extt_sh = glob_sum( zswi(:,:) * e1e2t(:,:) ) 414 405 ! 415 406 IF ( iom_use( "SH_icearea" ) ) CALL iom_put( "SH_icearea", zdiag_area_sh ) 416 407 IF ( iom_use( "SH_icevolu" ) ) CALL iom_put( "SH_icevolu", zdiag_volu_sh ) 417 408 IF ( iom_use( "SH_iceextt" ) ) CALL iom_put( "SH_iceextt", zdiag_extt_sh ) 418 409 ! 419 410 ENDIF 420 421 ! ! Create an output files (output.lim.abort.nc) if S < 0 or u > 20 m/s 422 ! IF( kindic < 0 ) CALL ice_wri_state( 'output.abort' ) 423 ! not yet implemented 424 411 ! 412 !!CR ! ! Create an output files (output.lim.abort.nc) if S < 0 or u > 20 m/s 413 !!CR ! IF( kindic < 0 ) CALL ice_wri_state( 'output.abort' ) 414 !!CR ! not yet implemented 415 !!gm idem for the ocean... Ask Seb how to get read of ioipsl.... 416 ! 425 417 IF( nn_timing == 1 ) CALL timing_stop('icewri') 426 418 ! 427 419 END SUBROUTINE ice_wri 428 420 … … 437 429 !! ocean state in case of abnormal end of a simulation 438 430 !! 439 !! History : 440 !! 4.0 ! 2013-06 (C. Rousset) 431 !! History : 4.0 ! 2013-06 (C. Rousset) 441 432 !!---------------------------------------------------------------------- 442 433 INTEGER, INTENT( in ) :: kt ! ocean time-step index) … … 445 436 REAL(wp), DIMENSION(jpl) :: jcat 446 437 !!---------------------------------------------------------------------- 438 ! 447 439 DO jl = 1, jpl 448 440 jcat(jl) = REAL(jl) 449 END DO441 END DO 450 442 451 443 CALL histvert( kid, "ncatice", "Ice Categories","", jpl, jcat, nz_i, "up") … … 557 549 ! Close the file 558 550 ! ----------------- 551 !!gm I don't understand why the file is not closed ! 559 552 !CALL histclo( kid ) 560 553 ! 561 554 END SUBROUTINE ice_wri_state 562 555 … … 565 558 !! Default option : Empty module NO LIM sea-ice model 566 559 !!---------------------------------------------------------------------- 567 CONTAINS568 SUBROUTINE ice_wri ! Empty routine569 END SUBROUTINE ice_wri570 560 #endif 571 561
Note: See TracChangeset
for help on using the changeset viewer.