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/2019/dev_r11879_ENHANCE-05_SimonM-Harmonic_Analysis/src/OCE/DIA – NEMO

source: NEMO/branches/2019/dev_r11879_ENHANCE-05_SimonM-Harmonic_Analysis/src/OCE/DIA/diamlr.F90 @ 12097

Last change on this file since 12097 was 12097, checked in by smueller, 4 years ago

Addition of AGRIF directives to enable compilation with key_agrif (ticket #2175)

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