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.
icbrst.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/icbrst.F90 @ 11101

Last change on this file since 11101 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: 19.8 KB
Line 
1MODULE icbrst
2
3   !!======================================================================
4   !!                       ***  MODULE  icbrst  ***
5   !! Ocean physics:  read and write iceberg restart files
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   !!            -    !  2011-04  (Alderson)       Restore restart routine
12   !!            -    !                            Currently needs a fixed processor
13   !!            -    !                            layout between restarts
14   !!            -    !  2015-11  Dave Storkey     Convert icb_rst_read to use IOM so can
15   !!                                              read single restart files
16   !!----------------------------------------------------------------------
17   !!----------------------------------------------------------------------
18   !!   icb_rst_read    : read restart file
19   !!   icb_rst_write   : write restart file
20   !!----------------------------------------------------------------------
21   USE par_oce        ! NEMO parameters
22   USE phycst         ! for rday
23   USE dom_oce        ! NEMO domain
24   USE in_out_manager ! NEMO IO routines
25   USE ioipsl, ONLY : ju2ymds    ! for calendar
26   USE lib_mpp        ! NEMO MPI library, lk_mpp in particular
27   USE netcdf         ! netcdf routines for IO
28   USE iom
29   USE icb_oce        ! define iceberg arrays
30   USE icbutl         ! iceberg utility routines
31   USE timing
32
33   IMPLICIT NONE
34   PRIVATE
35
36   PUBLIC   icb_rst_read    ! routine called in icbini.F90 module
37   PUBLIC   icb_rst_write   ! routine called in icbstp.F90 module
38   
39   INTEGER ::   nlonid, nlatid, nxid, nyid, nuvelid, nvvelid
40   INTEGER ::   nmassid, nthicknessid, nwidthid, nlengthid
41   INTEGER ::   nyearid, ndayid
42   INTEGER ::   nscaling_id, nmass_of_bits_id, nheat_density_id, numberid
43   INTEGER ::   nsiceid, nsheatid, ncalvid, ncalvhid, nkountid
44   INTEGER ::   nret, ncid, nc_dim
45   
46   INTEGER,  DIMENSION(3)                  :: nstrt3, nlngth3
47
48   !!----------------------------------------------------------------------
49   !! NEMO/OPA 3.3 , NEMO Consortium (2011)
50   !! $Id$
51   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
52   !!----------------------------------------------------------------------
53CONTAINS
54
55   SUBROUTINE icb_rst_read()
56      !!----------------------------------------------------------------------
57      !!                 ***  SUBROUTINE icb_rst_read  ***
58      !!
59      !! ** Purpose :   read a iceberg restart file
60      !!      NB: for this version, we just read back in the restart for this processor
61      !!      so we cannot change the processor layout currently with iceberg code
62      !!----------------------------------------------------------------------
63      INTEGER                      ::   idim, ivar, iatt
64      INTEGER                      ::   jn, iunlim_dim, ibergs_in_file
65      INTEGER                      ::   ii,ij,iclass
66      REAL(wp), DIMENSION(nkounts) ::   zdata     
67      LOGICAL                      ::   ll_found_restart
68      CHARACTER(len=256)           ::   cl_path
69      CHARACTER(len=256)           ::   cl_filename
70      CHARACTER(len=NF90_MAX_NAME) ::   cl_dname
71      TYPE(iceberg)                ::   localberg ! NOT a pointer but an actual local variable
72      TYPE(point)                  ::   localpt   ! NOT a pointer but an actual local variable
73      !!----------------------------------------------------------------------
74      IF(nn_timing == 2)  CALL timing_start('iom_rstget')
75      ! Find a restart file. Assume iceberg restarts in same directory as ocean restarts
76      ! and are called TRIM(cn_ocerst)//'_icebergs'
77      cl_path = TRIM(cn_ocerst_indir)
78      IF( cl_path(LEN_TRIM(cl_path):) /= '/' ) cl_path = TRIM(cl_path) // '/'
79      cl_filename = TRIM(cn_ocerst_in)//'_icebergs'
80      CALL iom_open( TRIM(cl_path)//cl_filename, ncid )
81
82      IF( iom_file(ncid)%iduld .GE. 0) THEN
83
84         ibergs_in_file = iom_file(ncid)%lenuld
85         DO jn = 1,ibergs_in_file
86
87            ! iom_get treats the unlimited dimension as time. Here the unlimited dimension
88            ! is the iceberg index, but we can still use the ktime keyword to get the iceberg we want.
89
90            CALL iom_get( ncid, 'xi'     ,localpt%xi  , ktime=jn )
91            CALL iom_get( ncid, 'yj'     ,localpt%yj  , ktime=jn )
92
93            ii = INT( localpt%xi + 0.5 )
94            ij = INT( localpt%yj + 0.5 )
95            ! Only proceed if this iceberg is on the local processor (excluding halos).
96            IF ( ii .GE. nldi+nimpp-1 .AND. ii .LE. nlei+nimpp-1 .AND. &
97           &     ij .GE. nldj+njmpp-1 .AND. ij .LE. nlej+njmpp-1 ) THEN           
98
99               CALL iom_get( ncid, jpdom_unknown, 'number'       , zdata(:) , ktime=jn, kstart=(/1/), kcount=(/nkounts/) )
100               localberg%number(:) = INT(zdata(:))
101               CALL iom_get( ncid, 'mass_scaling' , localberg%mass_scaling, ktime=jn )
102               CALL iom_get( ncid, 'lon'          , localpt%lon           , ktime=jn )
103               CALL iom_get( ncid, 'lat'          , localpt%lat           , ktime=jn )
104               CALL iom_get( ncid, 'uvel'         , localpt%uvel          , ktime=jn )
105               CALL iom_get( ncid, 'vvel'         , localpt%vvel          , ktime=jn )
106               CALL iom_get( ncid, 'mass'         , localpt%mass          , ktime=jn )
107               CALL iom_get( ncid, 'thickness'    , localpt%thickness     , ktime=jn )
108               CALL iom_get( ncid, 'width'        , localpt%width         , ktime=jn )
109               CALL iom_get( ncid, 'length'       , localpt%length        , ktime=jn )
110               CALL iom_get( ncid, 'year'         , zdata(1)              , ktime=jn )
111               localpt%year = INT(zdata(1))
112               CALL iom_get( ncid, 'day'          , localpt%day           , ktime=jn )
113               CALL iom_get( ncid, 'mass_of_bits' , localpt%mass_of_bits  , ktime=jn )
114               CALL iom_get( ncid, 'heat_density' , localpt%heat_density  , ktime=jn )
115
116               !
117               CALL icb_utl_add( localberg, localpt )
118
119            ENDIF
120
121         END DO
122
123      ENDIF 
124
125      ! Gridded variables
126      CALL iom_get( ncid, jpdom_autoglo,    'calving'     , src_calving  )
127      CALL iom_get( ncid, jpdom_autoglo,    'calving_hflx', src_calving_hflx  )
128      CALL iom_get( ncid, jpdom_autoglo,    'stored_heat' , berg_grid%stored_heat  )
129      CALL iom_get( ncid, jpdom_autoglo_xy, 'stored_ice'  , berg_grid%stored_ice, kstart=(/1,1,1/), kcount=(/1,1,nclasses/) )
130     
131      CALL iom_get( ncid, jpdom_unknown, 'kount' , zdata(:) )
132      num_bergs(:) = INT(zdata(:))
133
134      ! Sanity check
135      jn = icb_utl_count()
136      IF (nprint > 0 .AND. lwp)   &
137         WRITE(numout,'(2(a,i5))') 'icebergs, read_restart_bergs: # bergs =',jn,' on PE',narea-1
138      IF( lk_mpp ) THEN
139         ! Only mpp_sum ibergs_in_file if we are reading from multiple restart files.
140         IF( INDEX(iom_file(ncid)%name,'icebergs.nc' ) .EQ. 0 ) CALL mpp_sum(ibergs_in_file)
141         CALL mpp_sum(jn)
142      ENDIF
143      IF(lwp .AND. nprint > 1)   &
144         &    WRITE(numout,'(a,i5,a,i5,a)') 'icebergs, read_restart_bergs: there were',ibergs_in_file,   &
145         &                                    ' bergs in the restart file and', jn,' bergs have been read'
146      !
147      ! Finish up
148      CALL iom_close( ncid )
149      !
150      IF(nn_timing == 2)  CALL timing_stop('iom_rstget')
151      IF( lwp .and. nprint >= 0)  WRITE(numout,'(a)') 'icebergs, read_restart_bergs: completed'
152      !
153   END SUBROUTINE icb_rst_read
154
155
156   SUBROUTINE icb_rst_write( kt )
157      !!----------------------------------------------------------------------
158      !!                 ***  SUBROUTINE icb_rst_write  ***
159      !!
160      !!----------------------------------------------------------------------
161      INTEGER, INTENT( in ) :: kt
162      !
163      INTEGER ::   jn   ! dummy loop index
164      INTEGER ::   ix_dim, iy_dim, ik_dim, in_dim
165      INTEGER             ::   iyear, imonth, iday
166      REAL (wp)           ::   zsec
167      REAL (wp)           ::   zfjulday
168      CHARACTER(len=256)  :: cl_path
169      CHARACTER(len=256)  :: cl_filename
170      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character
171      TYPE(iceberg), POINTER :: this
172      TYPE(point)  , POINTER :: pt
173      !!----------------------------------------------------------------------
174      IF(nn_timing == 2)  CALL timing_start('iom_rstput')
175      ! Assume we write iceberg restarts to same directory as ocean restarts.
176      cl_path = TRIM(cn_ocerst_outdir)
177      IF( cl_path(LEN_TRIM(cl_path):) /= '/' ) cl_path = TRIM(cl_path) // '/'
178      IF ( ln_rstdate ) THEN
179         zfjulday = fjulday + rdttra(1) / rday
180         IF( ABS(zfjulday - REAL(NINT(zfjulday),wp)) < 0.1 / rday )   zfjulday = REAL(NINT(zfjulday),wp)   ! avoid truncation error
181         CALL ju2ymds( zfjulday, iyear, imonth, iday, zsec )           
182         WRITE(clkt, '(i4.4,2i2.2)') iyear, imonth, iday
183      ELSE
184         IF( kt > 999999999 ) THEN   ;   WRITE(clkt, *       ) kt
185         ELSE                        ;   WRITE(clkt, '(i8.8)') kt
186         ENDIF
187      ENDIF
188      IF( lk_mpp ) THEN
189         WRITE(cl_filename,'(A,"_icebergs_",A,"_restart_",I4.4,".nc")') TRIM(cexper), TRIM(ADJUSTL(clkt)), narea-1
190      ELSE
191         WRITE(cl_filename,'(A,"_icebergs_",A,"_restart.nc")') TRIM(cexper), TRIM(ADJUSTL(clkt))
192      ENDIF
193      IF (nprint > 0 .AND. lwp) &
194                       WRITE(numout,'(2a)') 'icebergs, write_restart: creating ',TRIM(cl_path)//TRIM(cl_filename)
195
196      nret = NF90_CREATE(TRIM(cl_path)//TRIM(cl_filename), NF90_CLOBBER, ncid)
197      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_create failed')
198
199      ! Dimensions
200      nret = NF90_DEF_DIM(ncid, 'x', jpi, ix_dim)
201      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim x failed')
202
203      nret = NF90_DEF_DIM(ncid, 'y', jpj, iy_dim)
204      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim y failed')
205
206      nret = NF90_DEF_DIM(ncid, 'c', nclasses, nc_dim)
207      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim c failed')
208
209      nret = NF90_DEF_DIM(ncid, 'k', nkounts, ik_dim)
210      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim k failed')
211
212      ! global attributes
213      IF( lk_mpp ) THEN
214         ! Set domain parameters (assume jpdom_local_full)
215         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_number_total'   , jpnij              )
216         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_number'         , narea-1            )
217         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_dimensions_ids' , (/1     , 2     /) )
218         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_global'    , (/jpiglo, jpjglo/) )
219         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_local'     , (/jpi   , jpj   /) )
220         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_first' , (/nimpp , njmpp /) )
221         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_last'  , (/nimpp + jpi - 1 , njmpp + jpj - 1  /) )
222         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_start', (/nldi - 1        , nldj - 1         /) )
223         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_end'  , (/jpi - nlei      , jpj - nlej       /) )
224         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_type'           , 'BOX'              )
225      ENDIF
226     
227      IF (associated(first_berg)) then
228         nret = NF90_DEF_DIM(ncid, 'n', NF90_UNLIMITED, in_dim)
229         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim n failed')
230      ENDIF
231
232      ! Variables
233      nret = NF90_DEF_VAR(ncid, 'kount'       , NF90_INT   , (/ ik_dim /), nkountid)
234      nret = NF90_DEF_VAR(ncid, 'calving'     , NF90_DOUBLE, (/ ix_dim, iy_dim /), ncalvid)
235      nret = NF90_DEF_VAR(ncid, 'calving_hflx', NF90_DOUBLE, (/ ix_dim, iy_dim /), ncalvhid)
236      nret = NF90_DEF_VAR(ncid, 'stored_ice'  , NF90_DOUBLE, (/ ix_dim, iy_dim, nc_dim /), nsiceid)
237      nret = NF90_DEF_VAR(ncid, 'stored_heat' , NF90_DOUBLE, (/ ix_dim, iy_dim /), nsheatid)
238
239      ! Attributes
240      nret = NF90_PUT_ATT(ncid, ncalvid , 'long_name', 'iceberg calving')
241      nret = NF90_PUT_ATT(ncid, ncalvid , 'units', 'some')
242      nret = NF90_PUT_ATT(ncid, ncalvhid, 'long_name', 'heat flux associated with iceberg calving')
243      nret = NF90_PUT_ATT(ncid, ncalvhid, 'units', 'some')
244      nret = NF90_PUT_ATT(ncid, nsiceid , 'long_name', 'stored ice used to calve icebergs')
245      nret = NF90_PUT_ATT(ncid, nsiceid , 'units', 'kg/s')
246      nret = NF90_PUT_ATT(ncid, nsheatid, 'long_name', 'heat in stored ice used to calve icebergs')
247      nret = NF90_PUT_ATT(ncid, nsheatid, 'units', 'J/kg/s')
248
249      IF ( ASSOCIATED(first_berg) ) THEN
250
251         ! Only add berg variables for this PE if we have anything to say
252
253         ! Variables
254         nret = NF90_DEF_VAR(ncid, 'lon', NF90_DOUBLE, in_dim, nlonid)
255         nret = NF90_DEF_VAR(ncid, 'lat', NF90_DOUBLE, in_dim, nlatid)
256         nret = NF90_DEF_VAR(ncid, 'xi', NF90_DOUBLE, in_dim, nxid)
257         nret = NF90_DEF_VAR(ncid, 'yj', NF90_DOUBLE, in_dim, nyid)
258         nret = NF90_DEF_VAR(ncid, 'uvel', NF90_DOUBLE, in_dim, nuvelid)
259         nret = NF90_DEF_VAR(ncid, 'vvel', NF90_DOUBLE, in_dim, nvvelid)
260         nret = NF90_DEF_VAR(ncid, 'mass', NF90_DOUBLE, in_dim, nmassid)
261         nret = NF90_DEF_VAR(ncid, 'thickness', NF90_DOUBLE, in_dim, nthicknessid)
262         nret = NF90_DEF_VAR(ncid, 'width', NF90_DOUBLE, in_dim, nwidthid)
263         nret = NF90_DEF_VAR(ncid, 'length', NF90_DOUBLE, in_dim, nlengthid)
264         nret = NF90_DEF_VAR(ncid, 'number', NF90_INT, (/ik_dim,in_dim/), numberid)
265         nret = NF90_DEF_VAR(ncid, 'year', NF90_INT, in_dim, nyearid)
266         nret = NF90_DEF_VAR(ncid, 'day', NF90_DOUBLE, in_dim, ndayid)
267         nret = NF90_DEF_VAR(ncid, 'mass_scaling', NF90_DOUBLE, in_dim, nscaling_id)
268         nret = NF90_DEF_VAR(ncid, 'mass_of_bits', NF90_DOUBLE, in_dim, nmass_of_bits_id)
269         nret = NF90_DEF_VAR(ncid, 'heat_density', NF90_DOUBLE, in_dim, nheat_density_id)
270
271         ! Attributes
272         nret = NF90_PUT_ATT(ncid, nlonid, 'long_name', 'longitude')
273         nret = NF90_PUT_ATT(ncid, nlonid, 'units', 'degrees_E')
274         nret = NF90_PUT_ATT(ncid, nlatid, 'long_name', 'latitude')
275         nret = NF90_PUT_ATT(ncid, nlatid, 'units', 'degrees_N')
276         nret = NF90_PUT_ATT(ncid, nxid, 'long_name', 'x grid box position')
277         nret = NF90_PUT_ATT(ncid, nxid, 'units', 'fractional')
278         nret = NF90_PUT_ATT(ncid, nyid, 'long_name', 'y grid box position')
279         nret = NF90_PUT_ATT(ncid, nyid, 'units', 'fractional')
280         nret = NF90_PUT_ATT(ncid, nuvelid, 'long_name', 'zonal velocity')
281         nret = NF90_PUT_ATT(ncid, nuvelid, 'units', 'm/s')
282         nret = NF90_PUT_ATT(ncid, nvvelid, 'long_name', 'meridional velocity')
283         nret = NF90_PUT_ATT(ncid, nvvelid, 'units', 'm/s')
284         nret = NF90_PUT_ATT(ncid, nmassid, 'long_name', 'mass')
285         nret = NF90_PUT_ATT(ncid, nmassid, 'units', 'kg')
286         nret = NF90_PUT_ATT(ncid, nthicknessid, 'long_name', 'thickness')
287         nret = NF90_PUT_ATT(ncid, nthicknessid, 'units', 'm')
288         nret = NF90_PUT_ATT(ncid, nwidthid, 'long_name', 'width')
289         nret = NF90_PUT_ATT(ncid, nwidthid, 'units', 'm')
290         nret = NF90_PUT_ATT(ncid, nlengthid, 'long_name', 'length')
291         nret = NF90_PUT_ATT(ncid, nlengthid, 'units', 'm')
292         nret = NF90_PUT_ATT(ncid, numberid, 'long_name', 'iceberg number on this processor')
293         nret = NF90_PUT_ATT(ncid, numberid, 'units', 'count')
294         nret = NF90_PUT_ATT(ncid, nyearid, 'long_name', 'calendar year of calving event')
295         nret = NF90_PUT_ATT(ncid, nyearid, 'units', 'years')
296         nret = NF90_PUT_ATT(ncid, ndayid, 'long_name', 'year day of calving event')
297         nret = NF90_PUT_ATT(ncid, ndayid, 'units', 'days')
298         nret = NF90_PUT_ATT(ncid, nscaling_id, 'long_name', 'scaling factor for mass of calving berg')
299         nret = NF90_PUT_ATT(ncid, nscaling_id, 'units', 'none')
300         nret = NF90_PUT_ATT(ncid, nmass_of_bits_id, 'long_name', 'mass of bergy bits')
301         nret = NF90_PUT_ATT(ncid, nmass_of_bits_id, 'units', 'kg')
302         nret = NF90_PUT_ATT(ncid, nheat_density_id, 'long_name', 'heat density')
303         nret = NF90_PUT_ATT(ncid, nheat_density_id, 'units', 'J/kg')
304
305      ENDIF ! associated(first_berg)
306
307      ! End define mode
308      nret = NF90_ENDDEF(ncid)
309
310      ! --------------------------------
311      ! now write some data
312
313      nstrt3(1) = 1
314      nstrt3(2) = 1
315      nlngth3(1) = jpi
316      nlngth3(2) = jpj
317      nlngth3(3) = 1
318
319      DO jn=1,nclasses
320         griddata(:,:,1) = berg_grid%stored_ice(:,:,jn)
321         nstrt3(3) = jn
322         nret = NF90_PUT_VAR( ncid, nsiceid, griddata, nstrt3, nlngth3 )
323         IF (nret .ne. NF90_NOERR) THEN
324            IF( lwp ) WRITE(numout,*) TRIM(NF90_STRERROR( nret ))
325            CALL ctl_stop('icebergs, write_restart: nf_put_var stored_ice failed')
326         ENDIF
327      ENDDO
328      IF( lwp .AND. nprint > 1) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: stored_ice  written'
329
330      nret = NF90_PUT_VAR( ncid, nkountid, num_bergs(:) )
331      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var kount failed')
332
333      nret = NF90_PUT_VAR( ncid, nsheatid, berg_grid%stored_heat(:,:) )
334      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var stored_heat failed')
335      IF( lwp .AND. nprint > 1) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: stored_heat written'
336
337      nret = NF90_PUT_VAR( ncid, ncalvid , src_calving(:,:) )
338      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving failed')
339      nret = NF90_PUT_VAR( ncid, ncalvhid, src_calving_hflx(:,:) )
340      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving_hflx failed')
341      IF( lwp .AND. nprint > 1) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: calving written'
342
343      IF ( ASSOCIATED(first_berg) ) THEN
344
345         ! Write variables
346         ! just write out the current point of the trajectory
347
348         this => first_berg
349         jn = 0
350         DO WHILE (ASSOCIATED(this))
351            pt => this%current_point
352            jn=jn+1
353
354            nret = NF90_PUT_VAR(ncid, numberid, this%number, (/1,jn/), (/nkounts,1/) )
355            nret = NF90_PUT_VAR(ncid, nscaling_id, this%mass_scaling, (/ jn /) )
356
357            nret = NF90_PUT_VAR(ncid, nlonid, pt%lon, (/ jn /) )
358            nret = NF90_PUT_VAR(ncid, nlatid, pt%lat, (/ jn /) )
359            nret = NF90_PUT_VAR(ncid, nxid, pt%xi, (/ jn /) )
360            nret = NF90_PUT_VAR(ncid, nyid, pt%yj, (/ jn /) )
361            nret = NF90_PUT_VAR(ncid, nuvelid, pt%uvel, (/ jn /) )
362            nret = NF90_PUT_VAR(ncid, nvvelid, pt%vvel, (/ jn /) )
363            nret = NF90_PUT_VAR(ncid, nmassid, pt%mass, (/ jn /) )
364            nret = NF90_PUT_VAR(ncid, nthicknessid, pt%thickness, (/ jn /) )
365            nret = NF90_PUT_VAR(ncid, nwidthid, pt%width, (/ jn /) )
366            nret = NF90_PUT_VAR(ncid, nlengthid, pt%length, (/ jn /) )
367            nret = NF90_PUT_VAR(ncid, nyearid, pt%year, (/ jn /) )
368            nret = NF90_PUT_VAR(ncid, ndayid, pt%day, (/ jn /) )
369            nret = NF90_PUT_VAR(ncid, nmass_of_bits_id, pt%mass_of_bits, (/ jn /) )
370            nret = NF90_PUT_VAR(ncid, nheat_density_id, pt%heat_density, (/ jn /) )
371
372            this=>this%next
373         END DO
374         !
375      ENDIF ! associated(first_berg)
376
377      ! Finish up
378      nret = NF90_CLOSE(ncid)
379      IF (nret /= NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_close failed')
380      IF(nn_timing == 2)  CALL timing_stop('iom_rstput')
381      !
382   END SUBROUTINE icb_rst_write
383   !
384END MODULE icbrst
Note: See TracBrowser for help on using the repository browser.