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.
fldread.F90 in branches/2016/dev_r6711_SIMPLIF_6_aerobulk/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2016/dev_r6711_SIMPLIF_6_aerobulk/NEMOGCM/NEMO/OPA_SRC/SBC/fldread.F90 @ 7163

Last change on this file since 7163 was 7163, checked in by gm, 7 years ago

#1751 - branch SIMPLIF_6_aerobulk: update option control in sbcmod + uniformization of print in ocean_output (many module involved)

  • Property svn:keywords set to Id
File size: 85.6 KB
Line 
1MODULE fldread
2   !!======================================================================
3   !!                       ***  MODULE  fldread  ***
4   !! Ocean forcing:  read input field for surface boundary condition
5   !!=====================================================================
6   !! History :  2.0  !  2006-06  (S. Masson, G. Madec)  Original code
7   !!            3.0  !  2008-05  (S. Alderson)  Modified for Interpolation in memory from input grid to model grid
8   !!            3.4  !  2013-10  (D. Delrosso, P. Oddo)  suppression of land point prior to interpolation
9   !!----------------------------------------------------------------------
10
11   !!----------------------------------------------------------------------
12   !!   fld_read      : read input fields used for the computation of the surface boundary condition
13   !!   fld_init      : initialization of field read
14   !!   fld_rec       : determined the record(s) to be read
15   !!   fld_get       : read the data
16   !!   fld_map       : read global data from file and map onto local data using a general mapping (use for open boundaries)
17   !!   fld_rot       : rotate the vector fields onto the local grid direction
18   !!   fld_clopn     : update the data file name and close/open the files
19   !!   fld_fill      : fill the data structure with the associated information read in namelist
20   !!   wgt_list      : manage the weights used for interpolation
21   !!   wgt_print     : print the list of known weights
22   !!   fld_weight    : create a WGT structure and fill in data from file, restructuring as required
23   !!   apply_seaoverland : fill land with ocean values
24   !!   seaoverland   : create shifted matrices for seaoverland application
25   !!   fld_interp    : apply weights to input gridded data to create data on model grid
26   !!   ksec_week     : function returning the first 3 letters of the first day of the weekly file
27   !!----------------------------------------------------------------------
28   USE oce            ! ocean dynamics and tracers
29   USE dom_oce        ! ocean space and time domain
30   USE phycst         ! physical constant
31   USE sbc_oce        ! surface boundary conditions : fields
32   USE geo2ocean      ! for vector rotation on to model grid
33   !
34   USE in_out_manager ! I/O manager
35   USE iom            ! I/O manager library
36   USE ioipsl  , ONLY : ymds2ju, ju2ymds   ! for calendar
37   USE lib_mpp        ! MPP library
38   USE wrk_nemo       ! work arrays
39   USE lbclnk         ! ocean lateral boundary conditions (C1D case)
40   
41   IMPLICIT NONE
42   PRIVATE   
43 
44   PUBLIC   fld_map    ! routine called by tides_init
45   PUBLIC   fld_read, fld_fill   ! called by sbc... modules
46   PUBLIC   fld_clopn
47
48   TYPE, PUBLIC ::   FLD_N      !: Namelist field informations
49      CHARACTER(len = 256) ::   clname      ! generic name of the NetCDF flux file
50      REAL(wp)             ::   nfreqh      ! frequency of each flux file
51      CHARACTER(len = 34)  ::   clvar       ! generic name of the variable in the NetCDF flux file
52      LOGICAL              ::   ln_tint     ! time interpolation or not (T/F)
53      LOGICAL              ::   ln_clim     ! climatology or not (T/F)
54      CHARACTER(len = 8)   ::   cltype      ! type of data file 'daily', 'monthly' or yearly'
55      CHARACTER(len = 256) ::   wname       ! generic name of a NetCDF weights file to be used, blank if not
56      CHARACTER(len = 34)  ::   vcomp       ! symbolic component name if a vector that needs rotation
57      !                                     ! a string starting with "U" or "V" for each component   
58      !                                     ! chars 2 onwards identify which components go together 
59      CHARACTER(len = 34)  ::   lname       ! generic name of a NetCDF land/sea mask file to be used, blank if not
60      !                                     ! 0=sea 1=land
61   END TYPE FLD_N
62
63   TYPE, PUBLIC ::   FLD        !: Input field related variables
64      CHARACTER(len = 256)            ::   clrootname   ! generic name of the NetCDF file
65      CHARACTER(len = 256)            ::   clname       ! current name of the NetCDF file
66      REAL(wp)                        ::   nfreqh       ! frequency of each flux file
67      CHARACTER(len = 34)             ::   clvar        ! generic name of the variable in the NetCDF flux file
68      LOGICAL                         ::   ln_tint      ! time interpolation or not (T/F)
69      LOGICAL                         ::   ln_clim      ! climatology or not (T/F)
70      CHARACTER(len = 8)              ::   cltype       ! type of data file 'daily', 'monthly' or yearly'
71      INTEGER                         ::   num          ! iom id of the jpfld files to be read
72      INTEGER , DIMENSION(2)          ::   nrec_b       ! before record (1: index, 2: second since Jan. 1st 00h of nit000 year)
73      INTEGER , DIMENSION(2)          ::   nrec_a       ! after  record (1: index, 2: second since Jan. 1st 00h of nit000 year)
74      REAL(wp) , ALLOCATABLE, DIMENSION(:,:,:  ) ::   fnow   ! input fields interpolated to now time step
75      REAL(wp) , ALLOCATABLE, DIMENSION(:,:,:,:) ::   fdta   ! 2 consecutive record of input fields
76      CHARACTER(len = 256)            ::   wgtname      ! current name of the NetCDF weight file acting as a key
77      !                                                 ! into the WGTLIST structure
78      CHARACTER(len = 34)             ::   vcomp        ! symbolic name for a vector component that needs rotation
79      LOGICAL, DIMENSION(2)           ::   rotn         ! flag to indicate whether before/after field has been rotated
80      INTEGER                         ::   nreclast     ! last record to be read in the current file
81      CHARACTER(len = 256)            ::   lsmname      ! current name of the NetCDF mask file acting as a key
82   END TYPE FLD
83
84   TYPE, PUBLIC ::   MAP_POINTER      !: Map from input data file to local domain
85      INTEGER, POINTER, DIMENSION(:)  ::  ptr           ! Array of integer pointers to 1D arrays
86      LOGICAL                         ::  ll_unstruc    ! Unstructured (T) or structured (F) boundary data file
87   END TYPE MAP_POINTER
88
89!$AGRIF_DO_NOT_TREAT
90
91   !! keep list of all weights variables so they're only read in once
92   !! need to add AGRIF directives not to process this structure
93   !! also need to force wgtname to include AGRIF nest number
94   TYPE         ::   WGT        !: Input weights related variables
95      CHARACTER(len = 256)                    ::   wgtname      ! current name of the NetCDF weight file
96      INTEGER , DIMENSION(2)                  ::   ddims        ! shape of input grid
97      INTEGER , DIMENSION(2)                  ::   botleft      ! top left corner of box in input grid containing
98      !                                                         ! current processor grid
99      INTEGER , DIMENSION(2)                  ::   topright     ! top right corner of box
100      INTEGER                                 ::   jpiwgt       ! width of box on input grid
101      INTEGER                                 ::   jpjwgt       ! height of box on input grid
102      INTEGER                                 ::   numwgt       ! number of weights (4=bilinear, 16=bicubic)
103      INTEGER                                 ::   nestid       ! for agrif, keep track of nest we're in
104      INTEGER                                 ::   overlap      ! =0 when cyclic grid has no overlapping EW columns
105      !                                                         ! =>1 when they have one or more overlapping columns     
106      !                                                         ! =-1 not cyclic
107      LOGICAL                                 ::   cyclic       ! east-west cyclic or not
108      INTEGER,  DIMENSION(:,:,:), POINTER     ::   data_jpi     ! array of source integers
109      INTEGER,  DIMENSION(:,:,:), POINTER     ::   data_jpj     ! array of source integers
110      REAL(wp), DIMENSION(:,:,:), POINTER     ::   data_wgt     ! array of weights on model grid
111      REAL(wp), DIMENSION(:,:,:), POINTER     ::   fly_dta      ! array of values on input grid
112      REAL(wp), DIMENSION(:,:,:), POINTER     ::   col          ! temporary array for reading in columns
113   END TYPE WGT
114
115   INTEGER,     PARAMETER             ::   tot_wgts = 10
116   TYPE( WGT ), DIMENSION(tot_wgts)   ::   ref_wgts     ! array of wgts
117   INTEGER                            ::   nxt_wgt = 1  ! point to next available space in ref_wgts array
118   REAL(wp), PARAMETER                ::   undeff_lsm = -999.00_wp
119
120!$AGRIF_END_DO_NOT_TREAT
121
122   !!----------------------------------------------------------------------
123   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
124   !! $Id$
125   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
126   !!----------------------------------------------------------------------
127CONTAINS
128
129   SUBROUTINE fld_read( kt, kn_fsbc, sd, map, kit, kt_offset )
130      !!---------------------------------------------------------------------
131      !!                    ***  ROUTINE fld_read  ***
132      !!                   
133      !! ** Purpose :   provide at each time step the surface ocean fluxes
134      !!                (momentum, heat, freshwater and runoff)
135      !!
136      !! ** Method  :   READ each input fields in NetCDF files using IOM
137      !!      and intepolate it to the model time-step.
138      !!         Several assumptions are made on the input file:
139      !!      blahblahblah....
140      !!----------------------------------------------------------------------
141      INTEGER  , INTENT(in   )               ::   kt        ! ocean time step
142      INTEGER  , INTENT(in   )               ::   kn_fsbc   ! sbc computation period (in time step)
143      TYPE(FLD), INTENT(inout), DIMENSION(:) ::   sd        ! input field related variables
144      TYPE(MAP_POINTER),INTENT(in), OPTIONAL, DIMENSION(:) ::   map   ! global-to-local mapping indices
145      INTEGER  , INTENT(in   ), OPTIONAL     ::   kit       ! subcycle timestep for timesplitting option
146      INTEGER  , INTENT(in   ), OPTIONAL     ::   kt_offset ! provide fields at time other than "now"
147      !                                                     !   kt_offset = -1 => fields at "before" time level
148      !                                                     !   kt_offset = +1 => fields at "after"  time level
149      !                                                     !   etc.
150      INTEGER  ::   itmp         ! local variable
151      INTEGER  ::   imf          ! size of the structure sd
152      INTEGER  ::   jf           ! dummy indices
153      INTEGER  ::   isecend      ! number of second since Jan. 1st 00h of nit000 year at nitend
154      INTEGER  ::   isecsbc      ! number of seconds between Jan. 1st 00h of nit000 year and the middle of sbc time step
155      INTEGER  ::   it_offset    ! local time offset variable
156      LOGICAL  ::   llnxtyr      ! open next year  file?
157      LOGICAL  ::   llnxtmth     ! open next month file?
158      LOGICAL  ::   llstop       ! stop is the file does not exist
159      LOGICAL  ::   ll_firstcall ! true if this is the first call to fld_read for this set of fields
160      REAL(wp) ::   ztinta       ! ratio applied to after  records when doing time interpolation
161      REAL(wp) ::   ztintb       ! ratio applied to before records when doing time interpolation
162      CHARACTER(LEN=1000) ::   clfmt  ! write format
163      TYPE(MAP_POINTER)   ::   imap   ! global-to-local mapping indices
164      !!---------------------------------------------------------------------
165      ll_firstcall = kt == nit000
166      IF( PRESENT(kit) )   ll_firstcall = ll_firstcall .and. kit == 1
167
168      IF ( nn_components == jp_iam_sas ) THEN   ;   it_offset = nn_fsbc
169      ELSE                                      ;   it_offset = 0
170      ENDIF
171      IF( PRESENT(kt_offset) )   it_offset = kt_offset
172
173      imap%ptr => NULL()
174
175      ! Note that shifting time to be centrered in the middle of sbc time step impacts only nsec_* variables of the calendar
176      IF( present(kit) ) THEN   ! ignore kn_fsbc in this case
177         isecsbc = nsec_year + nsec1jan000 + (kit+it_offset)*NINT( rdt/REAL(nn_baro,wp) )
178      ELSE                      ! middle of sbc time step
179         isecsbc = nsec_year + nsec1jan000 + NINT(0.5 * REAL(kn_fsbc - 1,wp) * rdt) + it_offset * NINT(rdt)
180      ENDIF
181      imf = SIZE( sd )
182      !
183      IF( ll_firstcall ) THEN                      ! initialization
184         DO jf = 1, imf 
185            IF( PRESENT(map) ) imap = map(jf)
186            CALL fld_init( kn_fsbc, sd(jf), imap )  ! read each before field (put them in after as they will be swapped)
187         END DO
188         IF( lwp ) CALL wgt_print()                ! control print
189      ENDIF
190      !                                            ! ====================================== !
191      IF( MOD( kt-1, kn_fsbc ) == 0 ) THEN         ! update field at each kn_fsbc time-step !
192         !                                         ! ====================================== !
193         !
194         DO jf = 1, imf                            ! ---   loop over field   --- !
195           
196            IF( isecsbc > sd(jf)%nrec_a(2) .OR. ll_firstcall ) THEN    ! read/update the after data?
197
198               IF( PRESENT(map) )   imap = map(jf)   ! temporary definition of map
199
200               sd(jf)%nrec_b(:) = sd(jf)%nrec_a(:)                                  ! swap before record informations
201               sd(jf)%rotn(1) = sd(jf)%rotn(2)                                      ! swap before rotate informations
202               IF( sd(jf)%ln_tint )   sd(jf)%fdta(:,:,:,1) = sd(jf)%fdta(:,:,:,2)   ! swap before record field
203
204               CALL fld_rec( kn_fsbc, sd(jf), kt_offset = it_offset, kit = kit )    ! update after record informations
205
206               ! if kn_fsbc*rdt is larger than nfreqh (which is kind of odd),
207               ! it is possible that the before value is no more the good one... we have to re-read it
208               ! if before is not the last record of the file currently opened and after is the first record to be read
209               ! in a new file which means after = 1 (the file to be opened corresponds to the current time)
210               ! or after = nreclast + 1 (the file to be opened corresponds to a future time step)
211               IF( .NOT. ll_firstcall .AND. sd(jf)%ln_tint .AND. sd(jf)%nrec_b(1) /= sd(jf)%nreclast &
212                  &                   .AND. MOD( sd(jf)%nrec_a(1), sd(jf)%nreclast ) == 1 ) THEN
213                  itmp = sd(jf)%nrec_a(1)                       ! temporary storage
214                  sd(jf)%nrec_a(1) = sd(jf)%nreclast            ! read the last record of the file currently opened
215                  CALL fld_get( sd(jf), imap )                  ! read after data
216                  sd(jf)%fdta(:,:,:,1) = sd(jf)%fdta(:,:,:,2)   ! re-swap before record field
217                  sd(jf)%nrec_b(1) = sd(jf)%nrec_a(1)           ! update before record informations
218                  sd(jf)%nrec_b(2) = sd(jf)%nrec_a(2) - NINT( sd(jf)%nfreqh * 3600 )  ! assume freq to be in hours in this case
219                  sd(jf)%rotn(1)   = sd(jf)%rotn(2)             ! update before rotate informations
220                  sd(jf)%nrec_a(1) = itmp                       ! move back to after record
221               ENDIF
222
223               CALL fld_clopn( sd(jf) )   ! Do we need to open a new year/month/week/day file?
224               
225               IF( sd(jf)%ln_tint ) THEN
226                 
227                  ! if kn_fsbc*rdt is larger than nfreqh (which is kind of odd),
228                  ! it is possible that the before value is no more the good one... we have to re-read it
229                  ! if before record is not just just before the after record...
230                  IF( .NOT. ll_firstcall .AND. MOD( sd(jf)%nrec_a(1), sd(jf)%nreclast ) /= 1 &
231                     &                   .AND. sd(jf)%nrec_b(1) /= sd(jf)%nrec_a(1) - 1 ) THEN   
232                     sd(jf)%nrec_a(1) = sd(jf)%nrec_a(1) - 1       ! move back to before record
233                     CALL fld_get( sd(jf), imap )                  ! read after data
234                     sd(jf)%fdta(:,:,:,1) = sd(jf)%fdta(:,:,:,2)   ! re-swap before record field
235                     sd(jf)%nrec_b(1) = sd(jf)%nrec_a(1)           ! update before record informations
236                     sd(jf)%nrec_b(2) = sd(jf)%nrec_a(2) - NINT( sd(jf)%nfreqh * 3600 )  ! assume freq to be in hours in this case
237                     sd(jf)%rotn(1)   = sd(jf)%rotn(2)             ! update before rotate informations
238                     sd(jf)%nrec_a(1) = sd(jf)%nrec_a(1) + 1       ! move back to after record
239                  ENDIF
240
241                  ! do we have to change the year/month/week/day of the forcing field??
242                  ! if we do time interpolation we will need to open next year/month/week/day file before the end of the current
243                  ! one. If so, we are still before the end of the year/month/week/day when calling fld_rec so sd(jf)%nrec_a(1)
244                  ! will be larger than the record number that should be read for current year/month/week/day
245                  ! do we need next file data?
246                  IF( sd(jf)%nrec_a(1) > sd(jf)%nreclast ) THEN
247                     
248                     sd(jf)%nrec_a(1) = sd(jf)%nrec_a(1) - sd(jf)%nreclast   !
249                     
250                     IF( .NOT. ( sd(jf)%ln_clim .AND. sd(jf)%cltype == 'yearly' ) ) THEN   ! close/open the current/new file
251                       
252                        llnxtmth = sd(jf)%cltype == 'monthly' .OR. nday == nmonth_len(nmonth)      ! open next month file?
253                        llnxtyr  = sd(jf)%cltype == 'yearly'  .OR. (nmonth == 12 .AND. llnxtmth)   ! open next year  file?
254
255                        ! if the run finishes at the end of the current year/month/week/day, we will allow next
256                        ! year/month/week/day file to be not present. If the run continue further than the current
257                        ! year/month/week/day, next year/month/week/day file must exist
258                        isecend = nsec_year + nsec1jan000 + (nitend - kt) * NINT(rdt)   ! second at the end of the run
259                        llstop = isecend > sd(jf)%nrec_a(2)                                   ! read more than 1 record of next year
260                        ! we suppose that the date of next file is next day (should be ok even for weekly files...)
261                        CALL fld_clopn( sd(jf), nyear  + COUNT((/llnxtyr /))                                           ,         &
262                           &                    nmonth + COUNT((/llnxtmth/)) - 12                 * COUNT((/llnxtyr /)),         &
263                           &                    nday   + 1                   - nmonth_len(nmonth) * COUNT((/llnxtmth/)), llstop )
264
265                        IF( sd(jf)%num <= 0 .AND. .NOT. llstop ) THEN    ! next year file does not exist
266                           CALL ctl_warn('next year/month/week/day file: '//TRIM(sd(jf)%clname)//     &
267                              &     ' not present -> back to current year/month/day')
268                           CALL fld_clopn( sd(jf) )       ! back to the current year/month/day
269                           sd(jf)%nrec_a(1) = sd(jf)%nreclast     ! force to read the last record in the current year file
270                        ENDIF
271                       
272                     ENDIF
273                  ENDIF   ! open need next file?
274                 
275               ENDIF   ! temporal interpolation?
276
277               ! read after data
278               CALL fld_get( sd(jf), imap )
279
280            ENDIF   ! read new data?
281         END DO                                    ! --- end loop over field --- !
282
283         CALL fld_rot( kt, sd )                    ! rotate vector before/now/after fields if needed
284
285         DO jf = 1, imf                            ! ---   loop over field   --- !
286            !
287            IF( sd(jf)%ln_tint ) THEN              ! temporal interpolation
288               IF(lwp .AND. kt - nit000 <= 100 ) THEN
289                  clfmt = "('   fld_read: var ', a, ' kt = ', i8, ' (', f9.4,' days), Y/M/D = ', i4.4,'/', i2.2,'/', i2.2," //   &
290                     &    "', records b/a: ', i6.4, '/', i6.4, ' (days ', f9.4,'/', f9.4, ')')"
291                  WRITE(numout, clfmt)  TRIM( sd(jf)%clvar ), kt, REAL(isecsbc,wp)/rday, nyear, nmonth, nday,   &           
292                     & sd(jf)%nrec_b(1), sd(jf)%nrec_a(1), REAL(sd(jf)%nrec_b(2),wp)/rday, REAL(sd(jf)%nrec_a(2),wp)/rday
293                  WRITE(numout, *) '      it_offset is : ',it_offset
294               ENDIF
295               ! temporal interpolation weights
296               ztinta =  REAL( isecsbc - sd(jf)%nrec_b(2), wp ) / REAL( sd(jf)%nrec_a(2) - sd(jf)%nrec_b(2), wp )
297               ztintb =  1. - ztinta
298               sd(jf)%fnow(:,:,:) = ztintb * sd(jf)%fdta(:,:,:,1) + ztinta * sd(jf)%fdta(:,:,:,2)
299            ELSE   ! nothing to do...
300               IF(lwp .AND. kt - nit000 <= 100 ) THEN
301                  clfmt = "('   fld_read: var ', a, ' kt = ', i8,' (', f9.4,' days), Y/M/D = ', i4.4,'/', i2.2,'/', i2.2," //   &
302                     &    "', record: ', i6.4, ' (days ', f9.4, ' <-> ', f9.4, ')')"
303                  WRITE(numout, clfmt) TRIM(sd(jf)%clvar), kt, REAL(isecsbc,wp)/rday, nyear, nmonth, nday,    &
304                     &                 sd(jf)%nrec_a(1), REAL(sd(jf)%nrec_b(2),wp)/rday, REAL(sd(jf)%nrec_a(2),wp)/rday
305               ENDIF
306            ENDIF
307            !
308            IF( kt == nitend - kn_fsbc + 1 )   CALL iom_close( sd(jf)%num )   ! Close the input files
309
310         END DO                                    ! --- end loop over field --- !
311         !
312      ENDIF
313      !
314   END SUBROUTINE fld_read
315
316
317   SUBROUTINE fld_init( kn_fsbc, sdjf, map )
318      !!---------------------------------------------------------------------
319      !!                    ***  ROUTINE fld_init  ***
320      !!
321      !! ** Purpose :  - first call to fld_rec to define before values
322      !!               - if time interpolation, read before data
323      !!----------------------------------------------------------------------
324      INTEGER  , INTENT(in   ) ::   kn_fsbc   ! sbc computation period (in time step)
325      TYPE(FLD), INTENT(inout) ::   sdjf      ! input field related variables
326      TYPE(MAP_POINTER),INTENT(in) ::   map   ! global-to-local mapping indices
327      !!
328      LOGICAL :: llprevyr              ! are we reading previous year  file?
329      LOGICAL :: llprevmth             ! are we reading previous month file?
330      LOGICAL :: llprevweek            ! are we reading previous week  file?
331      LOGICAL :: llprevday             ! are we reading previous day   file?
332      LOGICAL :: llprev                ! llprevyr .OR. llprevmth .OR. llprevweek .OR. llprevday
333      INTEGER :: idvar                 ! variable id
334      INTEGER :: inrec                 ! number of record existing for this variable
335      INTEGER :: iyear, imonth, iday   ! first day of the current file in yyyy mm dd
336      INTEGER :: isec_week             ! number of seconds since start of the weekly file
337      CHARACTER(LEN=1000) ::   clfmt   ! write format
338      !!---------------------------------------------------------------------
339      llprevyr   = .FALSE.
340      llprevmth  = .FALSE.
341      llprevweek = .FALSE.
342      llprevday  = .FALSE.
343      isec_week  = 0
344      !
345      ! define record informations
346      CALL fld_rec( kn_fsbc, sdjf, ldbefore = .TRUE. )  ! return before values in sdjf%nrec_a (as we will swap it later)
347      !
348      ! Note that shifting time to be centrered in the middle of sbc time step impacts only nsec_* variables of the calendar
349      !
350      IF( sdjf%ln_tint ) THEN ! we need to read the previous record and we will put it in the current record structure
351         !
352         IF( sdjf%nrec_a(1) == 0  ) THEN   ! we redefine record sdjf%nrec_a(1) with the last record of previous year file
353            IF    ( sdjf%nfreqh == -12 ) THEN   ! yearly mean
354               IF( sdjf%cltype == 'yearly' ) THEN             ! yearly file
355                  sdjf%nrec_a(1) = 1                                                       ! force to read the unique record
356                  llprevyr  = .NOT. sdjf%ln_clim                                           ! use previous year  file?
357               ELSE
358                  CALL ctl_stop( "fld_init: yearly mean file must be in a yearly type of file: "//TRIM(sdjf%clrootname) )
359               ENDIF
360            ELSEIF( sdjf%nfreqh ==  -1 ) THEN   ! monthly mean
361               IF( sdjf%cltype == 'monthly' ) THEN            ! monthly file
362                  sdjf%nrec_a(1) = 1                                                       ! force to read the unique record
363                  llprevmth = .TRUE.                                                       ! use previous month file?
364                  llprevyr  = llprevmth .AND. nmonth == 1                                  ! use previous year  file?
365               ELSE                                           ! yearly file
366                  sdjf%nrec_a(1) = 12                                                      ! force to read december mean
367                  llprevyr = .NOT. sdjf%ln_clim                                            ! use previous year  file?
368               ENDIF
369            ELSE                                ! higher frequency mean (in hours)
370               IF    ( sdjf%cltype      == 'monthly' ) THEN   ! monthly file
371                  sdjf%nrec_a(1) = NINT( 24 * nmonth_len(nmonth-1) / sdjf%nfreqh )         ! last record of previous month
372                  llprevmth = .TRUE.                                                       ! use previous month file?
373                  llprevyr  = llprevmth .AND. nmonth == 1                                  ! use previous year  file?
374               ELSEIF( sdjf%cltype(1:4) == 'week'    ) THEN   ! weekly file
375                  llprevweek = .TRUE.                                                      ! use previous week  file?
376                  sdjf%nrec_a(1) = NINT( 24 * 7 / sdjf%nfreqh )                            ! last record of previous week
377                  isec_week = NINT(rday) * 7                                               ! add a shift toward previous week
378               ELSEIF( sdjf%cltype      == 'daily'   ) THEN   ! daily file
379                  sdjf%nrec_a(1) = NINT( 24 / sdjf%nfreqh )                                ! last record of previous day
380                  llprevday = .TRUE.                                                       ! use previous day   file?
381                  llprevmth = llprevday .AND. nday   == 1                                  ! use previous month file?
382                  llprevyr  = llprevmth .AND. nmonth == 1                                  ! use previous year  file?
383               ELSE                                           ! yearly file
384                  sdjf%nrec_a(1) = NINT( 24 * nyear_len(0) / sdjf%nfreqh )                 ! last record of previous year
385                  llprevyr = .NOT. sdjf%ln_clim                                            ! use previous year  file?
386               ENDIF
387            ENDIF
388         ENDIF
389         !
390         IF ( sdjf%cltype(1:4) == 'week' ) THEN
391            isec_week = isec_week + ksec_week( sdjf%cltype(6:8) )   ! second since the beginning of the week
392            llprevmth = isec_week > nsec_month                      ! longer time since the beginning of the week than the month
393            llprevyr  = llprevmth .AND. nmonth == 1
394         ENDIF
395         llprev = llprevyr .OR. llprevmth .OR. llprevweek .OR. llprevday
396         !
397         iyear  = nyear  - COUNT((/llprevyr /))
398         imonth = nmonth - COUNT((/llprevmth/)) + 12 * COUNT((/llprevyr /))
399         iday   = nday   - COUNT((/llprevday/)) + nmonth_len(nmonth-1) * COUNT((/llprevmth/)) - isec_week / NINT(rday)
400         !
401         CALL fld_clopn( sdjf, iyear, imonth, iday, .NOT. llprev )
402         !
403         ! if previous year/month/day file does not exist, we switch to the current year/month/day
404         IF( llprev .AND. sdjf%num <= 0 ) THEN
405            CALL ctl_warn( 'previous year/month/week/day file: '//TRIM(sdjf%clrootname)//   &
406               &           ' not present -> back to current year/month/week/day' )
407            ! we force to read the first record of the current year/month/day instead of last record of previous year/month/day
408            llprev = .FALSE.
409            sdjf%nrec_a(1) = 1
410            CALL fld_clopn( sdjf )
411         ENDIF
412         !
413         IF( llprev ) THEN   ! check if the record sdjf%nrec_a(1) exists in the file
414            idvar = iom_varid( sdjf%num, sdjf%clvar )                                        ! id of the variable sdjf%clvar
415            IF( idvar <= 0 )   RETURN
416            inrec = iom_file( sdjf%num )%dimsz( iom_file( sdjf%num )%ndims(idvar), idvar )   ! size of the last dim of idvar
417            sdjf%nrec_a(1) = MIN( sdjf%nrec_a(1), inrec )   ! make sure we select an existing record
418         ENDIF
419         !
420         CALL fld_get( sdjf, map )         ! read before data in after arrays(as we will swap it later)
421         !
422         clfmt = "('   fld_init : time-interpolation for ', a, ' read previous record = ', i6, ' at time = ', f7.2, ' days')"
423         IF(lwp) WRITE(numout, clfmt) TRIM(sdjf%clvar), sdjf%nrec_a(1), REAL(sdjf%nrec_a(2),wp)/rday
424         !
425      ENDIF
426      !
427   END SUBROUTINE fld_init
428
429
430   SUBROUTINE fld_rec( kn_fsbc, sdjf, ldbefore, kit, kt_offset )
431      !!---------------------------------------------------------------------
432      !!                    ***  ROUTINE fld_rec  ***
433      !!
434      !! ** Purpose : Compute
435      !!              if sdjf%ln_tint = .TRUE.
436      !!                  nrec_a: record number and its time (nrec_b is obtained from nrec_a when swapping)
437      !!              if sdjf%ln_tint = .FALSE.
438      !!                  nrec_a(1): record number
439      !!                  nrec_b(2) and nrec_a(2): time of the beginning and end of the record (for print only)
440      !!----------------------------------------------------------------------
441      INTEGER  , INTENT(in   )           ::   kn_fsbc   ! sbc computation period (in time step)
442      TYPE(FLD), INTENT(inout)           ::   sdjf      ! input field related variables
443      LOGICAL  , INTENT(in   ), OPTIONAL ::   ldbefore  ! sent back before record values (default = .FALSE.)
444      INTEGER  , INTENT(in   ), OPTIONAL ::   kit       ! index of barotropic subcycle
445      !                                                 ! used only if sdjf%ln_tint = .TRUE.
446      INTEGER  , INTENT(in   ), OPTIONAL ::   kt_offset ! Offset of required time level compared to "now"
447      !                                                 !   time level in units of time steps.
448      !
449      LOGICAL  ::   llbefore    ! local definition of ldbefore
450      INTEGER  ::   iendrec     ! end of this record (in seconds)
451      INTEGER  ::   imth        ! month number
452      INTEGER  ::   ifreq_sec   ! frequency mean (in seconds)
453      INTEGER  ::   isec_week   ! number of seconds since the start of the weekly file
454      INTEGER  ::   it_offset   ! local time offset variable
455      REAL(wp) ::   ztmp        ! temporary variable
456      !!----------------------------------------------------------------------
457      !
458      ! Note that shifting time to be centrered in the middle of sbc time step impacts only nsec_* variables of the calendar
459      !
460      IF( PRESENT(ldbefore) ) THEN   ;   llbefore = ldbefore .AND. sdjf%ln_tint   ! needed only if sdjf%ln_tint = .TRUE.
461      ELSE                           ;   llbefore = .FALSE.
462      ENDIF
463      !
464      IF ( nn_components == jp_iam_sas ) THEN   ;   it_offset = nn_fsbc
465      ELSE                                      ;   it_offset = 0
466      ENDIF
467      IF( PRESENT(kt_offset) )   it_offset = kt_offset
468      IF( PRESENT(kit) ) THEN   ;   it_offset = ( kit + it_offset ) * NINT( rdt/REAL(nn_baro,wp) )
469      ELSE                      ;   it_offset =         it_offset   * NINT(       rdt            )
470      ENDIF
471      !
472      !                                      ! =========== !
473      IF    ( sdjf%nfreqh == -12 ) THEN      ! yearly mean
474         !                                   ! =========== !
475         !
476         IF( sdjf%ln_tint ) THEN                 ! time interpolation, shift by 1/2 record
477            !
478            !                  INT( ztmp )
479            !                     /|\
480            !                    1 |    *----
481            !                    0 |----(             
482            !                      |----+----|--> time
483            !                      0   /|\   1   (nday/nyear_len(1))
484            !                           |   
485            !                           |   
486            !       forcing record :    1
487            !                           
488            ztmp = REAL( nsec_year, wp ) / ( REAL( nyear_len(1), wp ) * rday ) + 0.5 &
489           &       + REAL( it_offset, wp ) / ( REAL( nyear_len(1), wp ) * rday )
490            sdjf%nrec_a(1) = 1 + INT( ztmp ) - COUNT((/llbefore/))
491            ! swap at the middle of the year
492            IF( llbefore ) THEN   ;   sdjf%nrec_a(2) = nsec1jan000 - (1 - INT(ztmp)) * NINT(0.5 * rday) * nyear_len(0) + &
493                                    & INT(ztmp) * NINT( 0.5 * rday) * nyear_len(1) 
494            ELSE                  ;   sdjf%nrec_a(2) = nsec1jan000 + (1 - INT(ztmp)) * NINT(0.5 * rday) * nyear_len(1) + &
495                                    & INT(ztmp) * INT(rday) * nyear_len(1) + INT(ztmp) * NINT( 0.5 * rday) * nyear_len(2) 
496            ENDIF
497         ELSE                                    ! no time interpolation
498            sdjf%nrec_a(1) = 1
499            sdjf%nrec_a(2) = NINT(rday) * nyear_len(1) + nsec1jan000   ! swap at the end    of the year
500            sdjf%nrec_b(2) = nsec1jan000                               ! beginning of the year (only for print)
501         ENDIF
502         !
503         !                                   ! ============ !
504      ELSEIF( sdjf%nfreqh ==  -1 ) THEN      ! monthly mean !
505         !                                   ! ============ !
506         !
507         IF( sdjf%ln_tint ) THEN                 ! time interpolation, shift by 1/2 record
508            !
509            !                  INT( ztmp )
510            !                     /|\
511            !                    1 |    *----
512            !                    0 |----(             
513            !                      |----+----|--> time
514            !                      0   /|\   1   (nday/nmonth_len(nmonth))
515            !                           |   
516            !                           |   
517            !       forcing record :  nmonth
518            !                           
519            ztmp = REAL( nsec_month, wp ) / ( REAL( nmonth_len(nmonth), wp ) * rday ) + 0.5 &
520           &       + REAL( it_offset, wp ) / ( REAL( nmonth_len(nmonth), wp ) * rday )
521            imth = nmonth + INT( ztmp ) - COUNT((/llbefore/))
522            IF( sdjf%cltype == 'monthly' ) THEN   ;   sdjf%nrec_a(1) = 1 + INT( ztmp ) - COUNT((/llbefore/))
523            ELSE                                  ;   sdjf%nrec_a(1) = imth
524            ENDIF
525            sdjf%nrec_a(2) = nmonth_half(   imth ) + nsec1jan000   ! swap at the middle of the month
526         ELSE                                    ! no time interpolation
527            IF( sdjf%cltype == 'monthly' ) THEN   ;   sdjf%nrec_a(1) = 1
528            ELSE                                  ;   sdjf%nrec_a(1) = nmonth
529            ENDIF
530            sdjf%nrec_a(2) =  nmonth_end(nmonth  ) + nsec1jan000   ! swap at the end    of the month
531            sdjf%nrec_b(2) =  nmonth_end(nmonth-1) + nsec1jan000   ! beginning of the month (only for print)
532         ENDIF
533         !
534         !                                   ! ================================ !
535      ELSE                                   ! higher frequency mean (in hours)
536         !                                   ! ================================ !
537         !
538         ifreq_sec = NINT( sdjf%nfreqh * 3600 )                                         ! frequency mean (in seconds)
539         IF( sdjf%cltype(1:4) == 'week' )   isec_week = ksec_week( sdjf%cltype(6:8) )   ! since the first day of the current week
540         ! number of second since the beginning of the file
541         IF(     sdjf%cltype      == 'monthly' ) THEN   ;   ztmp = REAL(nsec_month,wp)  ! since the first day of the current month
542         ELSEIF( sdjf%cltype(1:4) == 'week'    ) THEN   ;   ztmp = REAL(isec_week ,wp)  ! since the first day of the current week
543         ELSEIF( sdjf%cltype      == 'daily'   ) THEN   ;   ztmp = REAL(nsec_day  ,wp)  ! since 00h of the current day
544         ELSE                                           ;   ztmp = REAL(nsec_year ,wp)  ! since 00h on Jan 1 of the current year
545         ENDIF
546         ztmp = ztmp + 0.5 * REAL(kn_fsbc - 1, wp) * rdt + REAL( it_offset, wp )        ! centrered in the middle of sbc time step
547         ztmp = ztmp + 0.01 * rdt                                                       ! avoid truncation error
548         IF( sdjf%ln_tint ) THEN                ! time interpolation, shift by 1/2 record
549            !
550            !          INT( ztmp/ifreq_sec + 0.5 )
551            !                     /|\
552            !                    2 |        *-----(
553            !                    1 |  *-----(
554            !                    0 |--(             
555            !                      |--+--|--+--|--+--|--> time
556            !                      0 /|\ 1 /|\ 2 /|\ 3    (ztmp/ifreq_sec)
557            !                         |     |     |
558            !                         |     |     |
559            !       forcing record :  1     2     3
560            !                   
561            ztmp= ztmp / REAL(ifreq_sec, wp) + 0.5
562         ELSE                                   ! no time interpolation
563            !
564            !           INT( ztmp/ifreq_sec )
565            !                     /|\
566            !                    2 |           *-----(
567            !                    1 |     *-----(
568            !                    0 |-----(             
569            !                      |--+--|--+--|--+--|--> time
570            !                      0 /|\ 1 /|\ 2 /|\ 3    (ztmp/ifreq_sec)
571            !                         |     |     |
572            !                         |     |     |
573            !       forcing record :  1     2     3
574            !                           
575            ztmp= ztmp / REAL(ifreq_sec, wp)
576         ENDIF
577         sdjf%nrec_a(1) = 1 + INT( ztmp ) - COUNT((/llbefore/))   ! record number to be read
578
579         iendrec = ifreq_sec * sdjf%nrec_a(1) + nsec1jan000       ! end of this record (in second)
580         ! add the number of seconds between 00h Jan 1 and the end of previous month/week/day (ok if nmonth=1)
581         IF( sdjf%cltype      == 'monthly' )   iendrec = iendrec + NINT(rday) * SUM(nmonth_len(1:nmonth -1))
582         IF( sdjf%cltype(1:4) == 'week'    )   iendrec = iendrec + ( nsec_year - isec_week )
583         IF( sdjf%cltype      == 'daily'   )   iendrec = iendrec + NINT(rday) * ( nday_year - 1 )
584         IF( sdjf%ln_tint ) THEN
585             sdjf%nrec_a(2) = iendrec - ifreq_sec / 2        ! swap at the middle of the record
586         ELSE
587             sdjf%nrec_a(2) = iendrec                        ! swap at the end    of the record
588             sdjf%nrec_b(2) = iendrec - ifreq_sec            ! beginning of the record (only for print)
589         ENDIF
590         !
591      ENDIF
592      !
593   END SUBROUTINE fld_rec
594
595
596   SUBROUTINE fld_get( sdjf, map )
597      !!---------------------------------------------------------------------
598      !!                    ***  ROUTINE fld_get  ***
599      !!
600      !! ** Purpose :   read the data
601      !!----------------------------------------------------------------------
602      TYPE(FLD)        , INTENT(inout) ::   sdjf   ! input field related variables
603      TYPE(MAP_POINTER), INTENT(in   ) ::   map    ! global-to-local mapping indices
604      !
605      INTEGER ::   ipk      ! number of vertical levels of sdjf%fdta ( 2D: ipk=1 ; 3D: ipk=jpk )
606      INTEGER ::   iw       ! index into wgts array
607      INTEGER ::   ipdom    ! index of the domain
608      INTEGER ::   idvar    ! variable ID
609      INTEGER ::   idmspc   ! number of spatial dimensions
610      LOGICAL ::   lmoor    ! C1D case: point data
611      !!---------------------------------------------------------------------
612      !
613      ipk = SIZE( sdjf%fnow, 3 )
614      !
615      IF( ASSOCIATED(map%ptr) ) THEN
616         IF( sdjf%ln_tint ) THEN   ;   CALL fld_map( sdjf%num, sdjf%clvar, sdjf%fdta(:,:,:,2), sdjf%nrec_a(1), map )
617         ELSE                      ;   CALL fld_map( sdjf%num, sdjf%clvar, sdjf%fnow(:,:,:  ), sdjf%nrec_a(1), map )
618         ENDIF
619      ELSE IF( LEN(TRIM(sdjf%wgtname)) > 0 ) THEN
620         CALL wgt_list( sdjf, iw )
621         IF( sdjf%ln_tint ) THEN   ;   CALL fld_interp( sdjf%num, sdjf%clvar, iw, ipk, sdjf%fdta(:,:,:,2),          & 
622            &                                                                          sdjf%nrec_a(1), sdjf%lsmname )
623         ELSE                      ;   CALL fld_interp( sdjf%num, sdjf%clvar, iw, ipk, sdjf%fnow(:,:,:  ),          &
624            &                                                                          sdjf%nrec_a(1), sdjf%lsmname )
625         ENDIF
626      ELSE
627         IF( SIZE(sdjf%fnow, 1) == jpi ) THEN   ;   ipdom = jpdom_data
628         ELSE                                   ;   ipdom = jpdom_unknown
629         ENDIF
630         ! C1D case: If product of spatial dimensions == ipk, then x,y are of
631         ! size 1 (point/mooring data): this must be read onto the central grid point
632         idvar  = iom_varid( sdjf%num, sdjf%clvar )
633         idmspc = iom_file ( sdjf%num )%ndims( idvar )
634         IF( iom_file( sdjf%num )%luld( idvar ) )   idmspc = idmspc - 1
635         lmoor  = (  idmspc == 0 .OR. PRODUCT( iom_file( sdjf%num )%dimsz( 1:MAX(idmspc,1) ,idvar ) ) == ipk  )
636         !
637         SELECT CASE( ipk )
638         CASE(1)
639            IF( lk_c1d .AND. lmoor ) THEN
640               IF( sdjf%ln_tint ) THEN
641                  CALL iom_get( sdjf%num, sdjf%clvar, sdjf%fdta(2,2,1,2), sdjf%nrec_a(1) )
642                  CALL lbc_lnk( sdjf%fdta(:,:,1,2),'Z',1. )
643               ELSE
644                  CALL iom_get( sdjf%num, sdjf%clvar, sdjf%fnow(2,2,1  ), sdjf%nrec_a(1) )
645                  CALL lbc_lnk( sdjf%fnow(:,:,1  ),'Z',1. )
646               ENDIF
647            ELSE
648               IF( sdjf%ln_tint ) THEN   ;   CALL iom_get( sdjf%num, ipdom, sdjf%clvar, sdjf%fdta(:,:,1,2), sdjf%nrec_a(1) )
649               ELSE                      ;   CALL iom_get( sdjf%num, ipdom, sdjf%clvar, sdjf%fnow(:,:,1  ), sdjf%nrec_a(1) )
650               ENDIF
651            ENDIF
652         CASE DEFAULT
653            IF (lk_c1d .AND. lmoor ) THEN
654               IF( sdjf%ln_tint ) THEN
655                  CALL iom_get( sdjf%num, jpdom_unknown, sdjf%clvar, sdjf%fdta(2,2,:,2), sdjf%nrec_a(1) )
656                  CALL lbc_lnk( sdjf%fdta(:,:,:,2),'Z',1. )
657               ELSE
658                  CALL iom_get( sdjf%num, jpdom_unknown, sdjf%clvar, sdjf%fnow(2,2,:  ), sdjf%nrec_a(1) )
659                  CALL lbc_lnk( sdjf%fnow(:,:,:  ),'Z',1. )
660               ENDIF
661            ELSE
662               IF( sdjf%ln_tint ) THEN   ;   CALL iom_get( sdjf%num, ipdom, sdjf%clvar, sdjf%fdta(:,:,:,2), sdjf%nrec_a(1) )
663               ELSE                      ;   CALL iom_get( sdjf%num, ipdom, sdjf%clvar, sdjf%fnow(:,:,:  ), sdjf%nrec_a(1) )
664               ENDIF
665            ENDIF
666         END SELECT
667      ENDIF
668      !
669      sdjf%rotn(2) = .false.   ! vector not yet rotated
670      !
671   END SUBROUTINE fld_get
672
673
674   SUBROUTINE fld_map( num, clvar, dta, nrec, map )
675      !!---------------------------------------------------------------------
676      !!                    ***  ROUTINE fld_map  ***
677      !!
678      !! ** Purpose :   read global data from file and map onto local data
679      !!                using a general mapping (for open boundaries)
680      !!----------------------------------------------------------------------
681#if defined key_bdy
682      USE bdy_oce, ONLY:  dta_global, dta_global2         ! workspace to read in global data arrays
683#endif
684      INTEGER                   , INTENT(in ) ::   num     ! stream number
685      CHARACTER(LEN=*)          , INTENT(in ) ::   clvar   ! variable name
686      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   dta   ! output field on model grid (2 dimensional)
687      INTEGER                   , INTENT(in ) ::   nrec    ! record number to read (ie time slice)
688      TYPE(MAP_POINTER)         , INTENT(in ) ::   map     ! global-to-local mapping indices
689      !!
690      INTEGER                                 ::   ipi      ! length of boundary data on local process
691      INTEGER                                 ::   ipj      ! length of dummy dimension ( = 1 )
692      INTEGER                                 ::   ipk      ! number of vertical levels of dta ( 2D: ipk=1 ; 3D: ipk=jpk )
693      INTEGER                                 ::   ilendta  ! length of data in file
694      INTEGER                                 ::   idvar    ! variable ID
695      INTEGER                                 ::   ib, ik, ji, jj   ! loop counters
696      INTEGER                                 ::   ierr
697      REAL(wp), POINTER, DIMENSION(:,:,:)     ::   dta_read  ! work space for global data
698      !!---------------------------------------------------------------------
699      !
700      ipi = SIZE( dta, 1 )
701      ipj = 1
702      ipk = SIZE( dta, 3 )
703      !
704      idvar   = iom_varid( num, clvar )
705      ilendta = iom_file(num)%dimsz(1,idvar)
706
707#if defined key_bdy
708      ipj = iom_file(num)%dimsz(2,idvar)
709      IF( map%ll_unstruc) THEN   ! unstructured open boundary data file
710         dta_read => dta_global
711      ELSE                       ! structured open boundary data file
712         dta_read => dta_global2
713      ENDIF
714#endif
715
716      IF(lwp) WRITE(numout,*) 'Dim size for ',        TRIM(clvar),' is ', ilendta
717      IF(lwp) WRITE(numout,*) 'Number of levels for ',TRIM(clvar),' is ', ipk
718      !
719      SELECT CASE( ipk )
720      CASE(1)        ;   CALL iom_get ( num, jpdom_unknown, clvar, dta_read(1:ilendta,1:ipj,1    ), nrec )
721      CASE DEFAULT   ;   CALL iom_get ( num, jpdom_unknown, clvar, dta_read(1:ilendta,1:ipj,1:ipk), nrec )
722      END SELECT
723      !
724      IF( map%ll_unstruc ) THEN  ! unstructured open boundary data file
725         DO ib = 1, ipi
726            DO ik = 1, ipk
727               dta(ib,1,ik) =  dta_read(map%ptr(ib),1,ik)
728            END DO
729         END DO
730      ELSE                       ! structured open boundary data file
731         DO ib = 1, ipi
732            jj=1+floor(REAL(map%ptr(ib)-1)/REAL(ilendta))
733            ji=map%ptr(ib)-(jj-1)*ilendta
734            DO ik = 1, ipk
735               dta(ib,1,ik) =  dta_read(ji,jj,ik)
736            END DO
737         END DO
738      ENDIF
739      !
740   END SUBROUTINE fld_map
741
742
743   SUBROUTINE fld_rot( kt, sd )
744      !!---------------------------------------------------------------------
745      !!                    ***  ROUTINE fld_rot  ***
746      !!
747      !! ** Purpose :   Vector fields may need to be rotated onto the local grid direction
748      !!----------------------------------------------------------------------
749      INTEGER                , INTENT(in   ) ::   kt   ! ocean time step
750      TYPE(FLD), DIMENSION(:), INTENT(inout) ::   sd   ! input field related variables
751      !
752      INTEGER ::   ju, jv, jk, jn  ! loop indices
753      INTEGER ::   imf             ! size of the structure sd
754      INTEGER ::   ill             ! character length
755      INTEGER ::   iv              ! indice of V component
756      CHARACTER (LEN=100)               ::   clcomp       ! dummy weight name
757      REAL(wp), POINTER, DIMENSION(:,:) ::   utmp, vtmp   ! temporary arrays for vector rotation
758      !!---------------------------------------------------------------------
759      !
760      CALL wrk_alloc( jpi,jpj,   utmp, vtmp )
761      !
762      !! (sga: following code should be modified so that pairs arent searched for each time
763      !
764      imf = SIZE( sd )
765      DO ju = 1, imf
766         ill = LEN_TRIM( sd(ju)%vcomp )
767         DO jn = 2-COUNT((/sd(ju)%ln_tint/)), 2
768            IF( ill > 0 .AND. .NOT. sd(ju)%rotn(jn) ) THEN   ! find vector rotations required             
769               IF( sd(ju)%vcomp(1:1) == 'U' ) THEN      ! east-west component has symbolic name starting with 'U'
770                  ! look for the north-south component which has same symbolic name but with 'U' replaced with 'V'
771                  clcomp = 'V' // sd(ju)%vcomp(2:ill)   ! works even if ill == 1
772                  iv = -1
773                  DO jv = 1, imf
774                     IF( TRIM(sd(jv)%vcomp) == TRIM(clcomp) )   iv = jv
775                  END DO
776                  IF( iv > 0 ) THEN   ! fields ju and iv are two components which need to be rotated together
777                     DO jk = 1, SIZE( sd(ju)%fnow, 3 )
778                        IF( sd(ju)%ln_tint )THEN
779                           CALL rot_rep( sd(ju)%fdta(:,:,jk,jn), sd(iv)%fdta(:,:,jk,jn), 'T', 'en->i', utmp(:,:) )
780                           CALL rot_rep( sd(ju)%fdta(:,:,jk,jn), sd(iv)%fdta(:,:,jk,jn), 'T', 'en->j', vtmp(:,:) )
781                           sd(ju)%fdta(:,:,jk,jn) = utmp(:,:)   ;   sd(iv)%fdta(:,:,jk,jn) = vtmp(:,:)
782                        ELSE
783                           CALL rot_rep( sd(ju)%fnow(:,:,jk  ), sd(iv)%fnow(:,:,jk  ), 'T', 'en->i', utmp(:,:) )
784                           CALL rot_rep( sd(ju)%fnow(:,:,jk  ), sd(iv)%fnow(:,:,jk  ), 'T', 'en->j', vtmp(:,:) )
785                           sd(ju)%fnow(:,:,jk   ) = utmp(:,:)   ;   sd(iv)%fnow(:,:,jk   ) = vtmp(:,:)
786                        ENDIF
787                     END DO
788                     sd(ju)%rotn(jn) = .TRUE.               ! vector was rotated
789                     IF( lwp .AND. kt == nit000 )   WRITE(numout,*)   &
790                        &   'fld_read: vector pair ('//TRIM(sd(ju)%clvar)//', '//TRIM(sd(iv)%clvar)//') rotated on to model grid'
791                  ENDIF
792               ENDIF
793            ENDIF
794         END DO
795       END DO
796      !
797      CALL wrk_dealloc( jpi,jpj,   utmp, vtmp )
798      !
799   END SUBROUTINE fld_rot
800
801
802   SUBROUTINE fld_clopn( sdjf, kyear, kmonth, kday, ldstop )
803      !!---------------------------------------------------------------------
804      !!                    ***  ROUTINE fld_clopn  ***
805      !!
806      !! ** Purpose :   update the file name and close/open the files
807      !!----------------------------------------------------------------------
808      TYPE(FLD)        , INTENT(inout) ::   sdjf     ! input field related variables
809      INTEGER, OPTIONAL, INTENT(in   ) ::   kyear    ! year value
810      INTEGER, OPTIONAL, INTENT(in   ) ::   kmonth   ! month value
811      INTEGER, OPTIONAL, INTENT(in   ) ::   kday     ! day value
812      LOGICAL, OPTIONAL, INTENT(in   ) ::   ldstop   ! stop if open to read a non-existing file (default = .TRUE.)
813      !
814      LOGICAL :: llprevyr              ! are we reading previous year  file?
815      LOGICAL :: llprevmth             ! are we reading previous month file?
816      INTEGER :: iyear, imonth, iday   ! first day of the current file in yyyy mm dd
817      INTEGER :: isec_week             ! number of seconds since start of the weekly file
818      INTEGER :: indexyr               ! year undex (O/1/2: previous/current/next)
819      INTEGER :: iyear_len, imonth_len ! length (days) of iyear and imonth             !
820      CHARACTER(len = 256)::   clname  ! temporary file name
821      !!----------------------------------------------------------------------
822      IF( PRESENT(kyear) ) THEN                             ! use given values
823         iyear = kyear
824         imonth = kmonth
825         iday = kday
826         IF ( sdjf%cltype(1:4) == 'week' ) THEN             ! find the day of the beginning of the week
827            isec_week = ksec_week( sdjf%cltype(6:8) )- (86400 * 8 ) 
828            llprevmth  = isec_week > nsec_month             ! longer time since beginning of the week than the month
829            llprevyr   = llprevmth .AND. nmonth == 1
830            iyear  = nyear  - COUNT((/llprevyr /))
831            imonth = nmonth - COUNT((/llprevmth/)) + 12 * COUNT((/llprevyr /))
832            iday   = nday   + nmonth_len(nmonth-1) * COUNT((/llprevmth/)) - isec_week / NINT(rday)
833         ENDIF
834      ELSE                                                  ! use current day values
835         IF ( sdjf%cltype(1:4) == 'week' ) THEN             ! find the day of the beginning of the week
836            isec_week  = ksec_week( sdjf%cltype(6:8) )      ! second since the beginning of the week
837            llprevmth  = isec_week > nsec_month             ! longer time since beginning of the week than the month
838            llprevyr   = llprevmth .AND. nmonth == 1
839         ELSE
840            isec_week  = 0
841            llprevmth  = .FALSE.
842            llprevyr   = .FALSE.
843         ENDIF
844         iyear  = nyear  - COUNT((/llprevyr /))
845         imonth = nmonth - COUNT((/llprevmth/)) + 12 * COUNT((/llprevyr /))
846         iday   = nday   + nmonth_len(nmonth-1) * COUNT((/llprevmth/)) - isec_week / NINT(rday)
847      ENDIF
848
849      ! build the new filename if not climatological data
850      clname=TRIM(sdjf%clrootname)
851      !
852      ! note that sdjf%ln_clim is is only acting on the presence of the year in the file name
853      IF( .NOT. sdjf%ln_clim ) THEN   
854                                         WRITE(clname, '(a,"_y",i4.4)' ) TRIM( sdjf%clrootname ), iyear    ! add year
855         IF( sdjf%cltype /= 'yearly' )   WRITE(clname, '(a,"m" ,i2.2)' ) TRIM( clname          ), imonth   ! add month
856      ELSE
857         ! build the new filename if climatological data
858         IF( sdjf%cltype /= 'yearly' )   WRITE(clname, '(a,"_m",i2.2)' ) TRIM( sdjf%clrootname ), imonth   ! add month
859      ENDIF
860      IF( sdjf%cltype == 'daily' .OR. sdjf%cltype(1:4) == 'week' ) &
861            &                            WRITE(clname, '(a,"d" ,i2.2)' ) TRIM( clname          ), iday     ! add day
862      !
863      IF( TRIM(clname) /= TRIM(sdjf%clname) .OR. sdjf%num == 0 ) THEN   ! new file to be open
864         !
865         sdjf%clname = TRIM(clname)
866         IF( sdjf%num /= 0 )   CALL iom_close( sdjf%num )   ! close file if already open
867         CALL iom_open( sdjf%clname, sdjf%num, ldstop = ldstop, ldiof =  LEN(TRIM(sdjf%wgtname)) > 0 )
868         !
869         ! find the last record to be read -> update sdjf%nreclast
870         indexyr = iyear - nyear + 1
871         iyear_len = nyear_len( indexyr )
872         SELECT CASE ( indexyr )
873         CASE ( 0 )   ;   imonth_len = 31   ! previous year -> imonth = 12
874         CASE ( 1 )   ;   imonth_len = nmonth_len(imonth) 
875         CASE ( 2 )   ;   imonth_len = 31   ! next     year -> imonth = 1
876         END SELECT
877         !
878         ! last record to be read in the current file
879         IF    ( sdjf%nfreqh == -12 ) THEN                 ;   sdjf%nreclast = 1    !  yearly mean
880         ELSEIF( sdjf%nfreqh ==  -1 ) THEN                                          ! monthly mean
881            IF(     sdjf%cltype      == 'monthly' ) THEN   ;   sdjf%nreclast = 1
882            ELSE                                           ;   sdjf%nreclast = 12
883            ENDIF
884         ELSE                                                                       ! higher frequency mean (in hours)
885            IF(     sdjf%cltype      == 'monthly' ) THEN   ;   sdjf%nreclast = NINT( 24 * imonth_len / sdjf%nfreqh )
886            ELSEIF( sdjf%cltype(1:4) == 'week'    ) THEN   ;   sdjf%nreclast = NINT( 24 * 7          / sdjf%nfreqh )
887            ELSEIF( sdjf%cltype      == 'daily'   ) THEN   ;   sdjf%nreclast = NINT( 24              / sdjf%nfreqh )
888            ELSE                                           ;   sdjf%nreclast = NINT( 24 * iyear_len  / sdjf%nfreqh )
889            ENDIF
890         ENDIF
891         !
892      ENDIF
893      !
894   END SUBROUTINE fld_clopn
895
896
897   SUBROUTINE fld_fill( sdf, sdf_n, cdir, cdcaller, cdtitle, cdnam, knoprint )
898      !!---------------------------------------------------------------------
899      !!                    ***  ROUTINE fld_fill  ***
900      !!
901      !! ** Purpose :   fill the data structure (sdf) with the associated information
902      !!              read in namelist (sdf_n) and control print
903      !!----------------------------------------------------------------------
904      TYPE(FLD)  , DIMENSION(:)          , INTENT(inout) ::   sdf        ! structure of input fields (file informations, fields read)
905      TYPE(FLD_N), DIMENSION(:)          , INTENT(in   ) ::   sdf_n      ! array of namelist information structures
906      CHARACTER(len=*)                   , INTENT(in   ) ::   cdir       ! Root directory for location of flx files
907      CHARACTER(len=*)                   , INTENT(in   ) ::   cdcaller   ! name of the calling routine
908      CHARACTER(len=*)                   , INTENT(in   ) ::   cdtitle    ! description of the calling routine
909      CHARACTER(len=*)                   , INTENT(in   ) ::   cdnam      ! name of the namelist from which sdf_n comes
910      INTEGER                  , OPTIONAL, INTENT(in   ) ::   knoprint   ! no calling routine information printed
911      !
912      INTEGER  ::   jf   ! dummy indices
913      !!---------------------------------------------------------------------
914      !
915      DO jf = 1, SIZE(sdf)
916         sdf(jf)%clrootname = TRIM( cdir )//TRIM( sdf_n(jf)%clname )
917         sdf(jf)%clname     = "not yet defined"
918         sdf(jf)%nfreqh     = sdf_n(jf)%nfreqh
919         sdf(jf)%clvar      = sdf_n(jf)%clvar
920         sdf(jf)%ln_tint    = sdf_n(jf)%ln_tint
921         sdf(jf)%ln_clim    = sdf_n(jf)%ln_clim
922         sdf(jf)%cltype     = sdf_n(jf)%cltype
923         sdf(jf)%num        = -1
924         sdf(jf)%wgtname    = " "
925         IF( LEN( TRIM(sdf_n(jf)%wname) ) > 0 )   sdf(jf)%wgtname = TRIM( cdir )//TRIM( sdf_n(jf)%wname )
926         sdf(jf)%lsmname = " "
927         IF( LEN( TRIM(sdf_n(jf)%lname) ) > 0 )   sdf(jf)%lsmname = TRIM( cdir )//TRIM( sdf_n(jf)%lname )
928         sdf(jf)%vcomp      = sdf_n(jf)%vcomp
929         sdf(jf)%rotn(:)    = .TRUE.   ! pretend to be rotated -> won't try to rotate data before the first call to fld_get
930         IF( sdf(jf)%cltype(1:4) == 'week' .AND. nn_leapy == 0  )   &
931            &   CALL ctl_stop('fld_clopn: weekly file ('//TRIM(sdf(jf)%clrootname)//') needs nn_leapy = 1')
932         IF( sdf(jf)%cltype(1:4) == 'week' .AND. sdf(jf)%ln_clim )   &
933            &   CALL ctl_stop('fld_clopn: weekly file ('//TRIM(sdf(jf)%clrootname)//') needs ln_clim = .FALSE.')
934         sdf(jf)%nreclast = -1 ! Set to non zero default value to avoid errors, is updated to meaningful value during fld_clopn
935      END DO
936      !
937      IF(lwp) THEN      ! control print
938         WRITE(numout,*)
939         IF( .NOT.PRESENT( knoprint) ) THEN
940            WRITE(numout,*) TRIM( cdcaller )//' : '//TRIM( cdtitle )
941            WRITE(numout,*) (/ ('~', jf = 1, LEN_TRIM( cdcaller ) ) /)
942         ENDIF
943         WRITE(numout,*) '   fld_fill : fill data structure with information from namelist '//TRIM( cdnam )
944         WRITE(numout,*) '   ~~~~~~~~'
945         WRITE(numout,*) '      list of files and frequency (>0: in hours ; <0 in months)'
946         DO jf = 1, SIZE(sdf)
947            WRITE(numout,*) '      root filename: '  , TRIM( sdf(jf)%clrootname ), '   variable name: ', TRIM( sdf(jf)%clvar )
948            WRITE(numout,*) '         frequency: '      ,       sdf(jf)%nfreqh      ,   &
949               &                  '   time interp: '    ,       sdf(jf)%ln_tint     ,   &
950               &                  '   climatology: '    ,       sdf(jf)%ln_clim
951            WRITE(numout,*) '         weights: '        , TRIM( sdf(jf)%wgtname    ),   &
952               &                  '   pairing: '        , TRIM( sdf(jf)%vcomp      ),   &
953               &                  '   data type: '      ,       sdf(jf)%cltype      ,   &
954               &                  '   land/sea mask:'   , TRIM( sdf(jf)%lsmname    )
955            call flush(numout)
956         END DO
957      ENDIF
958      !
959   END SUBROUTINE fld_fill
960
961
962   SUBROUTINE wgt_list( sd, kwgt )
963      !!---------------------------------------------------------------------
964      !!                    ***  ROUTINE wgt_list  ***
965      !!
966      !! ** Purpose :   search array of WGTs and find a weights file entry,
967      !!                or return a new one adding it to the end if new entry.
968      !!                the weights data is read in and restructured (fld_weight)
969      !!----------------------------------------------------------------------
970      TYPE( FLD ), INTENT(in   ) ::   sd        ! field with name of weights file
971      INTEGER    , INTENT(inout) ::   kwgt      ! index of weights
972      !
973      INTEGER ::   kw, nestid   ! local integer
974      LOGICAL ::   found        ! local logical
975      !!----------------------------------------------------------------------
976      !
977      !! search down linked list
978      !! weights filename is either present or we hit the end of the list
979      found = .FALSE.
980      !
981      !! because agrif nest part of filenames are now added in iom_open
982      !! to distinguish between weights files on the different grids, need to track
983      !! nest number explicitly
984      nestid = 0
985#if defined key_agrif
986      nestid = Agrif_Fixed()
987#endif
988      DO kw = 1, nxt_wgt-1
989         IF( TRIM(ref_wgts(kw)%wgtname) == TRIM(sd%wgtname) .AND. &
990             ref_wgts(kw)%nestid == nestid) THEN
991            kwgt = kw
992            found = .TRUE.
993            EXIT
994         ENDIF
995      END DO
996      IF( .NOT.found ) THEN
997         kwgt = nxt_wgt
998         CALL fld_weight( sd )
999      ENDIF
1000      !
1001   END SUBROUTINE wgt_list
1002
1003
1004   SUBROUTINE wgt_print( )
1005      !!---------------------------------------------------------------------
1006      !!                    ***  ROUTINE wgt_print  ***
1007      !!
1008      !! ** Purpose :   print the list of known weights
1009      !!----------------------------------------------------------------------
1010      INTEGER ::   kw   !
1011      !!----------------------------------------------------------------------
1012      !
1013      DO kw = 1, nxt_wgt-1
1014         WRITE(numout,*) 'weight file:  ',TRIM(ref_wgts(kw)%wgtname)
1015         WRITE(numout,*) '      ddims:  ',ref_wgts(kw)%ddims(1),ref_wgts(kw)%ddims(2)
1016         WRITE(numout,*) '     numwgt:  ',ref_wgts(kw)%numwgt
1017         WRITE(numout,*) '     jpiwgt:  ',ref_wgts(kw)%jpiwgt
1018         WRITE(numout,*) '     jpjwgt:  ',ref_wgts(kw)%jpjwgt
1019         WRITE(numout,*) '    botleft:  ',ref_wgts(kw)%botleft
1020         WRITE(numout,*) '   topright:  ',ref_wgts(kw)%topright
1021         IF( ref_wgts(kw)%cyclic ) THEN
1022            WRITE(numout,*) '       cyclical'
1023            IF( ref_wgts(kw)%overlap > 0 ) WRITE(numout,*) '              with overlap of ', ref_wgts(kw)%overlap
1024         ELSE
1025            WRITE(numout,*) '       not cyclical'
1026         ENDIF
1027         IF( ASSOCIATED(ref_wgts(kw)%data_wgt) )  WRITE(numout,*) '       allocated'
1028      END DO
1029      !
1030   END SUBROUTINE wgt_print
1031
1032
1033   SUBROUTINE fld_weight( sd )
1034      !!---------------------------------------------------------------------
1035      !!                    ***  ROUTINE fld_weight  ***
1036      !!
1037      !! ** Purpose :   create a new WGT structure and fill in data from file,
1038      !!              restructuring as required
1039      !!----------------------------------------------------------------------
1040      TYPE( FLD ), INTENT(in) ::   sd   ! field with name of weights file
1041      !!
1042      INTEGER ::   jn         ! dummy loop indices
1043      INTEGER ::   inum       ! local logical unit
1044      INTEGER ::   id         ! local variable id
1045      INTEGER ::   ipk        ! local vertical dimension
1046      INTEGER ::   zwrap      ! local integer
1047      LOGICAL ::   cyclical   !
1048      CHARACTER (len=5) ::   aname   !
1049      INTEGER , DIMENSION(:), ALLOCATABLE ::   ddims
1050      INTEGER , POINTER, DIMENSION(:,:) ::   data_src
1051      REAL(wp), POINTER, DIMENSION(:,:) ::   data_tmp
1052      !!----------------------------------------------------------------------
1053      !
1054      CALL wrk_alloc( jpi,jpj,   data_src )   ! integer
1055      CALL wrk_alloc( jpi,jpj,   data_tmp )
1056      !
1057      IF( nxt_wgt > tot_wgts ) THEN
1058        CALL ctl_stop("fld_weight: weights array size exceeded, increase tot_wgts")
1059      ENDIF
1060      !
1061      !! new weights file entry, add in extra information
1062      !! a weights file represents a 2D grid of a certain shape, so we assume that the current
1063      !! input data file is representative of all other files to be opened and processed with the
1064      !! current weights file
1065
1066      !! open input data file (non-model grid)
1067      CALL iom_open( sd%clname, inum, ldiof =  LEN(TRIM(sd%wgtname)) > 0 )
1068
1069      !! get dimensions
1070      IF ( SIZE(sd%fnow, 3) > 1 ) THEN
1071         ALLOCATE( ddims(4) )
1072      ELSE
1073         ALLOCATE( ddims(3) )
1074      ENDIF
1075      id = iom_varid( inum, sd%clvar, ddims )
1076
1077      !! close it
1078      CALL iom_close( inum )
1079
1080      !! now open the weights file
1081
1082      CALL iom_open ( sd%wgtname, inum )   ! interpolation weights
1083      IF ( inum > 0 ) THEN
1084
1085         !! determine whether we have an east-west cyclic grid
1086         !! from global attribute called "ew_wrap" in the weights file
1087         !! note that if not found, iom_getatt returns -999 and cyclic with no overlap is assumed
1088         !! since this is the most common forcing configuration
1089
1090         CALL iom_getatt(inum, 'ew_wrap', zwrap)
1091         IF( zwrap >= 0 ) THEN
1092            cyclical = .TRUE.
1093         ELSE IF( zwrap == -999 ) THEN
1094            cyclical = .TRUE.
1095            zwrap = 0
1096         ELSE
1097            cyclical = .FALSE.
1098         ENDIF
1099
1100         ref_wgts(nxt_wgt)%ddims(1) = ddims(1)
1101         ref_wgts(nxt_wgt)%ddims(2) = ddims(2)
1102         ref_wgts(nxt_wgt)%wgtname = sd%wgtname
1103         ref_wgts(nxt_wgt)%overlap = zwrap
1104         ref_wgts(nxt_wgt)%cyclic = cyclical
1105         ref_wgts(nxt_wgt)%nestid = 0
1106#if defined key_agrif
1107         ref_wgts(nxt_wgt)%nestid = Agrif_Fixed()
1108#endif
1109         !! weights file is stored as a set of weights (wgt01->wgt04 or wgt01->wgt16)
1110         !! for each weight wgtNN there is an integer array srcNN which gives the point in
1111         !! the input data grid which is to be multiplied by the weight
1112         !! they are both arrays on the model grid so the result of the multiplication is
1113         !! added into an output array on the model grid as a running sum
1114
1115         !! two possible cases: bilinear (4 weights) or bicubic (16 weights)
1116         id = iom_varid(inum, 'src05', ldstop=.FALSE.)
1117         IF( id <= 0) THEN
1118            ref_wgts(nxt_wgt)%numwgt = 4
1119         ELSE
1120            ref_wgts(nxt_wgt)%numwgt = 16
1121         ENDIF
1122
1123         ALLOCATE( ref_wgts(nxt_wgt)%data_jpi(jpi,jpj,4) )
1124         ALLOCATE( ref_wgts(nxt_wgt)%data_jpj(jpi,jpj,4) )
1125         ALLOCATE( ref_wgts(nxt_wgt)%data_wgt(jpi,jpj,ref_wgts(nxt_wgt)%numwgt) )
1126
1127         DO jn = 1,4
1128            aname = ' '
1129            WRITE(aname,'(a3,i2.2)') 'src',jn
1130            data_tmp(:,:) = 0
1131            CALL iom_get ( inum, jpdom_data, aname, data_tmp(:,:) )
1132            data_src(:,:) = INT(data_tmp(:,:))
1133            ref_wgts(nxt_wgt)%data_jpj(:,:,jn) = 1 + (data_src(:,:)-1) / ref_wgts(nxt_wgt)%ddims(1)
1134            ref_wgts(nxt_wgt)%data_jpi(:,:,jn) = data_src(:,:) - ref_wgts(nxt_wgt)%ddims(1)*(ref_wgts(nxt_wgt)%data_jpj(:,:,jn)-1)
1135         END DO
1136
1137         DO jn = 1, ref_wgts(nxt_wgt)%numwgt
1138            aname = ' '
1139            WRITE(aname,'(a3,i2.2)') 'wgt',jn
1140            ref_wgts(nxt_wgt)%data_wgt(:,:,jn) = 0.0
1141            CALL iom_get ( inum, jpdom_data, aname, ref_wgts(nxt_wgt)%data_wgt(:,:,jn) )
1142         END DO
1143         CALL iom_close (inum)
1144 
1145         ! find min and max indices in grid
1146         ref_wgts(nxt_wgt)%botleft(1) = MINVAL(ref_wgts(nxt_wgt)%data_jpi(:,:,:))
1147         ref_wgts(nxt_wgt)%botleft(2) = MINVAL(ref_wgts(nxt_wgt)%data_jpj(:,:,:))
1148         ref_wgts(nxt_wgt)%topright(1) = MAXVAL(ref_wgts(nxt_wgt)%data_jpi(:,:,:))
1149         ref_wgts(nxt_wgt)%topright(2) = MAXVAL(ref_wgts(nxt_wgt)%data_jpj(:,:,:))
1150
1151         ! and therefore dimensions of the input box
1152         ref_wgts(nxt_wgt)%jpiwgt = ref_wgts(nxt_wgt)%topright(1) - ref_wgts(nxt_wgt)%botleft(1) + 1
1153         ref_wgts(nxt_wgt)%jpjwgt = ref_wgts(nxt_wgt)%topright(2) - ref_wgts(nxt_wgt)%botleft(2) + 1
1154
1155         ! shift indexing of source grid
1156         ref_wgts(nxt_wgt)%data_jpi(:,:,:) = ref_wgts(nxt_wgt)%data_jpi(:,:,:) - ref_wgts(nxt_wgt)%botleft(1) + 1
1157         ref_wgts(nxt_wgt)%data_jpj(:,:,:) = ref_wgts(nxt_wgt)%data_jpj(:,:,:) - ref_wgts(nxt_wgt)%botleft(2) + 1
1158
1159         ! create input grid, give it a halo to allow gradient calculations
1160         ! SA: +3 stencil is a patch to avoid out-of-bound computation in some configuration.
1161         ! a more robust solution will be given in next release
1162         ipk =  SIZE(sd%fnow, 3)
1163         ALLOCATE( ref_wgts(nxt_wgt)%fly_dta(ref_wgts(nxt_wgt)%jpiwgt+3, ref_wgts(nxt_wgt)%jpjwgt+3 ,ipk) )
1164         IF( ref_wgts(nxt_wgt)%cyclic ) ALLOCATE( ref_wgts(nxt_wgt)%col(1,ref_wgts(nxt_wgt)%jpjwgt+3,ipk) )
1165         !
1166         nxt_wgt = nxt_wgt + 1
1167         !
1168      ELSE
1169         CALL ctl_stop( '    fld_weight : unable to read the file ' )
1170      ENDIF
1171
1172      DEALLOCATE (ddims )
1173
1174      CALL wrk_dealloc( jpi,jpj, data_src )   ! integer
1175      CALL wrk_dealloc( jpi,jpj, data_tmp )
1176      !
1177   END SUBROUTINE fld_weight
1178
1179
1180   SUBROUTINE apply_seaoverland( clmaskfile, zfieldo, jpi1_lsm, jpi2_lsm, jpj1_lsm,   &
1181      &                          jpj2_lsm, itmpi, itmpj, itmpz, rec1_lsm, recn_lsm )
1182      !!---------------------------------------------------------------------
1183      !!                    ***  ROUTINE apply_seaoverland  ***
1184      !!
1185      !! ** Purpose :   avoid spurious fluxes in coastal or near-coastal areas
1186      !!                due to the wrong usage of "land" values from the coarse
1187      !!                atmospheric model when spatial interpolation is required
1188      !!      D. Delrosso INGV         
1189      !!----------------------------------------------------------------------
1190      INTEGER,                   INTENT(in   ) :: itmpi,itmpj,itmpz                    ! lengths
1191      INTEGER,                   INTENT(in   ) :: jpi1_lsm,jpi2_lsm,jpj1_lsm,jpj2_lsm  ! temporary indices
1192      INTEGER, DIMENSION(3),     INTENT(in   ) :: rec1_lsm,recn_lsm                    ! temporary arrays for start and length
1193      REAL(wp),DIMENSION (:,:,:),INTENT(inout) :: zfieldo                              ! input/output array for seaoverland application
1194      CHARACTER (len=100),       INTENT(in   ) :: clmaskfile                           ! land/sea mask file name
1195      !
1196      INTEGER :: inum,jni,jnj,jnz,jc   ! local indices
1197      REAL(wp),DIMENSION (:,:,:),ALLOCATABLE :: zslmec1             ! local array for land point detection
1198      REAL(wp),DIMENSION (:,:),  ALLOCATABLE :: zfieldn   ! array of forcing field with undeff for land points
1199      REAL(wp),DIMENSION (:,:),  ALLOCATABLE :: zfield    ! array of forcing field
1200      !!---------------------------------------------------------------------
1201      !
1202      ALLOCATE ( zslmec1(itmpi,itmpj,itmpz), zfieldn(itmpi,itmpj), zfield(itmpi,itmpj) )
1203      !
1204      ! Retrieve the land sea mask data
1205      CALL iom_open( clmaskfile, inum )
1206      SELECT CASE( SIZE(zfieldo(jpi1_lsm:jpi2_lsm,jpj1_lsm:jpj2_lsm,:),3) )
1207      CASE(1)
1208         CALL iom_get( inum, jpdom_unknown, 'LSM', zslmec1(jpi1_lsm:jpi2_lsm,jpj1_lsm:jpj2_lsm,1), 1, rec1_lsm, recn_lsm)
1209      CASE DEFAULT
1210         CALL iom_get( inum, jpdom_unknown, 'LSM', zslmec1(jpi1_lsm:jpi2_lsm,jpj1_lsm:jpj2_lsm,:), 1, rec1_lsm, recn_lsm)
1211      END SELECT
1212      CALL iom_close( inum )
1213      !
1214      DO jnz=1,rec1_lsm(3)             !! Loop over k dimension
1215         !
1216         DO jni = 1, itmpi                               !! copy the original field into a tmp array
1217            DO jnj = 1, itmpj                            !! substituting undeff over land points
1218               zfieldn(jni,jnj) = zfieldo(jni,jnj,jnz)
1219               IF( zslmec1(jni,jnj,jnz) == 1. )   zfieldn(jni,jnj) = undeff_lsm
1220            END DO
1221         END DO
1222         !
1223         CALL seaoverland( zfieldn, itmpi, itmpj, zfield )
1224         DO jc = 1, nn_lsm
1225            CALL seaoverland( zfield, itmpi, itmpj, zfield )
1226         END DO
1227         !
1228         !   Check for Undeff and substitute original values
1229         IF( ANY(zfield==undeff_lsm) ) THEN
1230            DO jni = 1, itmpi
1231               DO jnj = 1, itmpj
1232                  IF( zfield(jni,jnj)==undeff_lsm )   zfield(jni,jnj) = zfieldo(jni,jnj,jnz)
1233               END DO
1234            END DO
1235         ENDIF
1236         !
1237         zfieldo(:,:,jnz) = zfield(:,:)
1238         !
1239      END DO                           !! End Loop over k dimension
1240      !
1241      DEALLOCATE ( zslmec1, zfieldn, zfield )
1242      !
1243   END SUBROUTINE apply_seaoverland 
1244
1245
1246   SUBROUTINE seaoverland( zfieldn, ileni, ilenj, zfield )
1247      !!---------------------------------------------------------------------
1248      !!                    ***  ROUTINE seaoverland  ***
1249      !!
1250      !! ** Purpose :   create shifted matrices for seaoverland application 
1251      !!      D. Delrosso INGV
1252      !!----------------------------------------------------------------------
1253      INTEGER                      , INTENT(in   ) :: ileni,ilenj   ! lengths
1254      REAL, DIMENSION (ileni,ilenj), INTENT(in   ) :: zfieldn       ! array of forcing field with undeff for land points
1255      REAL, DIMENSION (ileni,ilenj), INTENT(  out) :: zfield        ! array of forcing field
1256      !
1257      REAL   , DIMENSION (ileni,ilenj)   :: zmat1, zmat2, zmat3, zmat4  ! local arrays
1258      REAL   , DIMENSION (ileni,ilenj)   :: zmat5, zmat6, zmat7, zmat8  !   -     -
1259      REAL   , DIMENSION (ileni,ilenj)   :: zlsm2d                      !   -     -
1260      REAL   , DIMENSION (ileni,ilenj,8) :: zlsm3d                      !   -     -
1261      LOGICAL, DIMENSION (ileni,ilenj,8) :: ll_msknan3d                 ! logical mask for undeff detection
1262      LOGICAL, DIMENSION (ileni,ilenj)   :: ll_msknan2d                 ! logical mask for undeff detection
1263      !!----------------------------------------------------------------------
1264      zmat8 = eoshift( zfieldn , SHIFT=-1 , BOUNDARY = (/zfieldn(:,1)/)     , DIM=2 )
1265      zmat1 = eoshift( zmat8   , SHIFT=-1 , BOUNDARY = (/zmat8(1,:)/)       , DIM=1 )
1266      zmat2 = eoshift( zfieldn , SHIFT=-1 , BOUNDARY = (/zfieldn(1,:)/)     , DIM=1 )
1267      zmat4 = eoshift( zfieldn , SHIFT= 1 , BOUNDARY = (/zfieldn(:,ilenj)/) , DIM=2 )
1268      zmat3 = eoshift( zmat4   , SHIFT=-1 , BOUNDARY = (/zmat4(1,:)/)       , DIM=1 )
1269      zmat5 = eoshift( zmat4   , SHIFT= 1 , BOUNDARY = (/zmat4(ileni,:)/)   , DIM=1 )
1270      zmat6 = eoshift( zfieldn , SHIFT= 1 , BOUNDARY = (/zfieldn(ileni,:)/) , DIM=1 )
1271      zmat7 = eoshift( zmat8   , SHIFT= 1 , BOUNDARY = (/zmat8(ileni,:)/)   , DIM=1 )
1272      !
1273      zlsm3d  = RESHAPE( (/ zmat1, zmat2, zmat3, zmat4, zmat5, zmat6, zmat7, zmat8 /), (/ ileni, ilenj, 8 /))
1274      ll_msknan3d = .NOT.( zlsm3d  == undeff_lsm )
1275      ll_msknan2d = .NOT.( zfieldn == undeff_lsm )  ! FALSE where is Undeff (land)
1276      zlsm2d = SUM( zlsm3d, 3 , ll_msknan3d ) / MAX( 1 , COUNT( ll_msknan3d , 3 ) )
1277      WHERE( COUNT( ll_msknan3d , 3 ) == 0._wp )   zlsm2d = undeff_lsm
1278      zfield = MERGE( zfieldn, zlsm2d, ll_msknan2d )
1279      !
1280   END SUBROUTINE seaoverland
1281
1282
1283   SUBROUTINE fld_interp( num, clvar, kw, kk, dta,  &
1284                          &         nrec, lsmfile)     
1285      !!---------------------------------------------------------------------
1286      !!                    ***  ROUTINE fld_interp  ***
1287      !!
1288      !! ** Purpose :   apply weights to input gridded data to create data
1289      !!                on model grid
1290      !!----------------------------------------------------------------------
1291      INTEGER                   , INTENT(in   ) ::   num     ! stream number
1292      CHARACTER(LEN=*)          , INTENT(in   ) ::   clvar   ! variable name
1293      INTEGER                   , INTENT(in   ) ::   kw      ! weights number
1294      INTEGER                   , INTENT(in   ) ::   kk      ! vertical dimension of kk
1295      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   dta     ! output field on model grid
1296      INTEGER                   , INTENT(in   ) ::   nrec    ! record number to read (ie time slice)
1297      CHARACTER(LEN=*)          , INTENT(in   ) ::   lsmfile ! land sea mask file name
1298      !
1299      INTEGER, DIMENSION(3) ::   rec1, recn           ! temporary arrays for start and length
1300      INTEGER, DIMENSION(3) ::   rec1_lsm, recn_lsm   ! temporary arrays for start and length in case of seaoverland
1301      INTEGER ::   ii_lsm1,ii_lsm2,ij_lsm1,ij_lsm2    ! temporary indices
1302      INTEGER ::   jk, jn, jm, jir, jjr               ! loop counters
1303      INTEGER ::   ni, nj                             ! lengths
1304      INTEGER ::   jpimin,jpiwid                      ! temporary indices
1305      INTEGER ::   jpimin_lsm,jpiwid_lsm              ! temporary indices
1306      INTEGER ::   jpjmin,jpjwid                      ! temporary indices
1307      INTEGER ::   jpjmin_lsm,jpjwid_lsm              ! temporary indices
1308      INTEGER ::   jpi1,jpi2,jpj1,jpj2                ! temporary indices
1309      INTEGER ::   jpi1_lsm,jpi2_lsm,jpj1_lsm,jpj2_lsm   ! temporary indices
1310      INTEGER ::   itmpi,itmpj,itmpz                     ! lengths
1311      REAL(wp),DIMENSION(:,:,:), ALLOCATABLE ::   ztmp_fly_dta                 ! local array of values on input grid     
1312      !!----------------------------------------------------------------------
1313      !
1314      !! for weighted interpolation we have weights at four corners of a box surrounding
1315      !! a model grid point, each weight is multiplied by a grid value (bilinear case)
1316      !! or by a grid value and gradients at the corner point (bicubic case)
1317      !! so we need to have a 4 by 4 subgrid surrounding each model point to cover both cases
1318
1319      !! sub grid from non-model input grid which encloses all grid points in this nemo process
1320      jpimin = ref_wgts(kw)%botleft(1)
1321      jpjmin = ref_wgts(kw)%botleft(2)
1322      jpiwid = ref_wgts(kw)%jpiwgt
1323      jpjwid = ref_wgts(kw)%jpjwgt
1324
1325      !! when reading in, expand this sub-grid by one halo point all the way round for calculating gradients
1326      rec1(1) = MAX( jpimin-1, 1 )
1327      rec1(2) = MAX( jpjmin-1, 1 )
1328      rec1(3) = 1
1329      recn(1) = MIN( jpiwid+2, ref_wgts(kw)%ddims(1)-rec1(1)+1 )
1330      recn(2) = MIN( jpjwid+2, ref_wgts(kw)%ddims(2)-rec1(2)+1 )
1331      recn(3) = kk
1332
1333      !! where we need to put it in the non-nemo grid fly_dta
1334      !! note that jpi1 and jpj1 only differ from 1 when jpimin and jpjmin are 1
1335      !! (ie at the extreme west or south of the whole input grid) and similarly for jpi2 and jpj2
1336      jpi1 = 2 + rec1(1) - jpimin
1337      jpj1 = 2 + rec1(2) - jpjmin
1338      jpi2 = jpi1 + recn(1) - 1
1339      jpj2 = jpj1 + recn(2) - 1
1340
1341
1342      IF( LEN( TRIM(lsmfile) ) > 0 ) THEN
1343      !! indeces for ztmp_fly_dta
1344      ! --------------------------
1345         rec1_lsm(1)=MAX(rec1(1)-nn_lsm,1)  ! starting index for enlarged external data, x direction
1346         rec1_lsm(2)=MAX(rec1(2)-nn_lsm,1)  ! starting index for enlarged external data, y direction
1347         rec1_lsm(3) = 1                    ! vertical dimension
1348         recn_lsm(1)=MIN(rec1(1)-rec1_lsm(1)+recn(1)+nn_lsm,ref_wgts(kw)%ddims(1)-rec1_lsm(1)) ! n points in x direction
1349         recn_lsm(2)=MIN(rec1(2)-rec1_lsm(2)+recn(2)+nn_lsm,ref_wgts(kw)%ddims(2)-rec1_lsm(2)) ! n points in y direction
1350         recn_lsm(3) = kk                   ! number of vertical levels in the input file
1351
1352      !  Avoid out of bound
1353         jpimin_lsm = MAX( rec1_lsm(1)+1, 1 )
1354         jpjmin_lsm = MAX( rec1_lsm(2)+1, 1 )
1355         jpiwid_lsm = MIN( recn_lsm(1)-2,ref_wgts(kw)%ddims(1)-rec1(1)+1)
1356         jpjwid_lsm = MIN( recn_lsm(2)-2,ref_wgts(kw)%ddims(2)-rec1(2)+1)
1357
1358         jpi1_lsm = 2+rec1_lsm(1)-jpimin_lsm
1359         jpj1_lsm = 2+rec1_lsm(2)-jpjmin_lsm
1360         jpi2_lsm = jpi1_lsm + recn_lsm(1) - 1
1361         jpj2_lsm = jpj1_lsm + recn_lsm(2) - 1
1362
1363
1364         itmpi=jpi2_lsm-jpi1_lsm+1
1365         itmpj=jpj2_lsm-jpj1_lsm+1
1366         itmpz=kk
1367         ALLOCATE(ztmp_fly_dta(itmpi,itmpj,itmpz))
1368         ztmp_fly_dta(:,:,:) = 0.0
1369         SELECT CASE( SIZE(ztmp_fly_dta(jpi1_lsm:jpi2_lsm,jpj1_lsm:jpj2_lsm,:),3) )
1370         CASE(1)
1371              CALL iom_get( num, jpdom_unknown, clvar, ztmp_fly_dta(jpi1_lsm:jpi2_lsm,jpj1_lsm:jpj2_lsm,1),   &
1372                 &                                                                nrec, rec1_lsm, recn_lsm)
1373         CASE DEFAULT
1374              CALL iom_get( num, jpdom_unknown, clvar, ztmp_fly_dta(jpi1_lsm:jpi2_lsm,jpj1_lsm:jpj2_lsm,:),   &
1375                 &                                                                nrec, rec1_lsm, recn_lsm)
1376         END SELECT
1377         CALL apply_seaoverland(lsmfile,ztmp_fly_dta(jpi1_lsm:jpi2_lsm,jpj1_lsm:jpj2_lsm,:),                  &
1378                 &                                      jpi1_lsm,jpi2_lsm,jpj1_lsm,jpj2_lsm,                  &
1379                 &                                      itmpi,itmpj,itmpz,rec1_lsm,recn_lsm)
1380
1381
1382         ! Relative indeces for remapping
1383         ii_lsm1 = (rec1(1)-rec1_lsm(1))+1
1384         ii_lsm2 = (ii_lsm1+recn(1))-1
1385         ij_lsm1 = (rec1(2)-rec1_lsm(2))+1
1386         ij_lsm2 = (ij_lsm1+recn(2))-1
1387
1388         ref_wgts(kw)%fly_dta(:,:,:) = 0.0
1389         ref_wgts(kw)%fly_dta(jpi1:jpi2,jpj1:jpj2,:) = ztmp_fly_dta(ii_lsm1:ii_lsm2,ij_lsm1:ij_lsm2,:)
1390         DEALLOCATE(ztmp_fly_dta)
1391
1392      ELSE
1393         
1394         ref_wgts(kw)%fly_dta(:,:,:) = 0.0
1395         SELECT CASE( SIZE(ref_wgts(kw)%fly_dta(jpi1:jpi2,jpj1:jpj2,:),3) )
1396         CASE(1)
1397              CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%fly_dta(jpi1:jpi2,jpj1:jpj2,1), nrec, rec1, recn)
1398         CASE DEFAULT
1399              CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%fly_dta(jpi1:jpi2,jpj1:jpj2,:), nrec, rec1, recn)
1400         END SELECT
1401      ENDIF
1402     
1403
1404      !! first four weights common to both bilinear and bicubic
1405      !! data_jpi, data_jpj have already been shifted to (1,1) corresponding to botleft
1406      !! note that we have to offset by 1 into fly_dta array because of halo
1407      dta(:,:,:) = 0.0
1408      DO jk = 1,4
1409        DO jn = 1, jpj
1410          DO jm = 1,jpi
1411            ni = ref_wgts(kw)%data_jpi(jm,jn,jk)
1412            nj = ref_wgts(kw)%data_jpj(jm,jn,jk)
1413            dta(jm,jn,:) = dta(jm,jn,:) + ref_wgts(kw)%data_wgt(jm,jn,jk) * ref_wgts(kw)%fly_dta(ni+1,nj+1,:)
1414          END DO
1415        END DO
1416      END DO
1417
1418      IF (ref_wgts(kw)%numwgt .EQ. 16) THEN
1419
1420        !! fix up halo points that we couldnt read from file
1421        IF( jpi1 == 2 ) THEN
1422           ref_wgts(kw)%fly_dta(jpi1-1,:,:) = ref_wgts(kw)%fly_dta(jpi1,:,:)
1423        ENDIF
1424        IF( jpi2 + jpimin - 1 == ref_wgts(kw)%ddims(1)+1 ) THEN
1425           ref_wgts(kw)%fly_dta(jpi2+1,:,:) = ref_wgts(kw)%fly_dta(jpi2,:,:)
1426        ENDIF
1427        IF( jpj1 == 2 ) THEN
1428           ref_wgts(kw)%fly_dta(:,jpj1-1,:) = ref_wgts(kw)%fly_dta(:,jpj1,:)
1429        ENDIF
1430        IF( jpj2 + jpjmin - 1 == ref_wgts(kw)%ddims(2)+1 .AND. jpj2 .lt. jpjwid+2 ) THEN
1431           ref_wgts(kw)%fly_dta(:,jpj2+1,:) = 2.0*ref_wgts(kw)%fly_dta(:,jpj2,:) - ref_wgts(kw)%fly_dta(:,jpj2-1,:)
1432        ENDIF
1433
1434        !! if data grid is cyclic we can do better on east-west edges
1435        !! but have to allow for whether first and last columns are coincident
1436        IF( ref_wgts(kw)%cyclic ) THEN
1437           rec1(2) = MAX( jpjmin-1, 1 )
1438           recn(1) = 1
1439           recn(2) = MIN( jpjwid+2, ref_wgts(kw)%ddims(2)-rec1(2)+1 )
1440           jpj1 = 2 + rec1(2) - jpjmin
1441           jpj2 = jpj1 + recn(2) - 1
1442           IF( jpi1 == 2 ) THEN
1443              rec1(1) = ref_wgts(kw)%ddims(1) - ref_wgts(kw)%overlap
1444              SELECT CASE( SIZE( ref_wgts(kw)%col(:,jpj1:jpj2,:),3) )
1445              CASE(1)
1446                   CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col(:,jpj1:jpj2,1), nrec, rec1, recn)
1447              CASE DEFAULT
1448                   CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col(:,jpj1:jpj2,:), nrec, rec1, recn)
1449              END SELECT     
1450              ref_wgts(kw)%fly_dta(jpi1-1,jpj1:jpj2,:) = ref_wgts(kw)%col(1,jpj1:jpj2,:)
1451           ENDIF
1452           IF( jpi2 + jpimin - 1 == ref_wgts(kw)%ddims(1)+1 ) THEN
1453              rec1(1) = 1 + ref_wgts(kw)%overlap
1454              SELECT CASE( SIZE( ref_wgts(kw)%col(:,jpj1:jpj2,:),3) )
1455              CASE(1)
1456                   CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col(:,jpj1:jpj2,1), nrec, rec1, recn)
1457              CASE DEFAULT
1458                   CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col(:,jpj1:jpj2,:), nrec, rec1, recn)
1459              END SELECT
1460              ref_wgts(kw)%fly_dta(jpi2+1,jpj1:jpj2,:) = ref_wgts(kw)%col(1,jpj1:jpj2,:)
1461           ENDIF
1462        ENDIF
1463
1464        ! gradient in the i direction
1465        DO jk = 1,4
1466          DO jn = 1, jpj
1467            DO jm = 1,jpi
1468              ni = ref_wgts(kw)%data_jpi(jm,jn,jk)
1469              nj = ref_wgts(kw)%data_jpj(jm,jn,jk)
1470              dta(jm,jn,:) = dta(jm,jn,:) + ref_wgts(kw)%data_wgt(jm,jn,jk+4) * 0.5 *         &
1471                               (ref_wgts(kw)%fly_dta(ni+2,nj+1,:) - ref_wgts(kw)%fly_dta(ni,nj+1,:))
1472            END DO
1473          END DO
1474        END DO
1475
1476        ! gradient in the j direction
1477        DO jk = 1,4
1478          DO jn = 1, jpj
1479            DO jm = 1,jpi
1480              ni = ref_wgts(kw)%data_jpi(jm,jn,jk)
1481              nj = ref_wgts(kw)%data_jpj(jm,jn,jk)
1482              dta(jm,jn,:) = dta(jm,jn,:) + ref_wgts(kw)%data_wgt(jm,jn,jk+8) * 0.5 *         &
1483                               (ref_wgts(kw)%fly_dta(ni+1,nj+2,:) - ref_wgts(kw)%fly_dta(ni+1,nj,:))
1484            END DO
1485          END DO
1486        END DO
1487
1488         ! gradient in the ij direction
1489         DO jk = 1,4
1490            DO jn = 1, jpj
1491               DO jm = 1,jpi
1492                  ni = ref_wgts(kw)%data_jpi(jm,jn,jk)
1493                  nj = ref_wgts(kw)%data_jpj(jm,jn,jk)
1494                  dta(jm,jn,:) = dta(jm,jn,:) + ref_wgts(kw)%data_wgt(jm,jn,jk+12) * 0.25 * ( &
1495                               (ref_wgts(kw)%fly_dta(ni+2,nj+2,:) - ref_wgts(kw)%fly_dta(ni  ,nj+2,:)) -   &
1496                               (ref_wgts(kw)%fly_dta(ni+2,nj  ,:) - ref_wgts(kw)%fly_dta(ni  ,nj  ,:)))
1497               END DO
1498            END DO
1499         END DO
1500         !
1501      END IF
1502      !
1503   END SUBROUTINE fld_interp
1504
1505
1506   FUNCTION ksec_week( cdday )
1507      !!---------------------------------------------------------------------
1508      !!                    ***  FUNCTION kshift_week ***
1509      !!
1510      !! ** Purpose :   return the first 3 letters of the first day of the weekly file
1511      !!---------------------------------------------------------------------
1512      CHARACTER(len=*), INTENT(in)   ::   cdday   ! first 3 letters of the first day of the weekly file
1513      !!
1514      INTEGER                        ::   ksec_week      ! output variable
1515      INTEGER                        ::   ijul, ishift   ! local integer
1516      CHARACTER(len=3),DIMENSION(7)  ::   cl_week 
1517      !!----------------------------------------------------------------------
1518      cl_week = (/"sun","sat","fri","thu","wed","tue","mon"/)
1519      DO ijul = 1, 7
1520         IF( cl_week(ijul) == TRIM(cdday) ) EXIT
1521      END DO
1522      IF( ijul .GT. 7 )   CALL ctl_stop( 'ksec_week: wrong day for sdjf%cltype(6:8): '//TRIM(cdday) )
1523      !
1524      ishift = ijul * NINT(rday)
1525      !
1526      ksec_week = nsec_week + ishift
1527      ksec_week = MOD( ksec_week, 7*NINT(rday) )
1528      !
1529   END FUNCTION ksec_week
1530
1531   !!======================================================================
1532END MODULE fldread
Note: See TracBrowser for help on using the repository browser.