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.
dtatsd.F90 in NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/DOM – NEMO

source: NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/DOM/dtatsd.F90 @ 11482

Last change on this file since 11482 was 11482, checked in by andmirek, 5 years ago

Ticket #2195 read initial conditions with XIOS

  • Property svn:keywords set to Id
File size: 20.1 KB
Line 
1MODULE dtatsd
2   !!======================================================================
3   !!                     ***  MODULE  dtatsd  ***
4   !! Ocean data  :  read ocean Temperature & Salinity Data from gridded data
5   !!======================================================================
6   !! History :  OPA  ! 1991-03  ()  Original code
7   !!             -   ! 1992-07  (M. Imbard)
8   !!            8.0  ! 1999-10  (M.A. Foujols, M. Imbard)  NetCDF FORMAT
9   !!   NEMO     1.0  ! 2002-06  (G. Madec)  F90: Free form and module
10   !!            3.3  ! 2010-10  (C. Bricaud, S. Masson)  use of fldread
11   !!            3.4  ! 2010-11  (G. Madec, C. Ethe) Merge of dtatem and dtasal + remove CPP keys
12   !!----------------------------------------------------------------------
13
14   !!----------------------------------------------------------------------
15   !!   dta_tsd      : read and time interpolated ocean Temperature & Salinity Data
16   !!----------------------------------------------------------------------
17   USE oce             ! ocean dynamics and tracers
18   USE phycst          ! physical constants
19   USE dom_oce         ! ocean space and time domain
20   USE fldread         ! read input fields
21   !
22   USE in_out_manager  ! I/O manager
23   USE lib_mpp         ! MPP library
24   USE iom, ONLY : iom_swap, iom_setkt, iom_context_finalize
25   USE lbclnk          ! lateal boundary condition / mpp exchanges
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   dta_tsd_init   ! called by opa.F90
31   PUBLIC   dta_tsd        ! called by istate.F90 and tradmp.90
32   PUBLIC   iom_dta_tsd_init
33
34   !                                  !!* namtsd  namelist : Temperature & Salinity Data *
35   LOGICAL , PUBLIC ::   ln_tsd_init   !: T & S data flag
36   LOGICAL , PUBLIC ::   ln_tsd_dmp    !: internal damping toward input data flag
37   LOGICAL , PRIVATE::   ln_tsd_xios
38
39   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_tsd   ! structure of input SST (file informations, fields read)
40   CHARACTER(lc), PUBLIC                ::   cinit_context    !: context name used in xios
41
42   !!----------------------------------------------------------------------
43   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
44   !! $Id$
45   !! Software governed by the CeCILL license (see ./LICENSE)
46   !!----------------------------------------------------------------------
47CONTAINS
48
49   SUBROUTINE dta_tsd_init( ld_tradmp )
50      !!----------------------------------------------------------------------
51      !!                   ***  ROUTINE dta_tsd_init  ***
52      !!                   
53      !! ** Purpose :   initialisation of T & S input data
54      !!
55      !! ** Method  : - Read namtsd namelist
56      !!              - allocates T & S data structure
57      !!----------------------------------------------------------------------
58      LOGICAL, INTENT(in), OPTIONAL ::   ld_tradmp   ! force the initialization when tradp is used
59      !
60      INTEGER ::   ios, ierr0, ierr1, ierr2, ierr3   ! local integers
61      !!
62      CHARACTER(len=100)            ::   cn_dir          ! Root directory for location of ssr files
63      TYPE(FLD_N), DIMENSION( jpts) ::   slf_i           ! array of namelist informations on the fields to read
64      TYPE(FLD_N)                   ::   sn_tem, sn_sal
65      !!
66      NAMELIST/namtsd/   ln_tsd_init, ln_tsd_dmp, cn_dir, sn_tem, sn_sal, ln_tsd_xios
67      !!----------------------------------------------------------------------
68      !
69      !  Initialisation
70      ierr0 = 0  ;  ierr1 = 0  ;  ierr2 = 0  ;  ierr3 = 0
71      !
72      REWIND( numnam_ref )              ! Namelist namtsd in reference namelist :
73      READ  ( numnam_ref, namtsd, IOSTAT = ios, ERR = 901)
74901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtsd in reference namelist', lwp )
75      REWIND( numnam_cfg )              ! Namelist namtsd in configuration namelist : Parameters of the run
76      READ  ( numnam_cfg, namtsd, IOSTAT = ios, ERR = 902 )
77902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtsd in configuration namelist', lwp )
78      IF(lwm) WRITE ( numond, namtsd )
79
80      IF( PRESENT( ld_tradmp ) )   ln_tsd_dmp = .TRUE.     ! forces the initialization when tradmp is used
81     
82      IF(lwp) THEN                  ! control print
83         WRITE(numout,*)
84         WRITE(numout,*) 'dta_tsd_init : Temperature & Salinity data '
85         WRITE(numout,*) '~~~~~~~~~~~~ '
86         WRITE(numout,*) '   Namelist namtsd'
87         WRITE(numout,*) '      Initialisation of ocean T & S with T &S input data   ln_tsd_init = ', ln_tsd_init
88         WRITE(numout,*) '      damping of ocean T & S toward T &S input data        ln_tsd_dmp  = ', ln_tsd_dmp
89         WRITE(numout,*)
90         IF( .NOT.ln_tsd_init .AND. .NOT.ln_tsd_dmp ) THEN
91            WRITE(numout,*)
92            WRITE(numout,*) '   ===>>   T & S data not used'
93         ENDIF
94      ENDIF
95      !
96      IF( ln_rstart .AND. ln_tsd_init ) THEN
97         CALL ctl_warn( 'dta_tsd_init: ocean restart and T & S data intialisation, ',   &
98            &           'we keep the restart T & S values and set ln_tsd_init to FALSE' )
99         ln_tsd_init = .FALSE.
100      ENDIF
101      !
102      !                             ! allocate the arrays (if necessary)
103      IF( ln_tsd_init .OR. ln_tsd_dmp ) THEN
104         !
105         ALLOCATE( sf_tsd(jpts), STAT=ierr0 )
106         IF( ierr0 > 0 ) THEN
107            CALL ctl_stop( 'dta_tsd_init: unable to allocate sf_tsd structure' )   ;   RETURN
108         ENDIF
109         !
110                                ALLOCATE( sf_tsd(jp_tem)%fnow(jpi,jpj,jpk)   , STAT=ierr0 )
111         IF( sn_tem%ln_tint )   ALLOCATE( sf_tsd(jp_tem)%fdta(jpi,jpj,jpk,2) , STAT=ierr1 )
112                                ALLOCATE( sf_tsd(jp_sal)%fnow(jpi,jpj,jpk)   , STAT=ierr2 )
113         IF( sn_sal%ln_tint )   ALLOCATE( sf_tsd(jp_sal)%fdta(jpi,jpj,jpk,2) , STAT=ierr3 )
114         !
115         IF( ierr0 + ierr1 + ierr2 + ierr3 > 0 ) THEN
116            CALL ctl_stop( 'dta_tsd : unable to allocate T & S data arrays' )   ;   RETURN
117         ENDIF
118         !                         ! fill sf_tsd with sn_tem & sn_sal and control print
119         slf_i(jp_tem) = sn_tem   ;   slf_i(jp_sal) = sn_sal
120         CALL fld_fill( sf_tsd, slf_i, cn_dir, 'dta_tsd', 'Temperature & Salinity data', 'namtsd', no_print )
121         cinit_context = 'dta_tsd_init'
122         IF( ln_tsd_xios) CALL iom_dta_tsd_init( cinit_context )
123         !
124      ENDIF
125      !
126   END SUBROUTINE dta_tsd_init
127
128
129   SUBROUTINE dta_tsd( kt, ptsd )
130#if defined key_iomput
131      use xios, ONLY : xios_recv_field
132#endif
133      !!----------------------------------------------------------------------
134      !!                   ***  ROUTINE dta_tsd  ***
135      !!                   
136      !! ** Purpose :   provides T and S data at kt
137      !!
138      !! ** Method  : - call fldread routine
139      !!              - ORCA_R2: add some hand made alteration to read data 
140      !!              - 'key_orca_lev10' interpolates on 10 times more levels
141      !!              - s- or mixed z-s coordinate: vertical interpolation on model mesh
142      !!              - ln_tsd_dmp=F: deallocates the T-S data structure
143      !!                as T-S data are no are used
144      !!
145      !! ** Action  :   ptsd   T-S data on medl mesh and interpolated at time-step kt
146      !!----------------------------------------------------------------------
147      INTEGER                              , INTENT(in   ) ::   kt     ! ocean time-step
148      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(  out) ::   ptsd   ! T & S data
149      !
150      INTEGER ::   ji, jj, jk, jl, jkk   ! dummy loop indicies
151      INTEGER ::   ik, il0, il1, ii0, ii1, ij0, ij1   ! local integers
152      REAL(wp)::   zl, zi                             ! local scalars
153      REAL(wp), DIMENSION(jpk) ::  ztp, zsp   ! 1D workspace
154      !!----------------------------------------------------------------------
155      !
156      IF(ln_tsd_xios) CALL iom_swap(cinit_context) 
157      CALL fld_read( kt, 1, sf_tsd, ldxios = ln_tsd_xios)      !==   read T & S data at kt time step   ==!
158      IF(kt == nitend .OR. (.NOT.ln_tsd_dmp) .AND. ln_tsd_xios)  CALL iom_context_finalize( cinit_context )
159      CALL iom_swap( cxios_context )
160      !
161      !
162!!gm  This should be removed from the code   ===>>>>  T & S files has to be changed
163      !
164      !                                   !==   ORCA_R2 configuration and T & S damping   ==!
165      IF( cn_cfg == "orca" .OR. cn_cfg == "ORCA" ) THEN
166         IF( nn_cfg == 2 .AND. ln_tsd_dmp ) THEN    ! some hand made alterations
167            !
168            ij0 = 101   ;   ij1 = 109                       ! Reduced T & S in the Alboran Sea
169            ii0 = 141   ;   ii1 = 155
170            DO jj = mj0(ij0), mj1(ij1)
171               DO ji = mi0(ii0), mi1(ii1)
172                  sf_tsd(jp_tem)%fnow(ji,jj,13:13) = sf_tsd(jp_tem)%fnow(ji,jj,13:13) - 0.20_wp
173                  sf_tsd(jp_tem)%fnow(ji,jj,14:15) = sf_tsd(jp_tem)%fnow(ji,jj,14:15) - 0.35_wp
174                  sf_tsd(jp_tem)%fnow(ji,jj,16:25) = sf_tsd(jp_tem)%fnow(ji,jj,16:25) - 0.40_wp
175                  !
176                  sf_tsd(jp_sal)%fnow(ji,jj,13:13) = sf_tsd(jp_sal)%fnow(ji,jj,13:13) - 0.15_wp
177                  sf_tsd(jp_sal)%fnow(ji,jj,14:15) = sf_tsd(jp_sal)%fnow(ji,jj,14:15) - 0.25_wp
178                  sf_tsd(jp_sal)%fnow(ji,jj,16:17) = sf_tsd(jp_sal)%fnow(ji,jj,16:17) - 0.30_wp
179                  sf_tsd(jp_sal)%fnow(ji,jj,18:25) = sf_tsd(jp_sal)%fnow(ji,jj,18:25) - 0.35_wp
180               END DO
181            END DO
182            ij0 =  87   ;   ij1 =  96                          ! Reduced temperature in Red Sea
183            ii0 = 148   ;   ii1 = 160
184            sf_tsd(jp_tem)%fnow( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ,  4:10 ) = 7.0_wp
185            sf_tsd(jp_tem)%fnow( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) , 11:13 ) = 6.5_wp
186            sf_tsd(jp_tem)%fnow( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) , 14:20 ) = 6.0_wp
187         ENDIF
188      ENDIF
189!!gm end
190      !
191      ptsd(:,:,:,jp_tem) = sf_tsd(jp_tem)%fnow(:,:,:)    ! NO mask
192      ptsd(:,:,:,jp_sal) = sf_tsd(jp_sal)%fnow(:,:,:) 
193      !
194      IF( ln_sco ) THEN                   !==   s- or mixed s-zps-coordinate   ==!
195         !
196         IF( kt == nit000 .AND. lwp )THEN
197            WRITE(numout,*)
198            WRITE(numout,*) 'dta_tsd: interpolates T & S data onto the s- or mixed s-z-coordinate mesh'
199         ENDIF
200         !
201         DO jj = 1, jpj                         ! vertical interpolation of T & S
202            DO ji = 1, jpi
203               DO jk = 1, jpk                        ! determines the intepolated T-S profiles at each (i,j) points
204                  zl = gdept_0(ji,jj,jk)
205                  IF(     zl < gdept_1d(1  ) ) THEN          ! above the first level of data
206                     ztp(jk) =  ptsd(ji,jj,1    ,jp_tem)
207                     zsp(jk) =  ptsd(ji,jj,1    ,jp_sal)
208                  ELSEIF( zl > gdept_1d(jpk) ) THEN          ! below the last level of data
209                     ztp(jk) =  ptsd(ji,jj,jpkm1,jp_tem)
210                     zsp(jk) =  ptsd(ji,jj,jpkm1,jp_sal)
211                  ELSE                                      ! inbetween : vertical interpolation between jkk & jkk+1
212                     DO jkk = 1, jpkm1                                  ! when  gdept(jkk) < zl < gdept(jkk+1)
213                        IF( (zl-gdept_1d(jkk)) * (zl-gdept_1d(jkk+1)) <= 0._wp ) THEN
214                           zi = ( zl - gdept_1d(jkk) ) / (gdept_1d(jkk+1)-gdept_1d(jkk))
215                           ztp(jk) = ptsd(ji,jj,jkk,jp_tem) + ( ptsd(ji,jj,jkk+1,jp_tem) - ptsd(ji,jj,jkk,jp_tem) ) * zi 
216                           zsp(jk) = ptsd(ji,jj,jkk,jp_sal) + ( ptsd(ji,jj,jkk+1,jp_sal) - ptsd(ji,jj,jkk,jp_sal) ) * zi
217                        ENDIF
218                     END DO
219                  ENDIF
220               END DO
221               DO jk = 1, jpkm1
222                  ptsd(ji,jj,jk,jp_tem) = ztp(jk) * tmask(ji,jj,jk)     ! mask required for mixed zps-s-coord
223                  ptsd(ji,jj,jk,jp_sal) = zsp(jk) * tmask(ji,jj,jk)
224               END DO
225               ptsd(ji,jj,jpk,jp_tem) = 0._wp
226               ptsd(ji,jj,jpk,jp_sal) = 0._wp
227            END DO
228         END DO
229         !
230      ELSE                                !==   z- or zps- coordinate   ==!
231         !                             
232         ptsd(:,:,:,jp_tem) = ptsd(:,:,:,jp_tem) * tmask(:,:,:)    ! Mask
233         ptsd(:,:,:,jp_sal) = ptsd(:,:,:,jp_sal) * tmask(:,:,:)
234         !
235         IF( ln_zps ) THEN                      ! zps-coordinate (partial steps) interpolation at the last ocean level
236            DO jj = 1, jpj
237               DO ji = 1, jpi
238                  ik = mbkt(ji,jj) 
239                  IF( ik > 1 ) THEN
240                     zl = ( gdept_1d(ik) - gdept_0(ji,jj,ik) ) / ( gdept_1d(ik) - gdept_1d(ik-1) )
241                     ptsd(ji,jj,ik,jp_tem) = (1.-zl) * ptsd(ji,jj,ik,jp_tem) + zl * ptsd(ji,jj,ik-1,jp_tem)
242                     ptsd(ji,jj,ik,jp_sal) = (1.-zl) * ptsd(ji,jj,ik,jp_sal) + zl * ptsd(ji,jj,ik-1,jp_sal)
243                  ENDIF
244                  ik = mikt(ji,jj)
245                  IF( ik > 1 ) THEN
246                     zl = ( gdept_0(ji,jj,ik) - gdept_1d(ik) ) / ( gdept_1d(ik+1) - gdept_1d(ik) ) 
247                     ptsd(ji,jj,ik,jp_tem) = (1.-zl) * ptsd(ji,jj,ik,jp_tem) + zl * ptsd(ji,jj,ik+1,jp_tem)
248                     ptsd(ji,jj,ik,jp_sal) = (1.-zl) * ptsd(ji,jj,ik,jp_sal) + zl * ptsd(ji,jj,ik+1,jp_sal)
249                  END IF
250               END DO
251            END DO
252         ENDIF
253         !
254      ENDIF
255      !
256      IF( .NOT.ln_tsd_dmp ) THEN                   !==   deallocate T & S structure   ==!
257         !                                              (data used only for initialisation)
258         IF(lwp) WRITE(numout,*) 'dta_tsd: deallocte T & S arrays as they are only use to initialize the run'
259                                        DEALLOCATE( sf_tsd(jp_tem)%fnow )     ! T arrays in the structure
260         IF( sf_tsd(jp_tem)%ln_tint )   DEALLOCATE( sf_tsd(jp_tem)%fdta )
261                                        DEALLOCATE( sf_tsd(jp_sal)%fnow )     ! S arrays in the structure
262         IF( sf_tsd(jp_sal)%ln_tint )   DEALLOCATE( sf_tsd(jp_sal)%fdta )
263                                        DEALLOCATE( sf_tsd              )     ! the structure itself
264      ENDIF
265      !
266   END SUBROUTINE dta_tsd
267
268   SUBROUTINE iom_dta_tsd_init( cdname, ld_tmppatch ) 
269#if defined key_iomput
270      use xios
271#endif
272      !!----------------------------------------------------------------------
273      !!                     ***  ROUTINE   ***
274      !!
275      !! ** Purpose :   initialize context for reading T & S input data
276      !!                to replace fld_ intrerface with XIOS to read initial
277      !!                conditions. Have it separated from other conditions
278      !!                because initialization happens before model starts
279      !!                time stepping.
280      !!
281      !!----------------------------------------------------------------------
282      CHARACTER(len=*),           INTENT(in)  :: cdname
283      LOGICAL         , OPTIONAL, INTENT(in)  :: ld_tmppatch
284#if defined key_iomput
285      !
286      CHARACTER(len=lc) :: clname
287      INTEGER, PARAMETER :: lstr = 256  !: length of the string set to 256
288      INTEGER           :: ji, jkmin
289      LOGICAL ::   ll_tmppatch = .TRUE.    !: seb: patch before we remove periodicity
290      INTEGER ::   nldi_save, nlei_save    !:      and close boundaries in output files
291      INTEGER ::   nldj_save, nlej_save    !:
292      LOGICAL ::   ll_global = .FALSE.     !: do we have variable on model grid
293      CHARACTER(len=lc), DIMENSION( jpts) :: cg_name(jpts)
294      CHARACTER(len=1), DIMENSION( 5)   :: cname
295      CHARACTER(len=lstr)               :: cfname ! file name without .nc
296      TYPE(xios_duration)               :: dtime    = xios_duration(0, 0, 0, 0, 0, 0), &
297                                           outp_frq = xios_duration(0, 0, 0, 0, 0, 0)
298      TYPE(xios_domaingroup)            :: domaingroup_hdl
299      TYPE(xios_domain)                 :: domain_hdl
300      TYPE(xios_axisgroup)              :: axisgroup_hdl
301      TYPE(xios_axis)                   :: axis_hdl
302      TYPE(xios_scalar)                 :: scalar_hdl
303      TYPE(xios_scalargroup)            :: scalargroup_hdl
304      TYPE(xios_file)                   :: file_hdl
305      TYPE(xios_filegroup)              :: filegroup_hdl
306      TYPE(xios_field)                  :: field_hdl
307      INTEGER                           :: jf, ni, nj, ipos
308
309      cname(1)='a'
310      cname(2)='b'
311      cname(3)='c'
312      cname(4)='d'
313      cname(5)='e'
314      !!----------------------------------------------------------------------
315      !
316      ! seb: patch before we remove periodicity and close boundaries in output files
317      IF ( ll_tmppatch ) THEN
318         nldi_save = nldi   ;   nlei_save = nlei
319         nldj_save = nldj   ;   nlej_save = nlej
320         IF( nimpp           ==      1 ) nldi = 1
321         IF( nimpp + jpi - 1 == jpiglo ) nlei = jpi
322         IF( njmpp           ==      1 ) nldj = 1
323         IF( njmpp + jpj - 1 == jpjglo ) nlej = jpj
324      ENDIF
325      !
326      clname = cdname
327      IF( TRIM(Agrif_CFixed()) /= '0' )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(cdname)
328      CALL xios_context_initialize(TRIM(clname), mpi_comm_oce)
329      CALL iom_swap( cdname )
330      ! Calendar type is now defined in xml file
331      SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL
332      CASE ( 1)   ; CALL xios_define_calendar( TYPE = "Gregorian", time_origin = xios_date(1976,01,01,00,00,00), &
333          &                                    start_date = xios_date(1976,02,15,00,00,00) )
334      CASE ( 0)   ; CALL xios_define_calendar( TYPE = "NoLeap"   , time_origin = xios_date(1976,01,01,00,00,00), &
335          &                                    start_date = xios_date(1976,02,15,00,00,00) )
336      CASE (30)   ; CALL xios_define_calendar( TYPE = "D360"     , time_origin = xios_date(1976,01,01,00,00,00), &
337          &                                    start_date = xios_date(nyear, nmonth, nday, 00, 00, 00) )
338      END SELECT
339
340      DO jf = 1, SIZE(sf_tsd)
341         IF( LEN( TRIM(sf_tsd(jf)%wgtname) ) > 0) THEN
342            STOP 'IMPLEMENTATION NOT FINISHED'
343         ELSE
344            IF(.NOT. ll_global) THEN
345               CALL xios_get_handle("domain_definition",domaingroup_hdl)
346               CALL xios_add_child(domaingroup_hdl, domain_hdl, "grid_global")
347               ni = nlei-nldi+1
348               nj = nlej-nldj+1
349               CALL xios_set_domain_attr("grid_global", ni_glo=jpiglo, nj_glo=jpjglo, ibegin=nimpp+nldi-2, jbegin=njmpp+nldj-2, ni=ni, nj=nj)
350               CALL xios_set_domain_attr("grid_global", data_dim=2, data_ibegin = 1-nldi, data_ni = jpi, data_jbegin = 1-nldj, data_nj = jpj)
351               CALL xios_set_domain_attr("grid_global", type='curvilinear')
352               ll_global = .TRUE.
353            ENDIF
354         ENDIF
355      ENDDO
356
357      CALL xios_get_handle("axis_definition",axisgroup_hdl)
358      CALL xios_add_child(axisgroup_hdl, axis_hdl, "depth")
359      CALL xios_set_axis_attr     ("depth" , n_glo= jpk)
360
361
362      CALL xios_get_handle("file_definition", filegroup_hdl )
363 
364      DO jf = 1, SIZE(sf_tsd)
365
366         IF(sf_tsd(jf)%nfreqh < 0 ) THEN
367           outp_frq%month = -sf_tsd(jf)%nfreqh
368         ELSE
369           outp_frq%hour = sf_tsd(jf)%nfreqh
370         ENDIF
371         CALL xios_add_child(filegroup_hdl, file_hdl, cname(jf))
372         ipos = index(sf_tsd(jf)%clrootname,'.nc')
373         cfname(1:lstr) = " "
374         IF(ipos > 0) THEN
375          cfname(1:ipos-1) = sf_tsd(jf)%clrootname(1:ipos-1)
376         ELSE
377          cfname(1:lstr) = sf_tsd(jf)%clrootname(1:lstr)
378         ENDIF
379         CALL xios_set_file_attr( cname(jf), name=TRIM(cfname),  &
380                type="one_file", time_counter_name="time", &
381                par_access="collective", enabled=.TRUE., mode="read", &
382                output_freq=outp_frq, time_units = "days")
383         CALL xios_add_child(file_hdl, field_hdl, TRIM(sf_tsd(jf)%clvar))
384         CALL xios_set_attr (field_hdl, enabled = .TRUE., &
385                          name = TRIM(sf_tsd(jf)%clvar), domain_ref="grid_global", &
386                          axis_ref="depth", operation = "instant") 
387      ENDDO
388
389      dtime%month = 1
390      CALL xios_set_timestep( dtime )
391      CALL xios_close_context_definition()
392      CALL xios_update_calendar( 0 )
393
394      IF ( ll_tmppatch ) THEN
395         nldi = nldi_save   ;   nlei = nlei_save
396         nldj = nldj_save   ;   nlej = nlej_save
397      ENDIF
398#endif
399      !
400   END SUBROUTINE iom_dta_tsd_init
401
402
403   !!======================================================================
404END MODULE dtatsd
Note: See TracBrowser for help on using the repository browser.