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_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/ICB – NEMO

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/ICB/icbrst.F90 @ 11738

Last change on this file since 11738 was 11738, checked in by marc, 4 years ago

The Dr Hook changes from my perl code.

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