diff --git a/cfgs/SHARED/namelist_ref b/cfgs/SHARED/namelist_ref
index ae9d42ee79e125df420a6142699d2a3f4de78754..47c83e255c4f5b86fa6fc86f94f68295b559deb9 100644
--- a/cfgs/SHARED/namelist_ref
+++ b/cfgs/SHARED/namelist_ref
@@ -627,8 +627,10 @@
    !                          ! diagnostics:
    ln_bergdia        = .true.        ! Calculate budgets
    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:
    !                                 ! Initial mass required for an iceberg of each class
diff --git a/src/OCE/ICB/icbini.F90 b/src/OCE/ICB/icbini.F90
index d7bd2624c38eab5be0807f39bb84ee1dd42bd486..10e84041a06193c2f647a2a4a72a65f82981ed0b 100644
--- a/src/OCE/ICB/icbini.F90
+++ b/src/OCE/ICB/icbini.F90
@@ -522,6 +522,16 @@ CONTAINS
          CALL ctl_stop( 'icb_nam: a negative rn_distribution value encountered ==>> change your namelist namberg' )
       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
 
    !!======================================================================
diff --git a/src/OCE/ICB/icbstp.F90 b/src/OCE/ICB/icbstp.F90
index 6cbda449f4b842f4b33cb95dac09028f87a5be78..8118f945064cd94e610a1ed7616bc736e38fbf33 100644
--- a/src/OCE/ICB/icbstp.F90
+++ b/src/OCE/ICB/icbstp.F90
@@ -68,78 +68,79 @@ CONTAINS
       IF( ln_timing )   CALL timing_start('icb_stp')
 
       !                       !==  start of timestep housekeeping  ==!
-      !
-      nktberg = kt
-      !
-      !CALL test_icb_utl_getkb
-      !CALL ctl_stop('end test icb')
-      !
-      IF( nn_test_icebergs < 0 .OR. ln_use_calving ) THEN !* read calving data
+
+      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN
          !
-         CALL fld_read ( kt, 1, sf_icb )
-         src_calving     (:,:) = sf_icb(1)%fnow(:,:,1)    ! calving in km^3/year (water equivalent)
-         src_calving_hflx(:,:) = 0._wp                    ! NO heat flux for now
+         nktberg = kt
          !
-      ENDIF
-      !
-      berg_grid%floating_melt(:,:) = 0._wp
-      !
-      !                                   !* anything that needs to be reset to zero each timestep 
-      CALL icb_dia_step()                 !  for budgets is dealt with here
-      !
-      !                                   !* write out time
-      ll_verbose = .FALSE.
-      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
- 9100 FORMAT('kt= ',i8, ' day= ',i8,' secs=',i8)
-      !
-      !                                   !* copy nemo forcing arrays into iceberg versions with extra halo
-      CALL icb_utl_copy( Kmm )                 ! only necessary for variables not on T points
-      !
-      !
-      !                       !==  process icebergs  ==!
-      !                              !
-                                     CALL icb_clv_flx( kt )   ! Accumulate ice from calving
-      !                              !
-                                     CALL icb_clv( kt )       ! Calve excess stored ice into icebergs
-      !                              !
-      !
-      !                       !==  For each berg, evolve  ==!
-      !
-      IF( ASSOCIATED(first_berg) )   CALL icb_dyn( kt )       ! ice berg dynamics
-
-      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
-
-      IF( ASSOCIATED(first_berg) )   CALL icb_thm( kt )       ! Ice berg thermodynamics (melting) + rolling
-      !
-      !
-      !                       !==  diagnostics and output  ==!
-      !
-      !                                   !* For each berg, record trajectory (when needed)
-      ll_sample_traj = .FALSE.
-      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 )
-
-      !                                   !* Gridded diagnostics
-      !                                   !  To get these iom_put's and those preceding to actually do something
-      !                                   !  use key_xios in cpp file and create content for XML file
-      !
-      CALL iom_put( "calving"           , berg_grid%calving      (:,:)   )  ! 'calving mass input'
-      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'
-      !
-      CALL icb_dia_put()                  !* store mean budgets
-      !
-      !                                   !*  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 )
+         IF( nn_test_icebergs < 0 .OR. ln_use_calving ) THEN !* read calving data
+            !
+            CALL fld_read ( kt, 1, sf_icb )
+            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
+         !
+         berg_grid%floating_melt(:,:) = 0._wp
+         !
+         !                                   !* anything that needs to be reset to zero each timestep 
+         CALL icb_dia_step()                 !  for budgets is dealt with here
+         !
+         !                                   !* write out time
+         ll_verbose = .FALSE.
+         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
+    9100 FORMAT('kt= ',i8, ' day= ',i8,' secs=',i8)
+         !
+         !                                   !* copy nemo forcing arrays into iceberg versions with extra halo
+         CALL icb_utl_copy( Kmm )                 ! only necessary for variables not on T points
+         !
+         !
+         !                       !==  process icebergs  ==!
+         !                              !
+                                        CALL icb_clv_flx( kt )   ! Accumulate ice from calving
+         !                              !
+                                        CALL icb_clv( kt )       ! Calve excess stored ice into icebergs
+         !                              !
+         !
+         !                       !==  For each berg, evolve  ==!
+         !
+         IF( ASSOCIATED(first_berg) )   CALL icb_dyn( kt )       ! ice berg dynamics
+   
+         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
+   
+         IF( ASSOCIATED(first_berg) )   CALL icb_thm( kt )       ! Ice berg thermodynamics (melting) + rolling
+         !
+         !
+         !                       !==  diagnostics and output  ==!
+         !
+         !                                   !* For each berg, record trajectory (when needed)
+         ll_sample_traj = .FALSE.
+         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 )
+   
+         !                                   !* Gridded diagnostics
+         !                                   !  To get these iom_put's and those preceding to actually do something
+         !                                   !  use key_xios in cpp file and create content for XML file
+         !
+         CALL iom_put( "calving"           , berg_grid%calving      (:,:)   )  ! 'calving mass input'
+         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'
+         !
+         CALL icb_dia_put()                  !* store mean budgets
+         !
+         !                                   !*  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
          CALL icb_rst_write( kt )