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.
icbrun.F90 in branches/2012/dev_r3337_NOCS10_ICB/NEMOGCM/NEMO/OPA_SRC/ICB – NEMO

source: branches/2012/dev_r3337_NOCS10_ICB/NEMOGCM/NEMO/OPA_SRC/ICB/icbrun.F90 @ 3372

Last change on this file since 3372 was 3372, checked in by sga, 12 years ago

NEMO branch dev_r3337_NOCS10_ICB: change all routine names and create more Gurvanistic havoc

File size: 8.6 KB
Line 
1MODULE icbrun
2
3   !!======================================================================
4   !!                       ***  MODULE  icbrun  ***
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
27   USE icb_oce        ! define iceberg arrays
28   USE icbini         ! iceberg initialisation routines
29   USE icbutl         ! iceberg utility routines
30   USE icbrst         ! iceberg restart routines
31   USE icbdyn         ! iceberg dynamics (ie advection) routines
32   USE icbclv         ! iceberg calving routines
33   USE icbthm         ! iceberg thermodynamics routines
34   USE icblbc         ! iceberg lateral boundary routines (including mpp)
35   USE icbtrj         ! iceberg trajectory I/O routines
36   USE icbdia         ! iceberg budget
37
38   IMPLICIT NONE
39   PRIVATE
40
41   PUBLIC   icb_stp        ! routine called in sbcmod.F90 module
42   PUBLIC   icb_end        ! routine called in nemogcm.F90 module
43
44   !!----------------------------------------------------------------------
45   !! NEMO/OPA 3.3 , NEMO Consortium (2011)
46   !! $Id:$
47   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
48   !!----------------------------------------------------------------------
49CONTAINS
50
51   SUBROUTINE icb_stp( kt )
52      !!----------------------------------------------------------------------
53      !!                  ***  ROUTINE icb_stp  ***
54      !!
55      !! ** Purpose :   iceberg time stepping.
56      !!
57      !! ** Method  : - blah blah
58      !!----------------------------------------------------------------------
59      INTEGER, INTENT(in) ::   kt   ! time step index
60      !
61      INTEGER ::   iyr, imon, iday, ihr, imin, isec        ! local integers
62      LOGICAL ::   ll_sample_traj, ll_budget, ll_verbose   ! local logical
63      !!----------------------------------------------------------------------
64      !! start of timestep housekeeping
65
66      nktberg = kt
67
68      IF( nn_test_icebergs < 0 ) THEN      ! read calving data
69         !
70         CALL fld_read ( kt, 1, sf_icb )
71         src_calving(:,:)      = sf_icb(1)%fnow(:,:,1)    ! calving in km^3/year (water equivalent)
72         src_calving_hflx(:,:) = 0._wp                    ! NO heat flux for now
73         !
74      ENDIF
75
76      berg_grid%floating_melt(:,:) = 0._wp
77
78      ! anything that needs to be reset to zero each timestep for budgets is dealt with here
79      CALL icb_dia_step()
80
81      ! Manage time
82      ! Convert nemo time variables from dom_oce into local versions
83      ! Note that yearday function assumes 365 day year!!
84      iyr = nyear
85      imon = nmonth
86      iday = nday
87      ihr = INT(nsec_day/3600)
88      imin = INT((nsec_day-ihr*3600)/60)
89      isec = nsec_day - ihr*3600 - imin*60
90      current_year    = iyr
91      current_yearday = icb_utl_yearday(imon, iday, ihr, imin, isec)
92
93      ll_verbose = .FALSE.
94      IF( nn_verbose_write > 0 .AND. &
95          MOD(kt-1,nn_verbose_write ) == 0 )   ll_verbose = nn_verbose_level >= 0
96      IF( ll_verbose ) WRITE(numicb,9100) iyr, imon, iday, ihr, imin, isec, &
97                                        current_year, current_yearday
98 9100 FORMAT('y,m,d=',3i5,' h,m,s=',3i5,' yr,yrdy=',i5,f8.3)
99
100      ! copy nemo forcing arrays into iceberg versions with extra halo
101      ! only necessary for variables not on T points
102      CALL icb_utl_copy()
103
104      !!----------------------------------------------------------------------
105      !! process icebergs
106
107                                     CALL icb_clv_flx( kt )   ! Accumulate ice from calving
108
109                                     CALL icb_clv()           ! Calve excess stored ice into icebergs
110
111
112!                               !==  For each berg, evolve  ==!
113      !
114      IF( ASSOCIATED(first_berg) )   CALL icb_dyn()           ! ice berg dynamics
115
116      IF( lk_mpp ) THEN          ;   CALL icb_lbc_mpp()       ! Send bergs to other PEs
117      ELSE                       ;   CALL icb_lbc()           ! Deal with any cyclic boundaries in non-mpp case
118      ENDIF
119
120      IF( ASSOCIATED(first_berg) )   CALL icb_thm( kt )       ! Ice berg thermodynamics (melting) + rolling
121
122      !!----------------------------------------------------------------------
123      !! end of timestep housekeeping
124
125      ll_sample_traj = .FALSE.
126      IF( nn_sample_rate > 0 .AND. MOD(kt-1,nn_sample_rate) == 0 )   ll_sample_traj = .TRUE.
127      IF( ll_sample_traj .AND.   &
128          ASSOCIATED(first_berg) )   CALL icb_trj_write( kt )  ! For each berg, record trajectory
129
130      ! Gridded diagnostics
131      ! To get these iom_put's and those preceding to actually do something
132      ! use key_iomput in cpp file and create content for XML file
133
134      CALL iom_put( "calving"           , berg_grid%calving      (:,:)   )  ! 'calving mass input'
135      CALL iom_put( "berg_floating_melt", berg_grid%floating_melt(:,:)   )  ! 'Melt rate of icebergs + bits' , 'kg/m2/s'
136      CALL iom_put( "berg_stored_ice"   , berg_grid%stored_ice   (:,:,:) )  ! 'Accumulated ice mass by class', 'kg'
137
138      ! store mean budgets
139      CALL icb_dia_put()
140
141      ! Dump icebergs to screen
142      if ( nn_verbose_level >= 2 )   CALL icb_utl_print( 'icb_stp, status', kt )
143
144      ! Diagnose budgets
145      ll_budget = .FALSE.
146      IF( nn_verbose_write > 0 .AND. MOD(kt-1,nn_verbose_write) == 0 )   ll_budget = ln_bergdia
147      CALL icb_dia( ll_budget )
148
149      IF( MOD(kt,nn_stock) == 0 ) THEN
150         CALL icb_rst_write( kt )
151         IF( nn_sample_rate > 0 )   CALL icb_trj_sync()
152      ENDIF
153
154      !
155   END SUBROUTINE icb_stp
156
157
158   SUBROUTINE icb_end( kt )
159      !!----------------------------------------------------------------------
160      !!                  ***  ROUTINE icb_end  ***
161      !!
162      !! ** Purpose :   close iceberg files
163      !!
164      !!----------------------------------------------------------------------
165      INTEGER, INTENT( in )  :: kt
166      !
167      TYPE(iceberg), POINTER :: this, next
168      !!----------------------------------------------------------------------
169
170      ! expanded arrays for bilinear interpolation
171      DEALLOCATE( uo_e )
172      DEALLOCATE( vo_e )
173      DEALLOCATE( ff_e )
174      DEALLOCATE( ua_e )
175      DEALLOCATE( va_e )
176#if defined key_lim2 || defined key_lim3
177      DEALLOCATE( ui_e )
178      DEALLOCATE( vi_e )
179#endif
180      DEALLOCATE( ssh_e )
181
182      DEALLOCATE( nicbfldpts )
183      DEALLOCATE( nicbflddest )
184      DEALLOCATE( nicbfldproc )
185
186      IF (.NOT.ASSOCIATED(berg_grid)) RETURN
187
188      ! only write a restart if not done in icb_stp
189      IF( MOD(kt,nn_stock) .NE. 0 ) CALL icb_rst_write( kt )
190
191      ! finish with trajectories if they were written
192      IF( nn_sample_rate .GT. 0 ) CALL icb_trj_end()
193
194      ! Delete bergs and structures
195      this=>first_berg
196      DO WHILE (ASSOCIATED(this))
197        next=>this%next
198        CALL icb_utl_destroy(this)
199        this=>next
200      END DO
201
202      CALL icb_dia_end()
203
204      DEALLOCATE(berg_grid%calving)
205      DEALLOCATE(berg_grid%calving_hflx)
206      DEALLOCATE(berg_grid%stored_heat)
207      DEALLOCATE(berg_grid%floating_melt)
208      DEALLOCATE(berg_grid%maxclass)
209      DEALLOCATE(berg_grid%tmp)
210      DEALLOCATE(berg_grid%stored_ice)
211      DEALLOCATE(berg_grid)
212
213      DEALLOCATE(first_width)
214      DEALLOCATE(first_length)
215
216      IF(lwp)   WRITE(numout,'(a,i6)') 'icebergs: icb_end complete', narea
217      CALL flush( numicb )
218      CLOSE( numicb )
219      !
220   END SUBROUTINE icb_end
221
222   !!-------------------------------------------------------------------------
223
224END MODULE icbrun
Note: See TracBrowser for help on using the repository browser.