New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
icbstp.F90 in branches/UKMO/dev_r5518_GO6_starthour_obsoper/NEMOGCM/NEMO/OPA_SRC/ICB – NEMO

source: branches/UKMO/dev_r5518_GO6_starthour_obsoper/NEMOGCM/NEMO/OPA_SRC/ICB/icbstp.F90 @ 12555

Last change on this file since 12555 was 12555, checked in by charris, 4 years ago

Changes from GO6 package branch (GMED ticket 450):

svn merge -r 11035:11101 svn+ssh://charris@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/UKMO/dev_r5518_GO6_package

File size: 7.4 KB
Line 
1MODULE icbstp
2
3   !!======================================================================
4   !!                       ***  MODULE  icbstp  ***
5   !! Icebergs:  initialise variables for iceberg tracking
6   !!======================================================================
7   !! History : 3.3.1 !  2010-01  (Martin&Adcroft) Original code
8   !!            -    !  2011-03  (Madec)          Part conversion to NEMO form
9   !!            -    !                            Removal of mapping from another grid
10   !!            -    !  2011-04  (Alderson)       Split into separate modules
11   !!            -    !                            Move budgets to icbdia routine
12   !!            -    !  2011-05  (Alderson)       Add call to copy forcing arrays
13   !!            -    !                            into icb copies with haloes
14   !!----------------------------------------------------------------------
15   !!----------------------------------------------------------------------
16   !!   icb_stp       : start iceberg tracking
17   !!   icb_end       : end   iceberg tracking
18   !!----------------------------------------------------------------------
19   USE par_oce        ! nemo parameters
20   USE dom_oce        ! ocean domain
21   USE sbc_oce        ! ocean surface forcing
22   USE phycst
23   USE in_out_manager ! nemo IO
24   USE lib_mpp
25   USE iom
26   USE fldread
27   USE timing         ! timing
28
29   USE icb_oce        ! define iceberg arrays
30   USE icbini         ! iceberg initialisation routines
31   USE icbutl         ! iceberg utility routines
32   USE icbrst         ! iceberg restart routines
33   USE icbdyn         ! iceberg dynamics (ie advection) routines
34   USE icbclv         ! iceberg calving routines
35   USE icbthm         ! iceberg thermodynamics routines
36   USE icblbc         ! iceberg lateral boundary routines (including mpp)
37   USE icbtrj         ! iceberg trajectory I/O routines
38   USE icbdia         ! iceberg budget
39
40   IMPLICIT NONE
41   PRIVATE
42
43   PUBLIC   icb_stp        ! routine called in sbcmod.F90 module
44   PUBLIC   icb_end        ! routine called in nemogcm.F90 module
45
46   !!----------------------------------------------------------------------
47   !! NEMO/OPA 3.3 , NEMO Consortium (2011)
48   !! $Id$
49   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
50   !!----------------------------------------------------------------------
51CONTAINS
52
53   SUBROUTINE icb_stp( kt )
54      !!----------------------------------------------------------------------
55      !!                  ***  ROUTINE icb_stp  ***
56      !!
57      !! ** Purpose :   iceberg time stepping.
58      !!
59      !! ** Method  : - top level routine to do things in the correct order
60      !!----------------------------------------------------------------------
61      INTEGER, INTENT(in) ::   kt   ! time step index
62      INTEGER             ::   ii   ! loop index
63      !
64      LOGICAL ::   ll_sample_traj, ll_budget, ll_verbose   ! local logical
65      !!----------------------------------------------------------------------
66      !
67      IF( nn_timing == 1 ) CALL timing_start('icb_stp')
68
69      !! start of timestep housekeeping
70
71      nktberg = kt
72
73      IF( nn_test_icebergs < 0 ) THEN      ! read calving data
74         !
75         CALL fld_read ( kt, 1, sf_icb )
76         src_calving(:,:)      = sf_icb(1)%fnow(:,:,1)    ! calving in km^3/year (water equivalent)
77         src_calving_hflx(:,:) = 0._wp                    ! NO heat flux for now
78         !
79      ENDIF
80
81      berg_grid%floating_melt(:,:) = 0._wp
82
83      ! anything that needs to be reset to zero each timestep for budgets is dealt with here
84      CALL icb_dia_step()
85
86      ll_verbose = .FALSE.
87      IF( nn_verbose_write > 0 .AND. &
88          MOD(kt-1,nn_verbose_write ) == 0 )   ll_verbose = nn_verbose_level >= 0
89
90      ! write out time
91      IF( ll_verbose .AND. numicb.NE.-1) WRITE(numicb,9100) nktberg, ndastp, nsec_day
92 9100 FORMAT('kt= ',i8, ' day= ',i8,' secs=',i8)
93
94      ! copy nemo forcing arrays into iceberg versions with extra halo
95      ! only necessary for variables not on T points
96      CALL icb_utl_copy()
97
98      !!----------------------------------------------------------------------
99      !! process icebergs
100
101                                     CALL icb_clv_flx( kt )   ! Accumulate ice from calving
102
103                                     CALL icb_clv()           ! Calve excess stored ice into icebergs
104
105
106!                               !==  For each berg, evolve  ==!
107      !
108      IF( ASSOCIATED(first_berg) )   CALL icb_dyn( kt )       ! ice berg dynamics
109
110      IF( lk_mpp ) THEN          ;   CALL icb_lbc_mpp()       ! Send bergs to other PEs
111      ELSE                       ;   CALL icb_lbc()           ! Deal with any cyclic boundaries in non-mpp case
112      ENDIF
113
114      IF( ASSOCIATED(first_berg) )   CALL icb_thm( kt )       ! Ice berg thermodynamics (melting) + rolling
115
116      !!----------------------------------------------------------------------
117      !! end of timestep housekeeping
118
119      ll_sample_traj = .FALSE.
120      IF( nn_sample_rate > 0 .AND. MOD(kt-1,nn_sample_rate) == 0 )   ll_sample_traj = .TRUE.
121      IF( ll_sample_traj .AND.   &
122          ASSOCIATED(first_berg) )   CALL icb_trj_write( kt )  ! For each berg, record trajectory
123
124      ! Gridded diagnostics
125      ! To get these iom_put's and those preceding to actually do something
126      ! use key_iomput in cpp file and create content for XML file
127
128      CALL iom_put( "calving"           , berg_grid%calving      (:,:)   )  ! 'calving mass input'
129      CALL iom_put( "berg_floating_melt", berg_grid%floating_melt(:,:)   )  ! 'Melt rate of icebergs + bits' , 'kg/m2/s'
130      CALL iom_put( "berg_stored_ice"   , berg_grid%stored_ice   (:,:,:) )  ! 'Accumulated ice mass by class', 'kg'
131
132      ! store mean budgets
133      CALL icb_dia_put()
134
135      ! Dump icebergs to screen
136      if ( nn_verbose_level >= 2 )   CALL icb_utl_print( 'icb_stp, status', kt )
137
138      ! Diagnose budgets
139      ll_budget = .FALSE.
140      IF( nn_verbose_write > 0 .AND. MOD(kt-1,nn_verbose_write) == 0 )   ll_budget = ln_bergdia
141      CALL icb_dia( ll_budget )
142
143      IF( ln_rst_list ) THEN
144         DO ii=1,10
145            IF(nstocklist(ii)==kt) THEN
146               CALL icb_rst_write( kt )
147               EXIT
148            END IF
149         END DO
150      ELSE IF( MOD(kt,nn_stock) == 0 ) THEN
151         CALL icb_rst_write( kt )
152         IF( nn_sample_rate > 0 )   CALL icb_trj_sync()
153      ENDIF
154
155      IF( nn_timing == 1 ) CALL timing_stop('icb_stp')
156      !
157   END SUBROUTINE icb_stp
158
159
160   SUBROUTINE icb_end( kt )
161      !!----------------------------------------------------------------------
162      !!                  ***  ROUTINE icb_end  ***
163      !!
164      !! ** Purpose :   close iceberg files
165      !!
166      !!----------------------------------------------------------------------
167      INTEGER, INTENT( in )  :: kt
168      !!----------------------------------------------------------------------
169
170      ! only write a restart if not done in icb_stp and not using restart list
171      IF( ( MOD(kt,nn_stock) .NE. 0 ) .AND. (.NOT. ln_rst_list) )      &
172           CALL icb_rst_write( kt )
173
174      ! finish with trajectories if they were written
175      IF( nn_sample_rate .GT. 0 ) CALL icb_trj_end()
176
177      IF(lwp .AND. nprint>3)   WRITE(numout,'(a,i6)') 'icebergs: icb_end complete', narea
178      IF(numicb.NE.-1) THEN
179         CALL flush( numicb )
180         CLOSE( numicb )
181      ENDIF
182      !
183   END SUBROUTINE icb_end
184
185   !!-------------------------------------------------------------------------
186
187END MODULE icbstp
Note: See TracBrowser for help on using the repository browser.