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/2014/dev_CNRS0_NOC1_LDF/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2014/dev_CNRS0_NOC1_LDF/NEMOGCM/NEMO/OPA_SRC/SBC/fldread.F90 @ 4616

Last change on this file since 4616 was 4616, checked in by gm, 10 years ago

#1260 : see the associated wiki page for explanation

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