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.
icbini.F90 in branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/ICB – NEMO

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/ICB/icbini.F90 @ 11257

Last change on this file since 11257 was 11101, checked in by frrh, 5 years ago

Merge changes from Met Office GMED ticket 450 to reduce unnecessary
text output from NEMO.
This output, which is typically not switchable, is rarely of interest
in normal (non-debugging) runs and simply redunantley consumes extra
file space.
Further, the presence of this text output has been shown to
significantly degrade performance of models which are run during
Met Office HPC RAID (disk) checks.
The new code introduces switches which are configurable via the
changes made in the associated Met Office MOCI ticket 399.

File size: 21.8 KB
RevLine 
[3614]1MODULE icbini
2   !!======================================================================
3   !!                       ***  MODULE  icbini  ***
4   !! Icebergs:  initialise variables for iceberg tracking
5   !!======================================================================
6   !! History :   -   !  2010-01  (T. Martin & A. Adcroft)  Original code
7   !!            3.3  !  2011-03  (G. Madec)  Part conversion to NEMO form ; Removal of mapping from another grid
8   !!             -   !  2011-04  (S. Alderson)  Split into separate modules ; Restore restart routines
9   !!             -   !  2011-05  (S. Alderson)  generate_test_icebergs restored ; new forcing arrays with extra halo ;
10   !!             -   !                          north fold exchange arrays added
11   !!----------------------------------------------------------------------
12   !!----------------------------------------------------------------------
13   !!   icb_init     : initialise icebergs
14   !!   icb_ini_gen  : generate test icebergs
15   !!   icb_nam      : read iceberg namelist
16   !!----------------------------------------------------------------------
17   USE dom_oce        ! ocean domain
18   USE in_out_manager ! IO routines and numout in particular
19   USE lib_mpp        ! mpi library and lk_mpp in particular
[3785]20   USE sbc_oce        ! ocean  : surface boundary condition
21   USE sbc_ice        ! sea-ice: surface boundary condition
[3614]22   USE iom            ! IOM library
23   USE fldread        ! field read
24   USE lbclnk         ! lateral boundary condition - MPP link
25   !
26   USE icb_oce        ! define iceberg arrays
27   USE icbutl         ! iceberg utility routines
28   USE icbrst         ! iceberg restart routines
29   USE icbtrj         ! iceberg trajectory I/O routines
30   USE icbdia         ! iceberg budget routines
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC   icb_init  ! routine called in nemogcm.F90 module
36
[4153]37   CHARACTER(len=100)                                 ::   cn_dir = './'   !: Root directory for location of icb files
38   TYPE(FLD_N)                                        ::   sn_icb          !: information about the calving file to be read
39   TYPE(FLD), PUBLIC, ALLOCATABLE     , DIMENSION(:)  ::   sf_icb          !: structure: file information, fields read
40                                                                           !: used in icbini and icbstp
[3614]41   !!----------------------------------------------------------------------
42   !! NEMO/OPA 3.3 , NEMO Consortium (2011)
[5215]43   !! $Id$
[3614]44   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
45   !!----------------------------------------------------------------------
46CONTAINS
47
48   SUBROUTINE icb_init( pdt, kt )
49      !!----------------------------------------------------------------------
50      !!                  ***  ROUTINE dom_init  ***
51      !!
52      !! ** Purpose :   iceberg initialization.
53      !!
54      !! ** Method  : - read the iceberg namelist
55      !!              - find non-overlapping processor interior since we can only
56      !!                have one instance of a particular iceberg
57      !!              - calculate the destinations for north fold exchanges
58      !!              - setup either test icebergs or calving file
59      !!----------------------------------------------------------------------
60      REAL(wp), INTENT(in) ::   pdt   ! iceberg time-step (rdt*nn_fsbc)
61      INTEGER , INTENT(in) ::   kt    ! time step number
62      !
63      INTEGER ::   ji, jj, jn               ! dummy loop indices
64      INTEGER ::   i1, i2, i3               ! local integers
65      INTEGER ::   ii, inum, ivar           !   -       -
66      INTEGER ::   istat1, istat2, istat3   !   -       -
67      CHARACTER(len=300) ::   cl_sdist      ! local character
68      !!----------------------------------------------------------------------
69      !
70      CALL icb_nam               ! Read and print namelist parameters
71      !
72      IF( .NOT. ln_icebergs )   RETURN
73
74      !                          ! allocate gridded fields
75      IF( icb_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'icb_alloc : unable to allocate arrays' )
76
77      !                          ! open ascii output file or files for iceberg status information
78      !                          ! note that we choose to do this on all processors since we cannot
79      !                          ! predict where icebergs will be ahead of time
[11101]80      numicb=-1
81      IF(nn_verbose_level>0 .AND. nprint>0) THEN
82        CALL ctl_opn( numicb, 'icebergs.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
83      ELSE
84        IF(lwp) CALL ctl_opn( numicb, 'icebergs.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
85      ENDIF
[3614]86
87      ! set parameters (mostly from namelist)
88      !
89      berg_dt         = pdt
90      first_width (:) = SQRT(  rn_initial_mass(:) / ( rn_LoW_ratio * rn_rho_bergs * rn_initial_thickness(:) )  )
91      first_length(:) = rn_LoW_ratio * first_width(:)
92
93      berg_grid%calving      (:,:)   = 0._wp
94      berg_grid%calving_hflx (:,:)   = 0._wp
95      berg_grid%stored_heat  (:,:)   = 0._wp
96      berg_grid%floating_melt(:,:)   = 0._wp
97      berg_grid%maxclass     (:,:)   = nclasses
98      berg_grid%stored_ice   (:,:,:) = 0._wp
99      berg_grid%tmp          (:,:)   = 0._wp
100      src_calving            (:,:)   = 0._wp
101      src_calving_hflx       (:,:)   = 0._wp
102
103      !                          ! domain for icebergs
104      IF( lk_mpp .AND. jpni == 1 )   CALL ctl_stop( 'icbinit: having ONE processor in x currently does not work' )
105      ! NB: the issue here is simply that cyclic east-west boundary condition have not been coded in mpp case
106      ! for the north fold we work out which points communicate by asking
107      ! lbc_lnk to pass processor number (valid even in single processor case)
108      ! borrow src_calving arrays for this
109      !
110      ! pack i and j together using a scaling of a power of 10
111      nicbpack = 10000
112      IF( jpiglo >= nicbpack )   CALL ctl_stop( 'icbini: processor index packing failure' )
113      nicbfldproc(:) = -1
114
115      DO jj = 1, jpj
116         DO ji = 1, jpi
117            src_calving_hflx(ji,jj) = narea
118            src_calving     (ji,jj) = nicbpack * mjg(jj) + mig(ji)
119         END DO
120      END DO
121      CALL lbc_lnk( src_calving_hflx, 'T', 1._wp )
122      CALL lbc_lnk( src_calving     , 'T', 1._wp )
123
124      ! work out interior of processor from exchange array
125      ! first entry with narea for this processor is left hand interior index
126      ! last  entry                               is right hand interior index
[6823]127      jj = nlcj/2
[3614]128      nicbdi = -1
129      nicbei = -1
130      DO ji = 1, jpi
131         i3 = INT( src_calving(ji,jj) )
132         i2 = INT( i3/nicbpack )
133         i1 = i3 - i2*nicbpack
134         i3 = INT( src_calving_hflx(ji,jj) )
135         IF( i1 == mig(ji) .AND. i3 == narea ) THEN
136            IF( nicbdi < 0 ) THEN   ;   nicbdi = ji
137            ELSE                    ;   nicbei = ji
138            ENDIF
139         ENDIF
140      END DO
141      !
142      ! repeat for j direction
[6823]143      ji = nlci/2
[3614]144      nicbdj = -1
145      nicbej = -1
146      DO jj = 1, jpj
147         i3 = INT( src_calving(ji,jj) )
148         i2 = INT( i3/nicbpack )
149         i1 = i3 - i2*nicbpack
150         i3 = INT( src_calving_hflx(ji,jj) )
151         IF( i2 == mjg(jj) .AND. i3 == narea ) THEN
152            IF( nicbdj < 0 ) THEN   ;   nicbdj = jj
153            ELSE                    ;   nicbej = jj
154            ENDIF
155         ENDIF
156      END DO
157      !   
158      ! special for east-west boundary exchange we save the destination index
159      i1 = MAX( nicbdi-1, 1)
[6823]160      i3 = INT( src_calving(i1,nlcj/2) )
[3614]161      jj = INT( i3/nicbpack )
162      ricb_left = REAL( i3 - nicbpack*jj, wp )
163      i1 = MIN( nicbei+1, jpi )
[6823]164      i3 = INT( src_calving(i1,nlcj/2) )
[3614]165      jj = INT( i3/nicbpack )
166      ricb_right = REAL( i3 - nicbpack*jj, wp )
167     
168      ! north fold
169      IF( npolj > 0 ) THEN
170         !
171         ! icebergs in row nicbej+1 get passed across fold
172         nicbfldpts(:)  = INT( src_calving(:,nicbej+1) )
173         nicbflddest(:) = INT( src_calving_hflx(:,nicbej+1) )
174         !
175         ! work out list of unique processors to talk to
176         ! pack them into a fixed size array where empty slots are marked by a -1
177         DO ji = nicbdi, nicbei
178            ii = nicbflddest(ji)
[4990]179            IF( ii .GT. 0 ) THEN     ! Needed because land suppression can mean
180                                     ! that unused points are not set in edge haloes
181               DO jn = 1, jpni
182                  ! work along array until we find an empty slot
183                  IF( nicbfldproc(jn) == -1 ) THEN
184                     nicbfldproc(jn) = ii
185                     EXIT                             !!gm EXIT should be avoided: use DO WHILE expression instead
186                  ENDIF
187                  ! before we find an empty slot, we may find processor number is already here so we exit
188                  IF( nicbfldproc(jn) == ii ) EXIT
189               END DO
190            ENDIF
[3614]191         END DO
192      ENDIF
193      !
[11101]194      IF( nn_verbose_level > 0 .AND. numicb.NE.-1) THEN
[3614]195         WRITE(numicb,*) 'processor ', narea
196         WRITE(numicb,*) 'jpi, jpj   ', jpi, jpj
197         WRITE(numicb,*) 'nldi, nlei ', nldi, nlei
198         WRITE(numicb,*) 'nldj, nlej ', nldj, nlej
199         WRITE(numicb,*) 'berg i interior ', nicbdi, nicbei
200         WRITE(numicb,*) 'berg j interior ', nicbdj, nicbej
201         WRITE(numicb,*) 'berg left       ', ricb_left
202         WRITE(numicb,*) 'berg right      ', ricb_right
[6823]203         jj = nlcj/2
[3614]204         WRITE(numicb,*) "central j line:"
205         WRITE(numicb,*) "i processor"
206         WRITE(numicb,*) (INT(src_calving_hflx(ji,jj)), ji=1,jpi)
207         WRITE(numicb,*) "i point"
208         WRITE(numicb,*) (INT(src_calving(ji,jj)), ji=1,jpi)
[6823]209         ji = nlci/2
[3614]210         WRITE(numicb,*) "central i line:"
211         WRITE(numicb,*) "j processor"
212         WRITE(numicb,*) (INT(src_calving_hflx(ji,jj)), jj=1,jpj)
213         WRITE(numicb,*) "j point"
214         WRITE(numicb,*) (INT(src_calving(ji,jj)), jj=1,jpj)
215         IF( npolj > 0 ) THEN
216            WRITE(numicb,*) 'north fold destination points '
217            WRITE(numicb,*) nicbfldpts
218            WRITE(numicb,*) 'north fold destination procs  '
219            WRITE(numicb,*) nicbflddest
[4990]220            WRITE(numicb,*) 'north fold destination proclist  '
221            WRITE(numicb,*) nicbfldproc
[3614]222         ENDIF
223         CALL flush(numicb)
224      ENDIF
225     
226      src_calving     (:,:) = 0._wp
227      src_calving_hflx(:,:) = 0._wp
228
229      ! assign each new iceberg with a unique number constructed from the processor number
230      ! and incremented by the total number of processors
231      num_bergs(:) = 0
232      num_bergs(1) = narea - jpnij
233
234      ! when not generating test icebergs we need to setup calving file
235      IF( nn_test_icebergs < 0 ) THEN
236         !
237         ! maximum distribution class array does not change in time so read it once
238         cl_sdist = TRIM( cn_dir )//TRIM( sn_icb%clname )
239         CALL iom_open ( cl_sdist, inum )                              ! open file
240         ivar = iom_varid( inum, 'maxclass', ldstop=.FALSE. )
241         IF( ivar > 0 ) THEN
242            CALL iom_get  ( inum, jpdom_data, 'maxclass', src_calving )   ! read the max distribution array
243            berg_grid%maxclass(:,:) = INT( src_calving )
244            src_calving(:,:) = 0._wp
245         ENDIF
246         CALL iom_close( inum )                                     ! close file
247         !
[11101]248         IF(numicb.NE.-1) THEN
249            WRITE(numicb,*)
250            WRITE(numicb,*) '          calving read in a file'
251         ENDIF
[3614]252         ALLOCATE( sf_icb(1), STAT=istat1 )         ! Create sf_icb structure (calving)
253         ALLOCATE( sf_icb(1)%fnow(jpi,jpj,1), STAT=istat2 )
254         ALLOCATE( sf_icb(1)%fdta(jpi,jpj,1,2), STAT=istat3 )
255         IF( istat1+istat2+istat3 > 0 ) THEN
256            CALL ctl_stop( 'sbc_icb: unable to allocate sf_icb structure' )   ;   RETURN
257         ENDIF
258         !                                          ! fill sf_icb with the namelist (sn_icb) and control print
259         CALL fld_fill( sf_icb, (/ sn_icb /), cn_dir, 'icb_init', 'read calving data', 'namicb' )
260         !
261      ENDIF
262
263      IF( .NOT.ln_rstart ) THEN
264         IF( nn_test_icebergs > 0 )   CALL icb_ini_gen()
265      ELSE
266         IF( nn_test_icebergs > 0 ) THEN
267            CALL icb_ini_gen()
268         ELSE
269            CALL icb_rst_read()
270            l_restarted_bergs = .TRUE.
271         ENDIF
272      ENDIF
273      !
274      IF( nn_sample_rate .GT. 0 ) CALL icb_trj_init( nitend )
275      !
276      CALL icb_dia_init()
277      !
278      IF( nn_verbose_level >= 2 )   CALL icb_utl_print('icb_init, initial status', nit000-1)
279      !
280   END SUBROUTINE icb_init
281
[3785]282
[3614]283   SUBROUTINE icb_ini_gen()
284      !!----------------------------------------------------------------------
285      !!                  ***  ROUTINE icb_ini_gen  ***
286      !!
287      !! ** Purpose :   iceberg generation
288      !!
289      !! ** Method  : - at each grid point of the test box supplied in the namelist
290      !!                generate an iceberg in one class determined by the value of
291      !!                parameter nn_test_icebergs
292      !!----------------------------------------------------------------------
293      INTEGER                         ::   ji, jj, ibergs
294      TYPE(iceberg)                   ::   localberg ! NOT a pointer but an actual local variable
295      TYPE(point)                     ::   localpt
296      INTEGER                         ::   iyr, imon, iday, ihr, imin, isec
297      INTEGER                         ::   iberg
298      !!----------------------------------------------------------------------
299
300      ! For convenience
301      iberg = nn_test_icebergs
302
303      ! call get_date(Time, iyr, imon, iday, ihr, imin, isec)
304      ! Convert nemo time variables from dom_oce into local versions
305      iyr  = nyear
306      imon = nmonth
307      iday = nday
308      ihr = INT(nsec_day/3600)
309      imin = INT((nsec_day-ihr*3600)/60)
310      isec = nsec_day - ihr*3600 - imin*60
311
312      ! no overlap for icebergs since we want only one instance of each across the whole domain
313      ! so restrict area of interest
314      ! use tmask here because tmask_i has been doctored on one side of the north fold line
315
316      DO jj = nicbdj, nicbej
317         DO ji = nicbdi, nicbei
318            IF( tmask(ji,jj,1) > 0._wp        .AND.                                       &
319                rn_test_box(1) < glamt(ji,jj) .AND. glamt(ji,jj) < rn_test_box(2) .AND.   &
320                rn_test_box(3) < gphit(ji,jj) .AND. gphit(ji,jj) < rn_test_box(4) ) THEN
321               localberg%mass_scaling = rn_mass_scaling(iberg)
322               localpt%xi = REAL( mig(ji), wp )
323               localpt%yj = REAL( mjg(jj), wp )
324               localpt%lon = icb_utl_bilin(glamt, localpt%xi, localpt%yj, 'T' )
325               localpt%lat = icb_utl_bilin(gphit, localpt%xi, localpt%yj, 'T' )
326               localpt%mass      = rn_initial_mass     (iberg)
327               localpt%thickness = rn_initial_thickness(iberg)
328               localpt%width  = first_width (iberg)
329               localpt%length = first_length(iberg)
330               localpt%year = iyr
331               localpt%day = REAL(iday,wp)+(REAL(ihr,wp)+REAL(imin,wp)/60._wp)/24._wp
332               localpt%mass_of_bits = 0._wp
333               localpt%heat_density = 0._wp
334               localpt%uvel = 0._wp
335               localpt%vvel = 0._wp
336               CALL icb_utl_incr()
337               localberg%number(:) = num_bergs(:)
338               call icb_utl_add(localberg, localpt)
339            ENDIF
340         END DO
341      END DO
342      !
343      ibergs = icb_utl_count()
344      IF( lk_mpp ) CALL mpp_sum(ibergs)
[11101]345      IF(numicb.NE.-1) WRITE(numicb,'(a,i6,a)') 'diamonds, icb_ini_gen: ',ibergs,' were generated'
[3614]346      !
347   END SUBROUTINE icb_ini_gen
348
[3785]349
[3614]350   SUBROUTINE icb_nam
351      !!----------------------------------------------------------------------
352      !!                     ***  ROUTINE icb_nam  ***
353      !!
354      !! ** Purpose :   read iceberg namelist and print the variables.
355      !!
356      !! ** input   : - namberg namelist
357      !!----------------------------------------------------------------------
358      INTEGER  ::   jn      ! dummy loop indices
[4147]359      INTEGER  ::   ios     ! Local integer output status for namelist read
[3614]360      REAL(wp) ::   zfact   ! local scalar
361      !
362      NAMELIST/namberg/ ln_icebergs    , ln_bergdia     , nn_sample_rate      , rn_initial_mass      ,   &
363         &              rn_distribution, rn_mass_scaling, rn_initial_thickness, nn_verbose_write     ,   &
364         &              rn_rho_bergs   , rn_LoW_ratio   , nn_verbose_level    , ln_operator_splitting,   &
365         &              rn_bits_erosion_fraction        , rn_sicn_shift       , ln_passive_mode      ,   &
366         &              ln_time_average_weight          , nn_test_icebergs    , rn_test_box          ,   &
367         &              rn_speed_limit , cn_dir, sn_icb
368      !!----------------------------------------------------------------------
369
[4147]370#if !defined key_agrif
371      REWIND( numnam_ref )              ! Namelist namberg in reference namelist : Iceberg parameters
372      READ  ( numnam_ref, namberg, IOSTAT = ios, ERR = 901)
373901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namberg in reference namelist', lwp )
374      REWIND( numnam_cfg )              ! Namelist namberg in configuration namelist : Iceberg parameters
375      READ  ( numnam_cfg, namberg, IOSTAT = ios, ERR = 902 )
376902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namberg in configuration namelist', lwp )
[11101]377      IF(lwm .AND. nprint > 2) WRITE ( numond, namberg )
[4147]378#else
379      IF(lwp) THEN
380         WRITE(numout,*)
381         WRITE(numout,*) 'icbini :   AGRIF is not compatible with namelist namberg :  '
382         WRITE(numout,*) '         definition of rn_initial_mass(nclasses) with nclasses as PARAMETER '
383         WRITE(numout,*) ' namelist namberg not read'
384      ENDIF
385      ln_icebergs = .false.     
386#endif   
[3614]387      IF( .NOT. ln_icebergs ) THEN   ! no icebergs
388         IF(lwp) THEN
389            WRITE(numout,*)
[4147]390            WRITE(numout,*) 'icbini :   Namelist namberg ln_icebergs = F , NO icebergs used'
[3614]391            WRITE(numout,*) '~~~~~~~~ '
392         ENDIF
393         RETURN
394      ENDIF
395
396      IF( nn_test_icebergs > nclasses ) THEN
397          IF(lwp) WRITE(numout,*) 'Resetting nn_test_icebergs to ', nclasses
398          nn_test_icebergs = nclasses
399      ENDIF
400
401      zfact = SUM( rn_distribution )
402      IF( zfact < 1._wp ) THEN
403         IF( zfact <= 0._wp ) THEN
[3785]404           
[3614]405         ELSE
406            rn_distribution(:) = rn_distribution(:) / zfact
407            CALL ctl_warn( 'icb_nam: sum of berg input distribution not equal to one and so RESCALED' )
408         ENDIF
409      ENDIF
410
[4990]411!     IF( lk_lim3 .AND. ln_icebergs ) THEN
412!        CALL ctl_stop( 'icb_nam: the use of ICB with LIM3 not allowed. ice thickness missing in ICB' )
413!     ENDIF
[3785]414
[3614]415      IF(lwp) THEN                  ! control print
416         WRITE(numout,*)
417         WRITE(numout,*) 'icb_nam : iceberg initialization through namberg namelist read'
418         WRITE(numout,*) '~~~~~~~~ '
419         WRITE(numout,*) '   Calculate budgets                                            ln_bergdia       = ', ln_bergdia
420         WRITE(numout,*) '   Period between sampling of position for trajectory storage   nn_sample_rate = ', nn_sample_rate
421         WRITE(numout,*) '   Mass thresholds between iceberg classes (kg)                 rn_initial_mass     ='
422         DO jn=1,nclasses
423            WRITE(numout,'(a,f15.2)') '                                                                ',rn_initial_mass(jn)
424         ENDDO
425         WRITE(numout,*) '   Fraction of calving to apply to this class (non-dim)         rn_distribution     ='
426         DO jn = 1, nclasses
427            WRITE(numout,'(a,f10.2)') '                                                                ',rn_distribution(jn)
428         END DO
429         WRITE(numout,*) '   Ratio between effective and real iceberg mass (non-dim)      rn_mass_scaling     = '
430         DO jn = 1, nclasses
431            WRITE(numout,'(a,f10.2)') '                                                                ',rn_mass_scaling(jn)
432         END DO
433         WRITE(numout,*) '   Total thickness of newly calved bergs (m)                    rn_initial_thickness = '
434         DO jn = 1, nclasses
435            WRITE(numout,'(a,f10.2)') '                                                                ',rn_initial_thickness(jn)
436         END DO
437         WRITE(numout,*) '   Timesteps between verbose messages                           nn_verbose_write    = ', nn_verbose_write
438
439         WRITE(numout,*) '   Density of icebergs                           rn_rho_bergs  = ', rn_rho_bergs
440         WRITE(numout,*) '   Initial ratio L/W for newly calved icebergs   rn_LoW_ratio  = ', rn_LoW_ratio
441         WRITE(numout,*) '   Turn on more verbose output                          level  = ', nn_verbose_level
442         WRITE(numout,*) '   Use first order operator splitting for thermodynamics    ',   &
443            &                    'use_operator_splitting = ', ln_operator_splitting
444         WRITE(numout,*) '   Fraction of erosion melt flux to divert to bergy bits    ',   &
445            &                    'bits_erosion_fraction = ', rn_bits_erosion_fraction
446
447         WRITE(numout,*) '   Shift of sea-ice concentration in erosion flux modulation ',   &
448            &                    '(0<sicn_shift<1)    rn_sicn_shift  = ', rn_sicn_shift
449         WRITE(numout,*) '   Do not add freshwater flux from icebergs to ocean                ',   &
450            &                    '                  passive_mode            = ', ln_passive_mode
451         WRITE(numout,*) '   Time average the weight on the ocean   time_average_weight       = ', ln_time_average_weight
452         WRITE(numout,*) '   Create icebergs in absence of a restart file   nn_test_icebergs  = ', nn_test_icebergs
453         WRITE(numout,*) '                   in lon/lat box                                   = ', rn_test_box
454         WRITE(numout,*) '   CFL speed limit for a berg            speed_limit                = ', rn_speed_limit
455         WRITE(numout,*) '   Writing Iceberg status information to icebergs.stat file        '
456      ENDIF
457      !
458   END SUBROUTINE icb_nam
459
460   !!======================================================================
461END MODULE icbini
Note: See TracBrowser for help on using the repository browser.