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.
diamlr.F90 in NEMO/branches/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/OCE/DIA – NEMO

source: NEMO/branches/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/OCE/DIA/diamlr.F90 @ 14644

Last change on this file since 14644 was 14644, checked in by sparonuz, 3 years ago

Merge trunk -r14642:HEAD

File size: 23.8 KB
Line 
1MODULE diamlr
2   !!======================================================================
3   !!                       ***  MODULE  diamlr  ***
4   !! Management of the IOM context for multiple-linear-regression analysis
5   !!======================================================================
6   !! History :  4.0  !  2019  (S. Mueller)   Original code
7   !!----------------------------------------------------------------------
8
9   USE par_oce        , ONLY :   jpi, jpj
10   USE phycst         , ONLY :   rpi
11   USE dom_oce        , ONLY :   adatrj
12   USE tide_mod
13   !
14   USE in_out_manager , ONLY :   lwp, numout, ln_timing
15   USE iom            , ONLY :   iom_put, iom_use, iom_update_file_name
16   USE timing         , ONLY :   timing_start, timing_stop 
17   USE par_kind
18#if defined key_xios
19   USE xios
20#endif
21
22   IMPLICIT NONE
23   PRIVATE
24
25   LOGICAL, PUBLIC ::   lk_diamlr = .FALSE.   !:         ===>>>   NOT a DOCTOR norm name :  use l_diamlr
26   !                                                              lk_  is used only for logical controlled by a CPP key
27
28   PUBLIC ::   dia_mlr_init, dia_mlr_iom_init, dia_mlr
29
30   !! * Substitutions
31#  include "do_loop_substitute.h90"
32   !!----------------------------------------------------------------------
33   !! NEMO/OCE 4.0 , NEMO Consortium (2019)
34   !! $Id$
35   !! Software governed by the CeCILL license (see ./LICENSE)
36   !!----------------------------------------------------------------------
37CONTAINS
38   
39   SUBROUTINE dia_mlr_init
40      !!----------------------------------------------------------------------
41      !!                 ***  ROUTINE dia_mlr_init  ***
42      !!
43      !! ** Purpose : initialisation of IOM context management for
44      !!              multiple-linear-regression analysis
45      !!
46      !!----------------------------------------------------------------------
47      !
48      lk_diamlr = .TRUE.
49      !
50      IF(lwp) THEN
51         WRITE(numout, *)
52         WRITE(numout, *) 'dia_mlr_init : initialisation of IOM context management for'
53         WRITE(numout, *) '~~~~~~~~~~~~   multiple-linear-regression analysis'
54      END IF
55      !
56   END SUBROUTINE dia_mlr_init
57
58
59   SUBROUTINE dia_mlr_iom_init
60      !!----------------------------------------------------------------------
61      !!               ***  ROUTINE dia_mlr_iom_init  ***
62      !!
63      !! ** Purpose : IOM context setup for multiple-linear-regression
64      !!              analysis
65      !!
66      !!----------------------------------------------------------------------
67#if defined key_xios
68
69      TYPE(xios_fieldgroup)                       ::   slxhdl_fldgrp
70      TYPE(xios_filegroup)                        ::   slxhdl_filgrp
71      TYPE(xios_field), ALLOCATABLE, DIMENSION(:) ::   slxhdl_regs,    slxhdl_flds
72      TYPE(xios_field)                            ::   slxhdl_fld
73      TYPE(xios_file)                             ::   slxhdl_fil
74      LOGICAL                                     ::   llxatt_enabled, llxatt_comment
75      CHARACTER(LEN=256)                          ::   clxatt_expr,    clxatt_comment
76      CHARACTER(LEN=32)                           ::   clxatt_name1,   clxatt_name2
77      CHARACTER(LEN=32)                           ::   clxatt_gridref, clxatt_fieldref
78      INTEGER, PARAMETER                          ::   jpscanmax = 999
79      INTEGER                                     ::   ireg, ifld
80      CHARACTER(LEN=3)                            ::   cl3i
81      CHARACTER(LEN=6)                            ::   cl6a
82      CHARACTER(LEN=7)                            ::   cl7a
83      CHARACTER(LEN=1)                            ::   clgt
84      CHARACTER(LEN=2)                            ::   clgd
85      CHARACTER(LEN=25)                           ::   clfloat
86      CHARACTER(LEN=32)                           ::   clrepl
87      INTEGER                                     ::   jl, jm, jn
88      INTEGER                                     ::   itide                       ! Number of available tidal components
89      REAL(wp)                                    ::   ztide_phase                 ! Tidal-constituent phase at adatrj=0
90      CHARACTER (LEN=4), DIMENSION(jpmax_harmo)   ::   ctide_selected = 'n/a '
91      TYPE(tide_harmonic), DIMENSION(:), POINTER  ::   stideconst
92
93      IF(lwp) THEN
94         WRITE(numout, *)
95         WRITE(numout, *) 'dia_mlr_iom_init : IOM context setup for multiple-linear-regression'
96         WRITE(numout, *) '~~~~~~~~~~~~~~~~'
97      END IF
98
99      ! Get handles to multiple-linear-regression analysis configuration (field
100      ! group 'diamrl_fields' and file group 'diamlr_files'); if no suitable
101      ! configuration is found, disable diamlr
102      IF ( lk_diamlr .AND. xios_is_valid_fieldgroup( "diamlr_fields" ) .AND. xios_is_valid_field( "diamlr_time" ) .AND.   &
103         & xios_is_valid_filegroup( "diamlr_files" ) ) THEN
104         CALL xios_get_handle("diamlr_fields", slxhdl_fldgrp)
105         CALL xios_get_handle("diamlr_files",  slxhdl_filgrp)
106      ELSE
107         IF (lwp) THEN
108            WRITE(numout, *) "diamlr: configuration not found or incomplete (field group 'diamlr_fields'"
109            WRITE(numout, *) "        and/or file group 'diamlr_files' and/or field 'diamlr_time' missing);"
110            WRITE(numout, *) "        disabling output for multiple-linear-regression analysis."
111         END IF
112         lk_diamlr = .FALSE.
113      END IF
114
115      ! Set up IOM context for multiple-linear-regression analysis
116      IF ( lk_diamlr ) THEN
117
118         ! Set up output files for grid types scalar, grid_T, grid_U, grid_V,
119         ! and grid_W
120         DO jm = 1, 5
121            SELECT CASE( jm )
122            CASE( 1 )
123               cl6a = 'scalar'
124            CASE( 2 )
125               cl6a = 'grid_T'
126            CASE( 3 )
127               cl6a = 'grid_U'
128            CASE( 4 )
129               cl6a = 'grid_V'
130            CASE( 5 )
131               cl6a = 'grid_W'
132            END SELECT
133            CALL xios_add_child      ( slxhdl_filgrp, slxhdl_fil, "diamlr_file_"//cl6a )
134            CALL xios_set_attr       ( slxhdl_fil, name_suffix="_diamlr_"//cl6a,   &
135               &                       description="Intermediate output for multiple-linear-regression analysis - "//cl6a )
136            CALL iom_update_file_name( "diamlr_file_"//cl6a )
137         END DO
138
139         ! Compile lists of active regressors and of fields selected for
140         ! analysis (fields "diamlr_r<nnn>" and "diamlr_f<nnn>", where <nnn> is
141         ! a 3-digit integer); also carry out placeholder substitution of tidal
142         ! parameters in regressor expressions
143         !
144         ALLOCATE( slxhdl_regs( jpscanmax ), slxhdl_flds( jpscanmax ) )
145         ireg = 0
146         ifld = 0
147         !
148         IF ( ln_tide ) THEN
149            ! Retrieve information (frequency, phase, nodal correction) about all
150            ! available tidal constituents for placeholder substitution below
151            ! Warning: we must use the same character length in an array constructor (at least for gcc compiler)
152            ctide_selected(1:34) = (/ 'Mf  ', 'Mm  ', 'Ssa ', 'Mtm ', 'Msf ',         &
153               &                      'Msqm', 'Sa  ', 'K1  ', 'O1  ', 'P1  ',         &
154               &                      'Q1  ', 'J1  ', 'S1  ', 'M2  ', 'S2  ', 'N2  ', &
155               &                      'K2  ', 'nu2 ', 'mu2 ', '2N2 ', 'L2  ',         &
156               &                      'T2  ', 'eps2', 'lam2', 'R2  ', 'M3  ',         &
157               &                      'MKS2', 'MN4 ', 'MS4 ', 'M4  ', 'N4  ',         &
158               &                      'S4  ', 'M6  ', 'M8  ' /)
159            CALL tide_init_harmonics(ctide_selected, stideconst)
160            itide = size(stideconst)
161         ELSE
162            itide = 0
163         ENDIF
164         
165         DO jm = 1, jpscanmax
166            WRITE (cl3i, '(i3.3)') jm
167
168            ! Look for regressor
169            IF ( xios_is_valid_field( "diamlr_r"//cl3i ) ) THEN
170
171               CALL xios_get_handle( "diamlr_r"//cl3i, slxhdl_regs(ireg+1) )
172               ! Retrieve pre-configured value of "enabled" attribute and
173               ! regressor expression
174               CALL xios_get_attr  ( slxhdl_regs(ireg+1), enabled=llxatt_enabled, expr=clxatt_expr )
175               ! If enabled, keep handle in list of active regressors; also
176               ! substitute placeholders for tidal frequencies, phases, and
177               ! nodal corrections in regressor expressions
178               IF ( llxatt_enabled ) THEN
179
180                  ! Substitution of placeholders for tidal-constituent
181                  ! parameters (amplitudes, angular veloccities, nodal phase
182                  ! correction) with values that have been obtained from the
183                  ! tidal-forcing implementation (if enabled)
184                  DO jn = 1, itide
185                     ! Compute phase of tidal constituent (incl. current nodal
186                     ! correction) at the start of the model run (i.e. for
187                     ! adatrj=0)
188                     ztide_phase = MOD( stideconst(jn)%u +  stideconst(jn)%v0 - adatrj * 86400.0_wp * stideconst(jn)%omega, &
189                        & 2.0_wp * rpi )
190                     clrepl = "__TDE_"//TRIM( stideconst(jn)%cname_tide )//"_omega__"
191                     DO WHILE ( INDEX( clxatt_expr, TRIM( clrepl ) ) > 0 )
192                        WRITE (clfloat, '(e25.18)') stideconst(jn)%omega
193                        jl = INDEX( clxatt_expr, TRIM( clrepl ) )
194                        clxatt_expr = clxatt_expr(1:jl - 1)//clfloat//   &
195                           &          clxatt_expr(jl + LEN( TRIM( clrepl ) ):LEN( TRIM( clxatt_expr ) ))
196                     END DO
197                     clrepl = "__TDE_"//TRIM( stideconst(jn)%cname_tide )//"_phase__"
198                     DO WHILE ( INDEX( clxatt_expr, TRIM( clrepl ) ) > 0 )
199                        WRITE (clfloat, '(e25.18)') ztide_phase
200                        jl = INDEX( clxatt_expr, TRIM( clrepl ) )
201                        clxatt_expr = clxatt_expr(1:jl - 1)//clfloat//   &
202                           &          clxatt_expr(jl + LEN( TRIM( clrepl ) ):LEN( TRIM( clxatt_expr ) ))
203                     END DO
204                     clrepl = "__TDE_"//TRIM( stideconst(jn)%cname_tide )//"_amplitude__"
205                     DO WHILE (INDEX( clxatt_expr, TRIM( clrepl ) ) > 0 )
206                        WRITE (clfloat, '(e25.18)') stideconst(jn)%f
207                        jl = INDEX( clxatt_expr, TRIM( clrepl ) )
208                        clxatt_expr = clxatt_expr(1:jl - 1)//clfloat//   &
209                           &          clxatt_expr(jl + LEN( TRIM( clrepl ) ):LEN( TRIM( clxatt_expr ) ))
210                     END DO
211                  END DO
212
213                  ! Set standard value for comment attribute, including possible
214                  ! existing comment added in parantheses
215                  CALL xios_is_defined_attr( slxhdl_regs(ireg+1), comment=llxatt_comment )
216                  IF ( llxatt_comment ) THEN
217                     CALL xios_get_attr( slxhdl_regs(ireg+1), comment=clxatt_comment )
218                     clxatt_comment = "Regressor "//cl3i//" ("//TRIM( clxatt_comment )//") "
219                  ELSE
220                     clxatt_comment = "Regressor "//cl3i
221                  END IF
222
223                  ! Set name attribute (and overwrite possible pre-configured
224                  ! name) with field id to enable id string retrieval from
225                  ! stored handle below, re-set expression with possible
226                  ! substitutions, and set or re-set comment attribute
227                  CALL xios_set_attr  ( slxhdl_regs(ireg+1), name="diamlr_r"//cl3i, expr=TRIM( clxatt_expr ),   &
228                     &                  comment=TRIM( clxatt_comment ) )
229
230                  ireg = ireg + 1   ! Accept regressor in list of active regressors
231
232               END IF
233            END IF
234
235            ! Look for field
236            IF ( xios_is_valid_field( "diamlr_f"//cl3i ) ) THEN
237
238               CALL xios_get_handle( "diamlr_f"//cl3i, slxhdl_flds(ifld+1) )
239               ! Retrieve pre-configured value of "enabled" attribute
240               CALL xios_get_attr  ( slxhdl_flds(ifld+1), enabled=llxatt_enabled )
241               ! If enabled, keep handle in list of fields selected for analysis
242               IF ( llxatt_enabled ) THEN
243                 
244                  ! Set name attribute (and overwrite possible pre-configured name)
245                  ! with field id to enable id string retrieval from stored handle
246                  ! below
247                  CALL xios_set_attr  ( slxhdl_flds(ifld+1), name="diamlr_f"//cl3i )
248
249                  ifld = ifld + 1   ! Accept field in list of fields selected for analysis
250
251               END IF
252            END IF
253
254         END DO
255
256         ! Output number of active regressors and fields selected for analysis
257         IF ( lwp ) WRITE(numout,'(a,i3,a)' ) 'diamlr: ', ireg, ' active regressors found'
258         IF ( lwp ) WRITE(numout,'(a,i3,a)' ) 'diamlr: ', ifld, ' fields selected for analysis'
259
260         ! Set up output of minimum, maximum, and average values of the time
261         ! variable available for the computation of regressors (diamlr_time)
262         CALL xios_get_handle( "diamlr_file_scalar", slxhdl_fil )
263         CALL xios_add_child ( slxhdl_fil, slxhdl_fld, "diamlr_time_average" )
264!$AGRIF_DO_NOT_TREAT
265         CALL xios_set_attr  ( slxhdl_fld, standard_name="diamlr_time",                          &
266            &                  long_name="Elapsed model time at start of regression interval",   &
267            &                  unit="s", operation="average", field_ref="diamlr_time",           &
268            &                  grid_ref="diamlr_grid_2D_to_scalar" )
269!$AGRIF_END_DO_NOT_TREAT
270         CALL xios_add_child ( slxhdl_fil, slxhdl_fld, "diamlr_time_minimum" )
271!$AGRIF_DO_NOT_TREAT
272         CALL xios_set_attr  ( slxhdl_fld, standard_name="diamlr_time",                          &
273            &                  long_name="Elapsed model time at start of regression interval",   &
274            &                  unit="s", operation="minimum", field_ref="diamlr_time",           &
275            &                  grid_ref="diamlr_grid_2D_to_scalar" )
276!$AGRIF_END_DO_NOT_TREAT
277         CALL xios_add_child ( slxhdl_fil, slxhdl_fld, "diamlr_time_maximum" )
278!$AGRIF_DO_NOT_TREAT
279         CALL xios_set_attr  ( slxhdl_fld, standard_name="diamlr_time",                          &
280            &                  long_name="Elapsed model time at start of regression interval",   &
281            &                  unit="s", operation="maximum", field_ref="diamlr_time",           &
282            &                  grid_ref="diamlr_grid_2D_to_scalar" )
283!$AGRIF_END_DO_NOT_TREAT
284
285         ! For each active regressor:
286         DO jm = 1, ireg
287
288            !   i) set up 2-dimensional and 3-dimensional versions of the
289            !      regressors; explicitely set "enabled" attribute; note, while
290            !      the scalar versions of regressors are part of the
291            !      configuration, the respective 2-dimensional versions take
292            !      over the defining expression, while the scalar and
293            !      3-dimensional versions are simply obtained via grid
294            !      transformations from the 2-dimensional version.
295            CALL xios_get_attr  ( slxhdl_regs( jm ), name=clxatt_name1, expr=clxatt_expr,              &
296               &                  enabled=llxatt_enabled, comment=clxatt_comment )
297            CALL xios_add_child ( slxhdl_fldgrp, slxhdl_fld, TRIM( clxatt_name1 )//"_grid_T_2D" )
298            CALL xios_set_attr  ( slxhdl_fld, expr=TRIM( clxatt_expr ), grid_ref="diamlr_grid_T_2D",     &
299               &                  field_ref="diamlr_time", enabled=llxatt_enabled )
300            CALL xios_add_child ( slxhdl_fldgrp, slxhdl_fld, TRIM( clxatt_name1 )//"_grid_U_2D" )
301            CALL xios_set_attr  ( slxhdl_fld, expr=TRIM( clxatt_expr ), grid_ref="diamlr_grid_U_2D",     &
302               &                  field_ref="diamlr_time", enabled=llxatt_enabled )
303            CALL xios_add_child ( slxhdl_fldgrp, slxhdl_fld, TRIM( clxatt_name1 )//"_grid_V_2D" )
304            CALL xios_set_attr  ( slxhdl_fld, expr=TRIM( clxatt_expr ), grid_ref="diamlr_grid_V_2D",     &
305               &                  field_ref="diamlr_time", enabled=llxatt_enabled )
306            CALL xios_add_child ( slxhdl_fldgrp, slxhdl_fld, TRIM( clxatt_name1 )//"_grid_W_2D" )
307            CALL xios_set_attr  ( slxhdl_fld, expr=TRIM( clxatt_expr ), grid_ref="diamlr_grid_W_2D",     &
308               &                  field_ref="diamlr_time", enabled=llxatt_enabled )
309            CALL xios_add_child ( slxhdl_fldgrp, slxhdl_fld, TRIM( clxatt_name1 )//"_grid_T_3D")
310            CALL xios_set_attr  ( slxhdl_fld, expr="this", grid_ref="diamlr_grid_2D_to_grid_T_3D",            &
311               &                  field_ref=TRIM( clxatt_name1 )//"_grid_T_2D", enabled=llxatt_enabled)
312            CALL xios_add_child ( slxhdl_fldgrp, slxhdl_fld, TRIM( clxatt_name1 )//"_grid_U_3D")
313            CALL xios_set_attr  ( slxhdl_fld, expr="this", grid_ref="diamlr_grid_2D_to_grid_U_3D",            &
314               &                  field_ref=TRIM( clxatt_name1 )//"_grid_U_2D", enabled=llxatt_enabled)
315            CALL xios_add_child ( slxhdl_fldgrp, slxhdl_fld, TRIM( clxatt_name1 )//"_grid_V_3D")
316            CALL xios_set_attr  ( slxhdl_fld, expr="this", grid_ref="diamlr_grid_2D_to_grid_V_3D",            &
317               &                  field_ref=TRIM( clxatt_name1 )//"_grid_V_2D", enabled=llxatt_enabled)
318            CALL xios_add_child ( slxhdl_fldgrp, slxhdl_fld, TRIM( clxatt_name1 )//"_grid_W_3D")
319            CALL xios_set_attr  ( slxhdl_fld, expr="this", grid_ref="diamlr_grid_2D_to_grid_W_3D",            &
320               &                  field_ref=TRIM( clxatt_name1 )//"_grid_W_2D", enabled=llxatt_enabled)
321            CALL xios_set_attr  ( slxhdl_regs(jm), expr="this", grid_ref="diamlr_grid_2D_to_scalar",   &
322               &                  field_ref=TRIM( clxatt_name1 )//"_grid_T_2D", enabled=llxatt_enabled)
323
324            !  ii) set up output of active regressors, including metadata
325            CALL xios_get_handle( "diamlr_file_scalar", slxhdl_fil )
326            ! Add regressor to output file
327            CALL xios_add_child ( slxhdl_fil, slxhdl_fld, TRIM( clxatt_name1 ) )
328            CALL xios_set_attr  ( slxhdl_fld, standard_name=TRIM( clxatt_comment ), long_name=TRIM( clxatt_expr ),   &
329               &                  operation="average" )
330               
331            ! iii) set up the output of scalar products with itself and with
332            !      other active regressors
333            CALL xios_get_attr  ( slxhdl_regs(jm), name=clxatt_name1 )
334            DO jn = 1, jm
335               ! Field for product between regressors
336               CALL xios_get_attr  ( slxhdl_regs(jn), name=clxatt_name2 )
337               CALL xios_add_child ( slxhdl_fldgrp, slxhdl_fld, TRIM( clxatt_name1 )//"."//TRIM( clxatt_name2 ) )
338               ! Set appropriate name attribute to avoid the possibility of
339               ! using an inappropriate inherited name attribute as the variable
340               ! name in the output file
341               CALL xios_set_attr  ( slxhdl_fld,                                                        &
342                  &                  name=TRIM( clxatt_name1 )//"."//TRIM( clxatt_name2 ),              &
343                  &                  grid_ref="diamlr_grid_scalar",                                     &
344                  &                  expr="this * "//TRIM( clxatt_name2 ),                              &
345                  &                  field_ref=TRIM( clxatt_name1 ),                                    &
346                  &                  enabled=llxatt_enabled,                                            &
347                  &                  long_name="Scalar product of regressor "//TRIM( clxatt_name1 )//   &
348                  &                     " and regressor "//TRIM( clxatt_name2 ),                        &
349                  &                  standard_name=TRIM( clxatt_name1 )//"."//TRIM( clxatt_name2 ),     &
350                  &                  operation="accumulate")
351               ! Add regressor-product field to output file
352               CALL xios_add_child ( slxhdl_fil, slxhdl_fld, TRIM( clxatt_name1 )//"."//TRIM( clxatt_name2 ) )
353            END DO
354
355            !  iv) set up definitions for the output of scalar products with
356            !      fields selected for analysis
357            DO jn = 1, ifld
358               CALL xios_get_attr  ( slxhdl_flds(jn), name=clxatt_name2, field_ref=clxatt_fieldref )
359               CALL xios_get_handle( TRIM( clxatt_fieldref ), slxhdl_fld )
360               CALL xios_get_attr  ( slxhdl_fld, grid_ref=clxatt_gridref )
361               clgt="T"
362               IF ( INDEX( clxatt_gridref, "_U_" ) > 0 ) clgt="U"
363               IF ( INDEX( clxatt_gridref, "_V_" ) > 0 ) clgt="V"
364               IF ( INDEX( clxatt_gridref, "_W_" ) > 0 ) clgt="W"
365               clgd="2D"
366               cl7a=""
367               IF ( INDEX( clxatt_gridref, "_3D" ) > 0 ) THEN
368                  clgd="3D"
369               ELSE
370                  cl7a="diamlr_"
371               END IF
372               CALL xios_add_child ( slxhdl_fldgrp, slxhdl_fld, TRIM( clxatt_name2 )//"."//TRIM( clxatt_name1 ) )
373               ! Set appropriate name attribute to avoid the possibility of
374               ! using an inappropriate inherited name attribute as the variable
375               ! name in the output file; use metadata (standard_name and
376               ! long_name) to refer to the id of the analysed field
377               CALL xios_set_attr  ( slxhdl_fld,                                                         &
378                  &                  name=TRIM( clxatt_name2 )//"."//TRIM( clxatt_name1 ),               &
379                  &                  expr="this * "//TRIM( clxatt_fieldref ),                            &
380                  &                  grid_ref=cl7a//"grid_"//clgt//"_"//clgd,                                      &
381                  &                  field_ref=TRIM( clxatt_name1 )//"_grid_"//clgt//"_"//clgd,          &
382                  &                  enabled=llxatt_enabled,                                             &
383                  &                  long_name="Scalar product of "//TRIM( clxatt_fieldref )//           &
384                  &                     " and regressor "//TRIM( clxatt_name1 ),                         &
385                  &                  standard_name=TRIM( clxatt_fieldref )//"."//TRIM( clxatt_name1 ),   &
386                  &                  operation="accumulate" )
387               CALL xios_get_handle( "diamlr_file_grid_"//clgt, slxhdl_fil )
388               CALL xios_add_child ( slxhdl_fil, slxhdl_fld, TRIM( clxatt_name2 )//"."//TRIM( clxatt_name1 ) )
389            END DO
390
391         END DO
392
393         ! Release list of active regressors and fields selected for analysis
394         DEALLOCATE( slxhdl_regs, slxhdl_flds )
395
396      END IF
397#else
398      IF( .FALSE. ) write(numout,*) 'dia_mlr_iom_init: should not see this'    ! useless statement to avoid compiler warnings
399#endif
400
401   END SUBROUTINE dia_mlr_iom_init
402
403
404   SUBROUTINE dia_mlr
405      !!----------------------------------------------------------------------
406      !!                   ***  ROUTINE dia_mlr  ***
407      !!
408      !! ** Purpose : update time used in multiple-linear-regression analysis
409      !!
410      !!----------------------------------------------------------------------
411      REAL(wp), DIMENSION(jpi,jpj) ::   zadatrj2d
412      !!----------------------------------------------------------------------
413
414      IF( ln_timing )   CALL timing_start('dia_mlr')
415
416      ! Update time to the continuous time since the start of the model run
417      ! (value of adatrj converted to time in units of seconds)
418      !
419      ! A 2-dimensional field of constant value is sent, and subsequently used directly
420      ! or transformed to a scalar or a constant 3-dimensional field as required.
421      zadatrj2d(:,:) = adatrj*86400.0_wp
422      IF ( iom_use('diamlr_time') ) CALL iom_put('diamlr_time', zadatrj2d)
423      !
424      IF( ln_timing )   CALL timing_stop('dia_mlr')
425      !
426   END SUBROUTINE dia_mlr
427
428   !!======================================================================
429END MODULE diamlr
Note: See TracBrowser for help on using the repository browser.