Skip to content
Snippets Groups Projects
Commit 4591b3ed authored by Guillaume Samson's avatar Guillaume Samson :snowman2:
Browse files

Merge branch 'cherry-pick-0dd6ddf5' into 'branch_4.2'

Merge branch '129-wrong-icb-melting-flux-depending-on-nn_fsbc' into 'branch_4.2'

See merge request nemo/nemo!278
parents 8173886d 919eb1e2
No related branches found
No related tags found
No related merge requests found
...@@ -627,8 +627,10 @@ ...@@ -627,8 +627,10 @@
! ! diagnostics: ! ! diagnostics:
ln_bergdia = .true. ! Calculate budgets ln_bergdia = .true. ! Calculate budgets
nn_verbose_level = 0 ! Turn on more verbose output if level > 0 nn_verbose_level = 0 ! Turn on more verbose output if level > 0
nn_verbose_write = 15 ! Timesteps between verbose messages !
nn_sample_rate = 1 ! Timesteps between sampling for trajectory storage ! nn_verbose_write and nn_sample_rate need to be a multiple of nn_fsbc
nn_verbose_write = 16 ! Timesteps between verbose messages
nn_sample_rate = 16 ! Timesteps between sampling for trajectory storage
! !
! ! iceberg setting: ! ! iceberg setting:
! ! Initial mass required for an iceberg of each class ! ! Initial mass required for an iceberg of each class
......
...@@ -522,6 +522,16 @@ CONTAINS ...@@ -522,6 +522,16 @@ CONTAINS
CALL ctl_stop( 'icb_nam: a negative rn_distribution value encountered ==>> change your namelist namberg' ) CALL ctl_stop( 'icb_nam: a negative rn_distribution value encountered ==>> change your namelist namberg' )
ENDIF ENDIF
! !
! ensure that nn_verbose_write is a multiple of nn_fsbc
IF (MOD(nn_verbose_write, nn_fsbc) /= 0) THEN
CALL ctl_stop( 'icb_nam: nn_verbose_write is not a multiple of nn_fsbc')
END IF
!
! ensure that nn_sample_rate is a multiple of nn_fsbc
IF (MOD(nn_sample_rate, nn_fsbc) /= 0) THEN
CALL ctl_stop( 'icb_nam: nn_sample_rate is not a multiple of nn_fsbc')
END IF
!
END SUBROUTINE icb_nam END SUBROUTINE icb_nam
!!====================================================================== !!======================================================================
......
...@@ -68,78 +68,79 @@ CONTAINS ...@@ -68,78 +68,79 @@ CONTAINS
IF( ln_timing ) CALL timing_start('icb_stp') IF( ln_timing ) CALL timing_start('icb_stp')
! !== start of timestep housekeeping ==! ! !== start of timestep housekeeping ==!
!
nktberg = kt IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN
!
!CALL test_icb_utl_getkb
!CALL ctl_stop('end test icb')
!
IF( nn_test_icebergs < 0 .OR. ln_use_calving ) THEN !* read calving data
! !
CALL fld_read ( kt, 1, sf_icb ) nktberg = kt
src_calving (:,:) = sf_icb(1)%fnow(:,:,1) ! calving in km^3/year (water equivalent)
src_calving_hflx(:,:) = 0._wp ! NO heat flux for now
! !
ENDIF IF( nn_test_icebergs < 0 .OR. ln_use_calving ) THEN !* read calving data
! !
berg_grid%floating_melt(:,:) = 0._wp CALL fld_read ( kt, 1, sf_icb )
! src_calving (:,:) = sf_icb(1)%fnow(:,:,1) ! calving in km^3/year (water equivalent)
! !* anything that needs to be reset to zero each timestep src_calving_hflx(:,:) = 0._wp ! NO heat flux for now
CALL icb_dia_step() ! for budgets is dealt with here !
! ENDIF
! !* write out time !
ll_verbose = .FALSE. berg_grid%floating_melt(:,:) = 0._wp
IF( nn_verbose_write > 0 .AND. MOD( kt-1 , nn_verbose_write ) == 0 ) ll_verbose = ( nn_verbose_level > 0 ) !
! ! !* anything that needs to be reset to zero each timestep
IF( ll_verbose ) WRITE(numicb,9100) nktberg, ndastp, nsec_day CALL icb_dia_step() ! for budgets is dealt with here
9100 FORMAT('kt= ',i8, ' day= ',i8,' secs=',i8) !
! ! !* write out time
! !* copy nemo forcing arrays into iceberg versions with extra halo ll_verbose = .FALSE.
CALL icb_utl_copy( Kmm ) ! only necessary for variables not on T points IF( nn_verbose_write > 0 .AND. MOD( kt-1 , nn_verbose_write ) == 0 ) ll_verbose = ( nn_verbose_level > 0 )
! !
! IF( ll_verbose ) WRITE(numicb,9100) nktberg, ndastp, nsec_day
! !== process icebergs ==! 9100 FORMAT('kt= ',i8, ' day= ',i8,' secs=',i8)
! ! !
CALL icb_clv_flx( kt ) ! Accumulate ice from calving ! !* copy nemo forcing arrays into iceberg versions with extra halo
! ! CALL icb_utl_copy( Kmm ) ! only necessary for variables not on T points
CALL icb_clv( kt ) ! Calve excess stored ice into icebergs !
! ! !
! ! !== process icebergs ==!
! !== For each berg, evolve ==! ! !
! CALL icb_clv_flx( kt ) ! Accumulate ice from calving
IF( ASSOCIATED(first_berg) ) CALL icb_dyn( kt ) ! ice berg dynamics ! !
CALL icb_clv( kt ) ! Calve excess stored ice into icebergs
IF( lk_mpp ) THEN ; CALL icb_lbc_mpp() ! Send bergs to other PEs ! !
ELSE ; CALL icb_lbc() ! Deal with any cyclic boundaries in non-mpp case !
ENDIF ! !== For each berg, evolve ==!
!
IF( ASSOCIATED(first_berg) ) CALL icb_thm( kt ) ! Ice berg thermodynamics (melting) + rolling IF( ASSOCIATED(first_berg) ) CALL icb_dyn( kt ) ! ice berg dynamics
!
! IF( lk_mpp ) THEN ; CALL icb_lbc_mpp() ! Send bergs to other PEs
! !== diagnostics and output ==! ELSE ; CALL icb_lbc() ! Deal with any cyclic boundaries in non-mpp case
! ENDIF
! !* For each berg, record trajectory (when needed)
ll_sample_traj = .FALSE. IF( ASSOCIATED(first_berg) ) CALL icb_thm( kt ) ! Ice berg thermodynamics (melting) + rolling
IF( nn_sample_rate > 0 .AND. MOD(kt-1,nn_sample_rate) == 0 ) ll_sample_traj = .TRUE. !
IF( ll_sample_traj .AND. ASSOCIATED(first_berg) ) CALL icb_trj_write( kt ) !
! !== diagnostics and output ==!
! !* Gridded diagnostics !
! ! To get these iom_put's and those preceding to actually do something ! !* For each berg, record trajectory (when needed)
! ! use key_xios in cpp file and create content for XML file ll_sample_traj = .FALSE.
! IF( nn_sample_rate > 0 .AND. MOD(kt-1,nn_sample_rate) == 0 ) ll_sample_traj = .TRUE.
CALL iom_put( "calving" , berg_grid%calving (:,:) ) ! 'calving mass input' IF( ll_sample_traj .AND. ASSOCIATED(first_berg) ) CALL icb_trj_write( kt )
CALL iom_put( "berg_floating_melt", berg_grid%floating_melt(:,:) ) ! 'Melt rate of icebergs + bits' , 'kg/m2/s'
CALL iom_put( "berg_stored_ice" , berg_grid%stored_ice (:,:,:) ) ! 'Accumulated ice mass by class', 'kg' ! !* Gridded diagnostics
! ! ! To get these iom_put's and those preceding to actually do something
CALL icb_dia_put() !* store mean budgets ! ! use key_xios in cpp file and create content for XML file
! !
! !* Dump icebergs to screen CALL iom_put( "calving" , berg_grid%calving (:,:) ) ! 'calving mass input'
IF( nn_verbose_level >= 2 ) CALL icb_utl_print( 'icb_stp, status', kt ) CALL iom_put( "berg_floating_melt", berg_grid%floating_melt(:,:) ) ! 'Melt rate of icebergs + bits' , 'kg/m2/s'
! CALL iom_put( "berg_stored_ice" , berg_grid%stored_ice (:,:,:) ) ! 'Accumulated ice mass by class', 'kg'
! !* Diagnose budgets !
ll_budget = .FALSE. CALL icb_dia_put() !* store mean budgets
IF( nn_verbose_write > 0 .AND. MOD(kt-1,nn_verbose_write) == 0 ) ll_budget = ln_bergdia !
CALL icb_dia( ll_budget ) ! !* Dump icebergs to screen
IF( nn_verbose_level >= 2 ) CALL icb_utl_print( 'icb_stp, status', kt )
!
! !* Diagnose budgets
ll_budget = .FALSE.
IF( nn_verbose_write > 0 .AND. MOD(kt-1,nn_verbose_write) == 0 ) ll_budget = ln_bergdia
CALL icb_dia( ll_budget )
!
END IF
! !
IF( lrst_oce ) THEN !* restart IF( lrst_oce ) THEN !* restart
CALL icb_rst_write( kt ) CALL icb_rst_write( kt )
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment