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.
icbtrj.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/icbtrj.F90 @ 11738

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

The Dr Hook changes from my perl code.

File size: 16.2 KB
RevLine 
[3614]1MODULE icbtrj
2
3   !!======================================================================
4   !!                       ***  MODULE  icbtrj  ***
5   !! Ocean physics:  trajectory I/O routines
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-05  (Alderson)       New module to handle trajectory output
11   !!----------------------------------------------------------------------
12   !!----------------------------------------------------------------------
13   !!   icb_trj_init          :
14   !!----------------------------------------------------------------------
15   USE par_oce        ! NEMO parameters
16   USE dom_oce        ! NEMO ocean domain
17   USE phycst         ! NEMO physical constants
18   USE lib_mpp        ! NEMO MPI library, lk_mpp in particular
19   USE in_out_manager ! NEMO IO, numout in particular
[7733]20   USE ioipsl, ONLY : ju2ymds    ! for calendar
[3614]21   USE netcdf
22   !
23   USE icb_oce        ! define iceberg arrays
24   USE icbutl         ! iceberg utility routines
25
[11738]26   USE yomhook, ONLY: lhook, dr_hook
27   USE parkind1, ONLY: jprb, jpim
28
[3614]29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   icb_trj_init    ! routine called in icbini.F90 module
33   PUBLIC   icb_trj_write   ! routine called in icbstp.F90 module
34   PUBLIC   icb_trj_sync    ! routine called in icbstp.F90 module
35   PUBLIC   icb_trj_end     ! routine called in icbstp.F90 module
36
37   INTEGER ::   num_traj
38   INTEGER ::   n_dim, m_dim
39   INTEGER ::   ntrajid
40   INTEGER ::   numberid, nstepid, nscaling_id
41   INTEGER ::   nlonid, nlatid, nxid, nyid, nuvelid, nvvelid, nmassid
42   INTEGER ::   nuoid, nvoid, nuaid, nvaid, nuiid, nviid
43   INTEGER ::   nsshxid, nsshyid, nsstid, ncntid, nthkid
44   INTEGER ::   nthicknessid, nwidthid, nlengthid
45   INTEGER ::   nyearid, ndayid
46   INTEGER ::   nmass_of_bits_id, nheat_density_id
47
48   !!----------------------------------------------------------------------
49   !! NEMO/OPA 3.3 , NEMO Consortium (2011)
[5215]50   !! $Id$
[3614]51   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
52   !!----------------------------------------------------------------------
53CONTAINS
54
55   !!-------------------------------------------------------------------------
56
57   SUBROUTINE icb_trj_init( ktend )
58      !!----------------------------------------------------------------------
59      !!                  ***  ROUTINE icb_trj_init  ***
60      !!
61      !! ** Purpose :   initialise iceberg trajectory output files
62      !!----------------------------------------------------------------------
63      INTEGER, INTENT( in )                 :: ktend
64      !
65      INTEGER                               :: iret
[7733]66      INTEGER                               :: iyear, imonth, iday
67      REAL(wp)                              :: zfjulday, zsec
[3614]68      CHARACTER(len=80)                     :: cl_filename
69      TYPE(iceberg), POINTER                :: this
70      TYPE(point)  , POINTER                :: pt
[7733]71      CHARACTER(LEN=20)                     :: cldate_ini, cldate_end
[11738]72      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
73      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
74      REAL(KIND=jprb)               :: zhook_handle
75
76      CHARACTER(LEN=*), PARAMETER :: RoutineName='ICB_TRJ_INIT'
77
78      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
79
[3614]80      !!----------------------------------------------------------------------
81
[7733]82      ! compute initial time step date
83      CALL ju2ymds( fjulday, iyear, imonth, iday, zsec )
84      WRITE(cldate_ini, '(i4.4,2i2.2)') iyear, imonth, iday
85
86      ! compute end time step date
87      zfjulday = fjulday + rdttra(1) / rday * REAL( nitend - nit000 + 1 , wp)
88      IF( ABS(zfjulday - REAL(NINT(zfjulday),wp)) < 0.1 / rday )   zfjulday = REAL(NINT(zfjulday),wp)   ! avoid truncation error
89      CALL ju2ymds( zfjulday, iyear, imonth, iday, zsec )
90      WRITE(cldate_end, '(i4.4,2i2.2)') iyear, imonth, iday
91
92      ! define trajectory output name
93      IF( lk_mpp ) THEN   ;   WRITE(cl_filename,'("trajectory_icebergs_",A,"-",A,"_",I4.4,".nc")') TRIM(ADJUSTL(cldate_ini)), TRIM(ADJUSTL(cldate_end)), narea-1
94      ELSE                ;   WRITE(cl_filename,'("trajectory_icebergs_",A,"-",A         ,".nc")') TRIM(ADJUSTL(cldate_ini)), TRIM(ADJUSTL(cldate_end))
[3614]95      ENDIF
96      IF ( lwp .AND. nn_verbose_level >= 0) WRITE(numout,'(2a)') 'icebergs, icb_trj_init: creating ',TRIM(cl_filename)
97
98      iret = NF90_CREATE(TRIM(cl_filename), NF90_CLOBBER, ntrajid)
99      IF (iret .NE. NF90_NOERR) CALL ctl_stop('icebergs, icb_trj_init: nf_create failed')
100
101      ! Dimensions
102      iret = NF90_DEF_DIM(ntrajid, 'n', NF90_UNLIMITED, n_dim)
103      IF (iret .NE. NF90_NOERR) CALL ctl_stop('icebergs, icb_trj_init: nf_def_dim n failed')
104      iret = NF90_DEF_DIM(ntrajid, 'k', nkounts, m_dim)
105      IF (iret .NE. NF90_NOERR) CALL ctl_stop('icebergs, icb_trj_init: nf_def_dim k failed')
106
107      ! Variables
108      iret = NF90_DEF_VAR(ntrajid, 'iceberg_number', NF90_INT, (/m_dim,n_dim/), numberid)
109      iret = NF90_DEF_VAR(ntrajid, 'timestep', NF90_INT, n_dim, nstepid)
110      iret = NF90_DEF_VAR(ntrajid, 'mass_scaling', NF90_DOUBLE, n_dim, nscaling_id)
111      iret = NF90_DEF_VAR(ntrajid, 'lon', NF90_DOUBLE, n_dim, nlonid)
112      iret = NF90_DEF_VAR(ntrajid, 'lat', NF90_DOUBLE, n_dim, nlatid)
113      iret = NF90_DEF_VAR(ntrajid, 'xi', NF90_DOUBLE, n_dim, nxid)
114      iret = NF90_DEF_VAR(ntrajid, 'yj', NF90_DOUBLE, n_dim, nyid)
115      iret = NF90_DEF_VAR(ntrajid, 'uvel', NF90_DOUBLE, n_dim, nuvelid)
116      iret = NF90_DEF_VAR(ntrajid, 'vvel', NF90_DOUBLE, n_dim, nvvelid)
117      iret = NF90_DEF_VAR(ntrajid, 'uto', NF90_DOUBLE, n_dim, nuoid)
118      iret = NF90_DEF_VAR(ntrajid, 'vto', NF90_DOUBLE, n_dim, nvoid)
119      iret = NF90_DEF_VAR(ntrajid, 'uta', NF90_DOUBLE, n_dim, nuaid)
120      iret = NF90_DEF_VAR(ntrajid, 'vta', NF90_DOUBLE, n_dim, nvaid)
121      iret = NF90_DEF_VAR(ntrajid, 'uti', NF90_DOUBLE, n_dim, nuiid)
122      iret = NF90_DEF_VAR(ntrajid, 'vti', NF90_DOUBLE, n_dim, nviid)
123      iret = NF90_DEF_VAR(ntrajid, 'ssh_x', NF90_DOUBLE, n_dim, nsshyid)
124      iret = NF90_DEF_VAR(ntrajid, 'ssh_y', NF90_DOUBLE, n_dim, nsshxid)
125      iret = NF90_DEF_VAR(ntrajid, 'sst', NF90_DOUBLE, n_dim, nsstid)
126      iret = NF90_DEF_VAR(ntrajid, 'icnt', NF90_DOUBLE, n_dim, ncntid)
127      iret = NF90_DEF_VAR(ntrajid, 'ithk', NF90_DOUBLE, n_dim, nthkid)
128      iret = NF90_DEF_VAR(ntrajid, 'mass', NF90_DOUBLE, n_dim, nmassid)
129      iret = NF90_DEF_VAR(ntrajid, 'thickness', NF90_DOUBLE, n_dim, nthicknessid)
130      iret = NF90_DEF_VAR(ntrajid, 'width', NF90_DOUBLE, n_dim, nwidthid)
131      iret = NF90_DEF_VAR(ntrajid, 'length', NF90_DOUBLE, n_dim, nlengthid)
132      iret = NF90_DEF_VAR(ntrajid, 'year', NF90_INT, n_dim, nyearid)
133      iret = NF90_DEF_VAR(ntrajid, 'day', NF90_DOUBLE, n_dim, ndayid)
134      iret = NF90_DEF_VAR(ntrajid, 'mass_of_bits', NF90_DOUBLE, n_dim, nmass_of_bits_id)
135      iret = NF90_DEF_VAR(ntrajid, 'heat_density', NF90_DOUBLE, n_dim, nheat_density_id)
136
137      ! Attributes
138      iret = NF90_PUT_ATT(ntrajid, numberid, 'long_name', 'iceberg number on this processor')
139      iret = NF90_PUT_ATT(ntrajid, numberid, 'units', 'count')
140      iret = NF90_PUT_ATT(ntrajid, nstepid, 'long_name', 'timestep number kt')
141      iret = NF90_PUT_ATT(ntrajid, nstepid, 'units', 'count')
142      iret = NF90_PUT_ATT(ntrajid, nlonid, 'long_name', 'longitude')
143      iret = NF90_PUT_ATT(ntrajid, nlonid, 'units', 'degrees_E')
144      iret = NF90_PUT_ATT(ntrajid, nlatid, 'long_name', 'latitude')
145      iret = NF90_PUT_ATT(ntrajid, nlatid, 'units', 'degrees_N')
146      iret = NF90_PUT_ATT(ntrajid, nxid, 'long_name', 'x grid box position')
147      iret = NF90_PUT_ATT(ntrajid, nxid, 'units', 'fractional')
148      iret = NF90_PUT_ATT(ntrajid, nyid, 'long_name', 'y grid box position')
149      iret = NF90_PUT_ATT(ntrajid, nyid, 'units', 'fractional')
150      iret = NF90_PUT_ATT(ntrajid, nuvelid, 'long_name', 'zonal velocity')
151      iret = NF90_PUT_ATT(ntrajid, nuvelid, 'units', 'm/s')
152      iret = NF90_PUT_ATT(ntrajid, nvvelid, 'long_name', 'meridional velocity')
153      iret = NF90_PUT_ATT(ntrajid, nvvelid, 'units', 'm/s')
154      iret = NF90_PUT_ATT(ntrajid, nuoid, 'long_name', 'ocean u component')
155      iret = NF90_PUT_ATT(ntrajid, nuoid, 'units', 'm/s')
156      iret = NF90_PUT_ATT(ntrajid, nvoid, 'long_name', 'ocean v component')
157      iret = NF90_PUT_ATT(ntrajid, nvoid, 'units', 'm/s')
158      iret = NF90_PUT_ATT(ntrajid, nuaid, 'long_name', 'atmosphere u component')
159      iret = NF90_PUT_ATT(ntrajid, nuaid, 'units', 'm/s')
160      iret = NF90_PUT_ATT(ntrajid, nvaid, 'long_name', 'atmosphere v component')
161      iret = NF90_PUT_ATT(ntrajid, nvaid, 'units', 'm/s')
162      iret = NF90_PUT_ATT(ntrajid, nuiid, 'long_name', 'sea ice u component')
163      iret = NF90_PUT_ATT(ntrajid, nuiid, 'units', 'm/s')
164      iret = NF90_PUT_ATT(ntrajid, nviid, 'long_name', 'sea ice v component')
165      iret = NF90_PUT_ATT(ntrajid, nviid, 'units', 'm/s')
166      iret = NF90_PUT_ATT(ntrajid, nsshxid, 'long_name', 'sea surface height gradient from x points')
167      iret = NF90_PUT_ATT(ntrajid, nsshxid, 'units', 'm/m')
168      iret = NF90_PUT_ATT(ntrajid, nsshyid, 'long_name', 'sea surface height gradient from y points')
169      iret = NF90_PUT_ATT(ntrajid, nsshyid, 'units', 'm/m')
170      iret = NF90_PUT_ATT(ntrajid, nsstid, 'long_name', 'sea surface temperature')
171      iret = NF90_PUT_ATT(ntrajid, nsstid, 'units', 'degC')
172      iret = NF90_PUT_ATT(ntrajid, ncntid, 'long_name', 'sea ice concentration')
173      iret = NF90_PUT_ATT(ntrajid, ncntid, 'units', 'degC')
174      iret = NF90_PUT_ATT(ntrajid, nthkid, 'long_name', 'sea ice thickness')
175      iret = NF90_PUT_ATT(ntrajid, nthkid, 'units', 'm')
176      iret = NF90_PUT_ATT(ntrajid, nmassid, 'long_name', 'mass')
177      iret = NF90_PUT_ATT(ntrajid, nmassid, 'units', 'kg')
178      iret = NF90_PUT_ATT(ntrajid, nthicknessid, 'long_name', 'thickness')
179      iret = NF90_PUT_ATT(ntrajid, nthicknessid, 'units', 'm')
180      iret = NF90_PUT_ATT(ntrajid, nwidthid, 'long_name', 'width')
181      iret = NF90_PUT_ATT(ntrajid, nwidthid, 'units', 'm')
182      iret = NF90_PUT_ATT(ntrajid, nlengthid, 'long_name', 'length')
183      iret = NF90_PUT_ATT(ntrajid, nlengthid, 'units', 'm')
184      iret = NF90_PUT_ATT(ntrajid, nyearid, 'long_name', 'calendar year')
185      iret = NF90_PUT_ATT(ntrajid, nyearid, 'units', 'years')
186      iret = NF90_PUT_ATT(ntrajid, ndayid, 'long_name', 'day of year')
187      iret = NF90_PUT_ATT(ntrajid, ndayid, 'units', 'days')
188      iret = NF90_PUT_ATT(ntrajid, nscaling_id, 'long_name', 'scaling factor for mass of berg')
189      iret = NF90_PUT_ATT(ntrajid, nscaling_id, 'units', 'none')
190      iret = NF90_PUT_ATT(ntrajid, nmass_of_bits_id, 'long_name', 'mass of bergy bits')
191      iret = NF90_PUT_ATT(ntrajid, nmass_of_bits_id, 'units', 'kg')
192      iret = NF90_PUT_ATT(ntrajid, nheat_density_id, 'long_name', 'heat density')
193      iret = NF90_PUT_ATT(ntrajid, nheat_density_id, 'units', 'J/kg')
194
195      ! End define mode
196      iret = NF90_ENDDEF(ntrajid)
197      !
[11738]198      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
[3614]199   END SUBROUTINE icb_trj_init
200
201
202   SUBROUTINE icb_trj_write( kt )
203      !!----------------------------------------------------------------------
204      !!                  ***  ROUTINE icb_trj_write  ***
205      !!
206      !! ** Purpose :   write out iceberg trajectories
207      !!
208      !! ** Method  : - for the moment write out each snapshot of positions later
209      !!                can rewrite so that it is buffered and written out more efficiently
210      !!----------------------------------------------------------------------
211      INTEGER, INTENT( in ) ::   kt
212      !
213      INTEGER                ::   iret, jn
214      CHARACTER(len=80)      ::   cl_filename
215      TYPE(iceberg), POINTER ::   this
216      TYPE(point)  , POINTER ::   pt
[11738]217      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
218      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
219      REAL(KIND=jprb)               :: zhook_handle
220
221      CHARACTER(LEN=*), PARAMETER :: RoutineName='ICB_TRJ_WRITE'
222
223      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
224
[3614]225      !!----------------------------------------------------------------------
226
227      ! Write variables
228      ! sga - just write out the current point of the trajectory
229
230      this => first_berg
231      jn = num_traj
232      DO WHILE (ASSOCIATED(this))
233         pt => this%current_point
234         jn=jn+1
235
236         iret = NF90_PUT_VAR(ntrajid, numberid, this%number, (/1,jn/), (/nkounts,1/) )
237         iret = NF90_PUT_VAR(ntrajid, nstepid, kt, (/ jn /) )
238         iret = NF90_PUT_VAR(ntrajid, nscaling_id, this%mass_scaling, (/ jn /) )
239
240         iret = NF90_PUT_VAR(ntrajid, nlonid, pt%lon, (/ jn /) )
241         iret = NF90_PUT_VAR(ntrajid, nlatid, pt%lat, (/ jn /) )
242         iret = NF90_PUT_VAR(ntrajid, nxid, pt%xi, (/ jn /) )
243         iret = NF90_PUT_VAR(ntrajid, nyid, pt%yj, (/ jn /) )
244         iret = NF90_PUT_VAR(ntrajid, nuvelid, pt%uvel, (/ jn /) )
245         iret = NF90_PUT_VAR(ntrajid, nvvelid, pt%vvel, (/ jn /) )
246         iret = NF90_PUT_VAR(ntrajid, nuoid, pt%uo, (/ jn /) )
247         iret = NF90_PUT_VAR(ntrajid, nvoid, pt%vo, (/ jn /) )
248         iret = NF90_PUT_VAR(ntrajid, nuaid, pt%ua, (/ jn /) )
249         iret = NF90_PUT_VAR(ntrajid, nvaid, pt%va, (/ jn /) )
250         iret = NF90_PUT_VAR(ntrajid, nuiid, pt%ui, (/ jn /) )
251         iret = NF90_PUT_VAR(ntrajid, nviid, pt%vi, (/ jn /) )
252         iret = NF90_PUT_VAR(ntrajid, nsshxid, pt%ssh_x, (/ jn /) )
253         iret = NF90_PUT_VAR(ntrajid, nsshyid, pt%ssh_y, (/ jn /) )
254         iret = NF90_PUT_VAR(ntrajid, nsstid, pt%sst, (/ jn /) )
255         iret = NF90_PUT_VAR(ntrajid, ncntid, pt%cn, (/ jn /) )
256         iret = NF90_PUT_VAR(ntrajid, nthkid, pt%hi, (/ jn /) )
257         iret = NF90_PUT_VAR(ntrajid, nmassid, pt%mass, (/ jn /) )
258         iret = NF90_PUT_VAR(ntrajid, nthicknessid, pt%thickness, (/ jn /) )
259         iret = NF90_PUT_VAR(ntrajid, nwidthid, pt%width, (/ jn /) )
260         iret = NF90_PUT_VAR(ntrajid, nlengthid, pt%length, (/ jn /) )
261         iret = NF90_PUT_VAR(ntrajid, nyearid, pt%year, (/ jn /) )
262         iret = NF90_PUT_VAR(ntrajid, ndayid, pt%day, (/ jn /) )
263         iret = NF90_PUT_VAR(ntrajid, nmass_of_bits_id, pt%mass_of_bits, (/ jn /) )
264         iret = NF90_PUT_VAR(ntrajid, nheat_density_id, pt%heat_density, (/ jn /) )
265
266         this=>this%next
267      END DO
268      IF( lwp .and. nn_verbose_level > 0 ) WRITE(numout,*) 'trajectory write to frame ', jn
269      num_traj = jn
270      !
[11738]271      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
[3614]272   END SUBROUTINE icb_trj_write
273
274   !!-------------------------------------------------------------------------
275
276   SUBROUTINE icb_trj_sync()
277      !!----------------------------------------------------------------------
278      !!                  ***  ROUTINE icb_trj_sync  ***
279      !!
280      !! ** Purpose :   
281      !!----------------------------------------------------------------------
282      INTEGER                               :: iret
[11738]283      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
284      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
285      REAL(KIND=jprb)               :: zhook_handle
286
287      CHARACTER(LEN=*), PARAMETER :: RoutineName='ICB_TRJ_SYNC'
288
289      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
290
[3614]291      !!----------------------------------------------------------------------
292      ! flush to file
293      iret = NF90_SYNC(ntrajid)
294      IF(iret /= NF90_NOERR)   CALL ctl_stop( 'icebergs, icb_trj_sync: nf_sync failed' )
295      !
[11738]296      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
[3614]297   END SUBROUTINE icb_trj_sync
298
299
300   SUBROUTINE icb_trj_end()
301      ! Local variables
302      INTEGER                               :: iret
[11738]303      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
304      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
305      REAL(KIND=jprb)               :: zhook_handle
306
307      CHARACTER(LEN=*), PARAMETER :: RoutineName='ICB_TRJ_END'
308
309      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
310
[3614]311      !!----------------------------------------------------------------------
312      ! Finish up
313      iret = NF90_CLOSE(ntrajid)
314      IF (iret /= NF90_NOERR)   CALL ctl_stop( 'icebergs, icb_trj_end: nf_close failed' )
315      !
[11738]316      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
[3614]317   END SUBROUTINE icb_trj_end
318
319   !!-------------------------------------------------------------------------
320
321END MODULE icbtrj
Note: See TracBrowser for help on using the repository browser.