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

source: branches/2012/dev_r3337_NOCS10_ICB/NEMOGCM/NEMO/OPA_SRC/ICB/icbrst.F90 @ 3609

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

NEMO branch dev_r3337_NOCS10_ICB: Changes to allow branch to compile with key_agrif. Not yet complete.

Along the way replace unnecessary POINTER declarations

File size: 20.1 KB
RevLine 
[3339]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   !!----------------------------------------------------------------------
15   !!----------------------------------------------------------------------
[3379]16   !!   icb_rst_read    : read restart file
17   !!   icb_rst_write   : write restart file
[3339]18   !!----------------------------------------------------------------------
19   USE par_oce        ! NEMO parameters
20   USE dom_oce        ! NEMO domain
21   USE in_out_manager ! NEMO IO routines
22   USE lib_mpp        ! NEMO MPI library, lk_mpp in particular
23   USE netcdf         ! netcdf routines for IO
24   USE icb_oce        ! define iceberg arrays
25   USE icbutl         ! iceberg utility routines
26
27   IMPLICIT NONE
28   PRIVATE
29
[3372]30   PUBLIC   icb_rst_read    ! routine called in icbini.F90 module
[3373]31   PUBLIC   icb_rst_write   ! routine called in icbstp.F90 module
[3370]32   
33   INTEGER ::   nlonid, nlatid, nxid, nyid, nuvelid, nvvelid
34   INTEGER ::   nmassid, nthicknessid, nwidthid, nlengthid
35   INTEGER ::   nyearid, ndayid
36   INTEGER ::   nscaling_id, nmass_of_bits_id, nheat_density_id, numberid
37   INTEGER ::   nsiceid, nsheatid, ncalvid, ncalvhid, nkountid
38   INTEGER ::   nret, ncid, nc_dim
39   
[3381]40   INTEGER,  DIMENSION(3)                  :: nstrt3, nlngth3
[3339]41
[3370]42   !!----------------------------------------------------------------------
43   !! NEMO/OPA 3.3 , NEMO Consortium (2011)
44   !! $Id:$
45   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
46   !!----------------------------------------------------------------------
[3339]47CONTAINS
48
[3372]49   SUBROUTINE icb_rst_read()
[3370]50      !!----------------------------------------------------------------------
[3372]51      !!                 ***  SUBROUTINE icb_rst_read  ***
[3370]52      !!
53      !! ** Purpose :   read a iceberg restart file
54      !!      NB: for this version, we just read back in the restart for this processor
55      !!      so we cannot change the processor layout currently with iceberg code
56      !!----------------------------------------------------------------------
57      INTEGER                      ::   idim, ivar, iatt
58      INTEGER                      ::   jn, iunlim_dim, ibergs_in_file
59      INTEGER                      ::   iclass
60      INTEGER, DIMENSION(1)        ::   istrt, ilngth, idata
61      INTEGER, DIMENSION(2)        ::   istrt2, ilngth2
62      INTEGER, DIMENSION(nkounts)  ::   idata2
63      REAL(wp), DIMENSION(1)       ::   zdata                                         ! need 1d array to read in with
[3339]64                                                                                            ! start and count arrays
[3375]65      LOGICAL                      ::   ll_found_restart
[3370]66      CHARACTER(len=80)            ::   cl_filename
67      CHARACTER(len=NF90_MAX_NAME) ::   cl_dname
68      TYPE(iceberg)                ::   localberg ! NOT a pointer but an actual local variable
69      TYPE(point)                  ::   localpt   ! NOT a pointer but an actual local variable
70      !!----------------------------------------------------------------------
[3339]71
72      ! Find a restart file
[3375]73      cl_filename = ' '
74      IF ( lk_mpp ) THEN
[3359]75         cl_filename = ' '
[3375]76         WRITE( cl_filename, '("restart_icebergs_",I4.4,".nc")' ) narea-1
77         INQUIRE( file=TRIM(cl_filename), exist=ll_found_restart )
78      ELSE
[3359]79         cl_filename = 'restart_icebergs.nc'
80         INQUIRE( file=TRIM(cl_filename), exist=ll_found_restart )
[3375]81      ENDIF
[3339]82
[3359]83      IF ( .NOT. ll_found_restart) THEN                     ! only do the following if a file was found
[3339]84         CALL ctl_stop('icebergs: no restart file found')
85      ENDIF
86
87      IF (nn_verbose_level >= 0 .AND. lwp)  &
[3359]88         WRITE(numout,'(2a)') 'icebergs, read_restart_bergs: found restart file = ',TRIM(cl_filename)
[3339]89
[3359]90      nret = NF90_OPEN(TRIM(cl_filename), NF90_NOWRITE, ncid)
91      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_open failed')
[3339]92
[3359]93      nret = nf90_inquire(ncid, idim, ivar, iatt, iunlim_dim)
94      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_inquire failed')
[3339]95
[3359]96      IF( iunlim_dim .NE. -1) THEN
[3339]97
[3359]98         nret = nf90_inquire_dimension(ncid, iunlim_dim, cl_dname, ibergs_in_file)
99         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_inq_dimlen failed')
[3339]100
[3359]101         nret = NF90_INQ_VARID(ncid, 'number', numberid)
102         nret = NF90_INQ_VARID(ncid, 'mass_scaling', nscaling_id)
103         nret = NF90_INQ_VARID(ncid, 'xi', nxid)
104         nret = NF90_INQ_VARID(ncid, 'yj', nyid)
105         nret = NF90_INQ_VARID(ncid, 'lon', nlonid)
106         nret = NF90_INQ_VARID(ncid, 'lat', nlatid)
107         nret = NF90_INQ_VARID(ncid, 'uvel', nuvelid)
108         nret = NF90_INQ_VARID(ncid, 'vvel', nvvelid)
109         nret = NF90_INQ_VARID(ncid, 'mass', nmassid)
110         nret = NF90_INQ_VARID(ncid, 'thickness', nthicknessid)
111         nret = NF90_INQ_VARID(ncid, 'width', nwidthid)
112         nret = NF90_INQ_VARID(ncid, 'length', nlengthid)
113         nret = NF90_INQ_VARID(ncid, 'year', nyearid)
114         nret = NF90_INQ_VARID(ncid, 'day', ndayid)
115         nret = NF90_INQ_VARID(ncid, 'mass_of_bits', nmass_of_bits_id)
116         nret = NF90_INQ_VARID(ncid, 'heat_density', nheat_density_id)
[3339]117
[3359]118         ilngth(1) = 1
119         istrt2(1) = 1
120         ilngth2(1) = nkounts
121         ilngth2(2) = 1
122         DO jn=1, ibergs_in_file
[3339]123
[3359]124            istrt(1) = jn
125            istrt2(2) = jn
[3339]126
[3359]127            nret = NF90_GET_VAR(ncid, numberid, idata2, istrt2, ilngth2 )
[3339]128            localberg%number(:) = idata2(:)
129
[3359]130            nret = NF90_GET_VAR(ncid, nscaling_id, zdata, istrt, ilngth )
131            localberg%mass_scaling = zdata(1)
[3339]132
[3359]133            nret = NF90_GET_VAR(ncid, nlonid, zdata, istrt, ilngth)
134            localpt%lon = zdata(1)
135            nret = NF90_GET_VAR(ncid, nlatid, zdata, istrt, ilngth)
136            localpt%lat = zdata(1)
[3339]137            IF (nn_verbose_level >= 2 .AND. lwp) THEN
[3359]138               WRITE(numout,'(a,i5,a,2f10.4,a,i5)') 'icebergs, read_restart_bergs: berg ',jn,' is at ', &
[3339]139                                              localpt%lon,localpt%lat,' on PE ',narea-1
140            ENDIF
[3359]141            nret = NF90_GET_VAR(ncid, nxid, zdata, istrt, ilngth)
142            localpt%xi = zdata(1)
143            nret = NF90_GET_VAR(ncid, nyid, zdata, istrt, ilngth)
144            localpt%yj = zdata(1)
145            nret = NF90_GET_VAR(ncid, nuvelid, zdata, istrt, ilngth )
146            localpt%uvel = zdata(1)
147            nret = NF90_GET_VAR(ncid, nvvelid, zdata, istrt, ilngth )
148            localpt%vvel = zdata(1)
149            nret = NF90_GET_VAR(ncid, nmassid, zdata, istrt, ilngth )
150            localpt%mass = zdata(1)
151            nret = NF90_GET_VAR(ncid, nthicknessid, zdata, istrt, ilngth )
152            localpt%thickness = zdata(1)
153            nret = NF90_GET_VAR(ncid, nwidthid, zdata, istrt, ilngth )
154            localpt%width = zdata(1)
155            nret = NF90_GET_VAR(ncid, nlengthid, zdata, istrt, ilngth )
156            localpt%length = zdata(1)
157            nret = NF90_GET_VAR(ncid, nyearid, idata, istrt, ilngth )
[3339]158            localpt%year = idata(1)
[3359]159            nret = NF90_GET_VAR(ncid, ndayid, zdata, istrt, ilngth )
160            localpt%day = zdata(1)
161            nret = NF90_GET_VAR(ncid, nmass_of_bits_id, zdata, istrt, ilngth )
162            localpt%mass_of_bits = zdata(1)
163            nret = NF90_GET_VAR(ncid, nheat_density_id, zdata, istrt, ilngth )
164            localpt%heat_density = zdata(1)
[3339]165            !
[3372]166            CALL icb_utl_add( localberg, localpt )
[3370]167         END DO
168         !
[3339]169      ENDIF
170
[3359]171      nret = NF90_INQ_DIMID( ncid, 'c', nc_dim )
172      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_inq_dimid c failed')
[3339]173
[3359]174      nret = NF90_INQUIRE_DIMENSION( ncid, nc_dim, cl_dname, iclass )
175      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_inquire_dimension failed')
[3339]176
[3359]177      nret = NF90_INQ_VARID(ncid, 'kount'       , nkountid)
178      nret = NF90_INQ_VARID(ncid, 'calving'     , ncalvid)
179      nret = NF90_INQ_VARID(ncid, 'calving_hflx', ncalvhid)
180      nret = NF90_INQ_VARID(ncid, 'stored_ice'  , nsiceid)
181      nret = NF90_INQ_VARID(ncid, 'stored_heat' , nsheatid)
[3339]182
[3359]183      nstrt3(1) = 1
184      nstrt3(2) = 1
185      nlngth3(1) = jpi
186      nlngth3(2) = jpj
187      nlngth3(3) = 1
[3339]188
[3370]189      DO jn = 1, iclass
[3359]190         nstrt3(3) = jn
[3370]191         nret      = NF90_GET_VAR( ncid, nsiceid , griddata, nstrt3, nlngth3 )
[3359]192         berg_grid%stored_ice(:,:,jn) = griddata(:,:,1)
[3370]193      END DO
[3339]194
[3370]195      nret = NF90_GET_VAR( ncid, ncalvid , src_calving          (:,:) )
196      nret = NF90_GET_VAR( ncid, ncalvhid, src_calving_hflx     (:,:) )
[3359]197      nret = NF90_GET_VAR( ncid, nsheatid, berg_grid%stored_heat(:,:) )
198      nret = NF90_GET_VAR( ncid, nkountid, idata2(:) )
199      num_bergs(:) = idata2(:)
[3339]200
201      ! Finish up
[3359]202      nret = NF90_CLOSE(ncid)
203      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_close failed')
[3339]204
205      ! Sanity check
[3372]206      jn = icb_utl_count()
[3339]207      IF (nn_verbose_level >= 0)   &
[3359]208         WRITE(numout,'(2(a,i5))') 'icebergs, read_restart_bergs: # bergs =',jn,' on PE',narea-1
[3339]209      IF( lk_mpp ) THEN
[3375]210         CALL mpp_sum(ibergs_in_file)
[3359]211         CALL mpp_sum(jn)
[3339]212      ENDIF
[3370]213      IF(lwp)   WRITE(numout,'(a,i5,a,i5,a)') 'icebergs, read_restart_bergs: there were',ibergs_in_file,   &
214         &                                    ' bergs in the restart file and', jn,' bergs have been read'
215      !
216      IF( lwp .and. nn_verbose_level >= 0)  WRITE(numout,'(a)') 'icebergs, read_restart_bergs: completed'
217      !
[3372]218   END SUBROUTINE icb_rst_read
[3339]219
220
[3372]221   SUBROUTINE icb_rst_write( kt )
[3370]222      !!----------------------------------------------------------------------
[3372]223      !!                 ***  SUBROUTINE icb_rst_write  ***
[3370]224      !!
225      !!----------------------------------------------------------------------
226      INTEGER, INTENT( in ) :: kt
227      !
228      INTEGER ::   jn   ! dummy loop index
229      INTEGER ::   ix_dim, iy_dim, ik_dim, in_dim
230      CHARACTER(len=80)      :: cl_filename
231      TYPE(iceberg), POINTER :: this
232      TYPE(point)  , POINTER :: pt
233      !!----------------------------------------------------------------------
[3339]234
[3375]235      IF( lk_mpp ) THEN
236         WRITE(cl_filename,'("icebergs_",I8.8,"_restart_",I4.4,".nc")') kt, narea-1
237      ELSE
238         WRITE(cl_filename,'("icebergs_",I8.8,"_restart.nc")') kt
239      ENDIF
[3359]240      IF (nn_verbose_level >= 0) WRITE(numout,'(2a)') 'icebergs, write_restart: creating ',TRIM(cl_filename)
[3339]241
[3359]242      nret = NF90_CREATE(TRIM(cl_filename), NF90_CLOBBER, ncid)
243      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_create failed')
[3339]244
245      ! Dimensions
[3359]246      nret = NF90_DEF_DIM(ncid, 'x', jpi, ix_dim)
247      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim x failed')
[3339]248
[3359]249      nret = NF90_DEF_DIM(ncid, 'y', jpj, iy_dim)
250      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim y failed')
[3339]251
[3359]252      nret = NF90_DEF_DIM(ncid, 'c', nclasses, nc_dim)
253      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim c failed')
[3339]254
[3359]255      nret = NF90_DEF_DIM(ncid, 'k', nkounts, ik_dim)
256      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim k failed')
[3339]257
258      IF (associated(first_berg)) then
[3359]259         nret = NF90_DEF_DIM(ncid, 'n', NF90_UNLIMITED, in_dim)
260         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim n failed')
[3339]261      ENDIF
262
263      ! Variables
[3359]264      nret = NF90_DEF_VAR(ncid, 'kount'       , NF90_INT   , (/ ik_dim /), nkountid)
265      nret = NF90_DEF_VAR(ncid, 'calving'     , NF90_DOUBLE, (/ ix_dim, iy_dim /), ncalvid)
266      nret = NF90_DEF_VAR(ncid, 'calving_hflx', NF90_DOUBLE, (/ ix_dim, iy_dim /), ncalvhid)
267      nret = NF90_DEF_VAR(ncid, 'stored_ice'  , NF90_DOUBLE, (/ ix_dim, iy_dim, nc_dim /), nsiceid)
268      nret = NF90_DEF_VAR(ncid, 'stored_heat' , NF90_DOUBLE, (/ ix_dim, iy_dim /), nsheatid)
[3339]269
270      ! Attributes
[3359]271      nret = NF90_PUT_ATT(ncid, ncalvid , 'long_name', 'iceberg calving')
272      nret = NF90_PUT_ATT(ncid, ncalvid , 'units', 'some')
273      nret = NF90_PUT_ATT(ncid, ncalvhid, 'long_name', 'heat flux associated with iceberg calving')
274      nret = NF90_PUT_ATT(ncid, ncalvhid, 'units', 'some')
275      nret = NF90_PUT_ATT(ncid, nsiceid , 'long_name', 'stored ice used to calve icebergs')
276      nret = NF90_PUT_ATT(ncid, nsiceid , 'units', 'kg/s')
277      nret = NF90_PUT_ATT(ncid, nsheatid, 'long_name', 'heat in stored ice used to calve icebergs')
278      nret = NF90_PUT_ATT(ncid, nsheatid, 'units', 'J/kg/s')
[3339]279
280      IF ( ASSOCIATED(first_berg) ) THEN
281
282         ! Only add berg variables for this PE if we have anything to say
283
284         ! Variables
[3359]285         nret = NF90_DEF_VAR(ncid, 'lon', NF90_DOUBLE, in_dim, nlonid)
286         nret = NF90_DEF_VAR(ncid, 'lat', NF90_DOUBLE, in_dim, nlatid)
287         nret = NF90_DEF_VAR(ncid, 'xi', NF90_DOUBLE, in_dim, nxid)
288         nret = NF90_DEF_VAR(ncid, 'yj', NF90_DOUBLE, in_dim, nyid)
289         nret = NF90_DEF_VAR(ncid, 'uvel', NF90_DOUBLE, in_dim, nuvelid)
290         nret = NF90_DEF_VAR(ncid, 'vvel', NF90_DOUBLE, in_dim, nvvelid)
291         nret = NF90_DEF_VAR(ncid, 'mass', NF90_DOUBLE, in_dim, nmassid)
292         nret = NF90_DEF_VAR(ncid, 'thickness', NF90_DOUBLE, in_dim, nthicknessid)
293         nret = NF90_DEF_VAR(ncid, 'width', NF90_DOUBLE, in_dim, nwidthid)
294         nret = NF90_DEF_VAR(ncid, 'length', NF90_DOUBLE, in_dim, nlengthid)
295         nret = NF90_DEF_VAR(ncid, 'number', NF90_INT, (/ik_dim,in_dim/), numberid)
296         nret = NF90_DEF_VAR(ncid, 'year', NF90_INT, in_dim, nyearid)
297         nret = NF90_DEF_VAR(ncid, 'day', NF90_DOUBLE, in_dim, ndayid)
298         nret = NF90_DEF_VAR(ncid, 'mass_scaling', NF90_DOUBLE, in_dim, nscaling_id)
299         nret = NF90_DEF_VAR(ncid, 'mass_of_bits', NF90_DOUBLE, in_dim, nmass_of_bits_id)
300         nret = NF90_DEF_VAR(ncid, 'heat_density', NF90_DOUBLE, in_dim, nheat_density_id)
[3339]301
302         ! Attributes
[3359]303         nret = NF90_PUT_ATT(ncid, nlonid, 'long_name', 'longitude')
304         nret = NF90_PUT_ATT(ncid, nlonid, 'units', 'degrees_E')
305         nret = NF90_PUT_ATT(ncid, nlatid, 'long_name', 'latitude')
306         nret = NF90_PUT_ATT(ncid, nlatid, 'units', 'degrees_N')
307         nret = NF90_PUT_ATT(ncid, nxid, 'long_name', 'x grid box position')
308         nret = NF90_PUT_ATT(ncid, nxid, 'units', 'fractional')
309         nret = NF90_PUT_ATT(ncid, nyid, 'long_name', 'y grid box position')
310         nret = NF90_PUT_ATT(ncid, nyid, 'units', 'fractional')
311         nret = NF90_PUT_ATT(ncid, nuvelid, 'long_name', 'zonal velocity')
312         nret = NF90_PUT_ATT(ncid, nuvelid, 'units', 'm/s')
313         nret = NF90_PUT_ATT(ncid, nvvelid, 'long_name', 'meridional velocity')
314         nret = NF90_PUT_ATT(ncid, nvvelid, 'units', 'm/s')
315         nret = NF90_PUT_ATT(ncid, nmassid, 'long_name', 'mass')
316         nret = NF90_PUT_ATT(ncid, nmassid, 'units', 'kg')
317         nret = NF90_PUT_ATT(ncid, nthicknessid, 'long_name', 'thickness')
318         nret = NF90_PUT_ATT(ncid, nthicknessid, 'units', 'm')
319         nret = NF90_PUT_ATT(ncid, nwidthid, 'long_name', 'width')
320         nret = NF90_PUT_ATT(ncid, nwidthid, 'units', 'm')
321         nret = NF90_PUT_ATT(ncid, nlengthid, 'long_name', 'length')
322         nret = NF90_PUT_ATT(ncid, nlengthid, 'units', 'm')
323         nret = NF90_PUT_ATT(ncid, numberid, 'long_name', 'iceberg number on this processor')
324         nret = NF90_PUT_ATT(ncid, numberid, 'units', 'count')
325         nret = NF90_PUT_ATT(ncid, nyearid, 'long_name', 'calendar year of calving event')
326         nret = NF90_PUT_ATT(ncid, nyearid, 'units', 'years')
327         nret = NF90_PUT_ATT(ncid, ndayid, 'long_name', 'year day of calving event')
328         nret = NF90_PUT_ATT(ncid, ndayid, 'units', 'days')
329         nret = NF90_PUT_ATT(ncid, nscaling_id, 'long_name', 'scaling factor for mass of calving berg')
330         nret = NF90_PUT_ATT(ncid, nscaling_id, 'units', 'none')
331         nret = NF90_PUT_ATT(ncid, nmass_of_bits_id, 'long_name', 'mass of bergy bits')
332         nret = NF90_PUT_ATT(ncid, nmass_of_bits_id, 'units', 'kg')
333         nret = NF90_PUT_ATT(ncid, nheat_density_id, 'long_name', 'heat density')
334         nret = NF90_PUT_ATT(ncid, nheat_density_id, 'units', 'J/kg')
[3339]335
336      ENDIF ! associated(first_berg)
337
338      ! End define mode
[3359]339      nret = NF90_ENDDEF(ncid)
[3339]340
341      ! --------------------------------
342      ! now write some data
343
[3359]344      nstrt3(1) = 1
345      nstrt3(2) = 1
346      nlngth3(1) = jpi
347      nlngth3(2) = jpj
348      nlngth3(3) = 1
[3339]349
[3359]350      DO jn=1,nclasses
351         griddata(:,:,1) = berg_grid%stored_ice(:,:,jn)
352         nstrt3(3) = jn
353         nret = NF90_PUT_VAR( ncid, nsiceid, griddata, nstrt3, nlngth3 )
354         IF (nret .ne. NF90_NOERR) THEN
355            IF( lwp ) WRITE(numout,*) TRIM(NF90_STRERROR( nret ))
[3339]356            CALL ctl_stop('icebergs, write_restart: nf_put_var stored_ice failed')
357         ENDIF
358      ENDDO
[3359]359      IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_filename),' var: stored_ice  written'
[3339]360
[3359]361      nret = NF90_PUT_VAR( ncid, nkountid, num_bergs(:) )
362      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var kount failed')
[3339]363
[3359]364      nret = NF90_PUT_VAR( ncid, nsheatid, berg_grid%stored_heat(:,:) )
365      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var stored_heat failed')
366      IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_filename),' var: stored_heat written'
[3339]367
[3359]368      nret = NF90_PUT_VAR( ncid, ncalvid , src_calving(:,:) )
369      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving failed')
370      nret = NF90_PUT_VAR( ncid, ncalvhid, src_calving_hflx(:,:) )
371      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving_hflx failed')
372      IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_filename),' var: calving written'
[3339]373
374      IF ( ASSOCIATED(first_berg) ) THEN
375
376         ! Write variables
[3359]377         ! just write out the current point of the trajectory
[3339]378
379         this => first_berg
[3359]380         jn = 0
[3339]381         DO WHILE (ASSOCIATED(this))
382            pt => this%current_point
[3359]383            jn=jn+1
[3339]384
[3359]385            nret = NF90_PUT_VAR(ncid, numberid, this%number, (/1,jn/), (/nkounts,1/) )
386            nret = NF90_PUT_VAR(ncid, nscaling_id, this%mass_scaling, (/ jn /) )
[3339]387
[3359]388            nret = NF90_PUT_VAR(ncid, nlonid, pt%lon, (/ jn /) )
389            nret = NF90_PUT_VAR(ncid, nlatid, pt%lat, (/ jn /) )
390            nret = NF90_PUT_VAR(ncid, nxid, pt%xi, (/ jn /) )
391            nret = NF90_PUT_VAR(ncid, nyid, pt%yj, (/ jn /) )
392            nret = NF90_PUT_VAR(ncid, nuvelid, pt%uvel, (/ jn /) )
393            nret = NF90_PUT_VAR(ncid, nvvelid, pt%vvel, (/ jn /) )
394            nret = NF90_PUT_VAR(ncid, nmassid, pt%mass, (/ jn /) )
395            nret = NF90_PUT_VAR(ncid, nthicknessid, pt%thickness, (/ jn /) )
396            nret = NF90_PUT_VAR(ncid, nwidthid, pt%width, (/ jn /) )
397            nret = NF90_PUT_VAR(ncid, nlengthid, pt%length, (/ jn /) )
398            nret = NF90_PUT_VAR(ncid, nyearid, pt%year, (/ jn /) )
399            nret = NF90_PUT_VAR(ncid, ndayid, pt%day, (/ jn /) )
400            nret = NF90_PUT_VAR(ncid, nmass_of_bits_id, pt%mass_of_bits, (/ jn /) )
401            nret = NF90_PUT_VAR(ncid, nheat_density_id, pt%heat_density, (/ jn /) )
[3339]402
403            this=>this%next
[3370]404         END DO
405         !
[3339]406      ENDIF ! associated(first_berg)
407
408      ! Finish up
[3359]409      nret = NF90_CLOSE(ncid)
[3370]410      IF (nret /= NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_close failed')
411      !
[3372]412   END SUBROUTINE icb_rst_write
[3370]413   !
[3339]414END MODULE icbrst
Note: See TracBrowser for help on using the repository browser.