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/DEV_r1784_3DF/NEMO/OPA_SRC/SBC – NEMO

source: branches/DEV_r1784_3DF/NEMO/OPA_SRC/SBC/fldread.F90 @ 2125

Last change on this file since 2125 was 2125, checked in by cbricaud, 14 years ago

modification: don't allocate fdta arrays when time-interpollation is not used

  • Property svn:keywords set to Id
File size: 57.3 KB
Line 
1MODULE fldread
2   !!======================================================================
3   !!                       ***  MODULE  fldread  ***
4   !! Ocean forcing:  read input field for surface boundary condition
5   !!=====================================================================
6   !! History :  9.0  !  06-06  (G. Madec) Original code
7   !!                 !  05-08  (S. Alderson) Modified for Interpolation in memory
8   !!                 !         from input grid to model grid
9   !!----------------------------------------------------------------------
10
11   !!----------------------------------------------------------------------
12   !!   fld_read      : read input fields used for the computation of the
13   !!                   surface boundary condition
14   !!----------------------------------------------------------------------
15   USE oce             ! ocean dynamics and tracers
16   USE dom_oce         ! ocean space and time domain
17   USE phycst          ! ???
18   USE in_out_manager  ! I/O manager
19   USE iom             ! I/O manager library
20   USE geo2ocean       ! for vector rotation on to model grid
21
22   IMPLICIT NONE
23   PRIVATE   
24
25   TYPE, PUBLIC ::   FLD_N      !: Namelist field informations
26      CHARACTER(len = 256) ::   clname      ! generic name of the NetCDF flux file
27      INTEGER              ::   nfreqh      ! frequency of each flux file
28      CHARACTER(len = 34)  ::   clvar       ! generic name of the variable in the NetCDF flux file
29      LOGICAL              ::   ln_tint     ! time interpolation or not (T/F)
30      LOGICAL              ::   ln_clim     ! climatology or not (T/F)
31      CHARACTER(len = 7)   ::   cltype      ! type of data file 'daily', 'monthly' or yearly'
32      CHARACTER(len = 34)  ::   wname       ! generic name of a NetCDF weights file to be used, blank if not
33      CHARACTER(len = 34)  ::   vcomp       ! symbolic component name if a vector that needs rotation
34                                           ! a string starting with "U" or "V" for each component   
35                                           ! chars 2 onwards identify which components go together 
36   END TYPE FLD_N
37
38   TYPE, PUBLIC ::   FLD        !: Input field related variables
39      CHARACTER(len = 256)            ::   clrootname   ! generic name of the NetCDF file
40      CHARACTER(len = 256)            ::   clname       ! current name of the NetCDF file
41      INTEGER                         ::   nfreqh       ! frequency of each flux file
42      CHARACTER(len = 34)             ::   clvar        ! generic name of the variable in the NetCDF flux file
43      LOGICAL                         ::   ln_tint      ! time interpolation or not (T/F)
44      LOGICAL                         ::   ln_clim      ! climatology or not (T/F)
45      CHARACTER(len = 7)              ::   cltype       ! type of data file 'daily', 'monthly' or yearly'
46      INTEGER                         ::   num          ! iom id of the jpfld files to be read
47      INTEGER                         ::   nswap_sec    ! swapping time in second since Jan. 1st 00h of nit000 year
48      INTEGER , DIMENSION(2)          ::   nrec_b       ! before record (1: index, 2: second since Jan. 1st 00h of nit000 year)
49      INTEGER , DIMENSION(2)          ::   nrec_a       ! after  record (1: index, 2: second since Jan. 1st 00h of nit000 year)
50      REAL(wp) , ALLOCATABLE, DIMENSION(:,:,:)   ::   fnow       ! input fields interpolated to now time step
51      REAL(wp) , ALLOCATABLE, DIMENSION(:,:,:,:) ::   fdta       ! 2 consecutive record of input fields
52      CHARACTER(len = 256)            ::   wgtname      ! current name of the NetCDF weight file acting as a key
53                                                        ! into the WGTLIST structure
54      CHARACTER(len = 34)             ::   vcomp        ! symbolic name for a vector component that needs rotation
55      LOGICAL ,  DIMENSION(2)         ::   rotn         ! flag to indicate whether field has been rotated
56   END TYPE FLD
57
58!$AGRIF_DO_NOT_TREAT
59
60   !! keep list of all weights variables so they're only read in once
61   !! need to add AGRIF directives not to process this structure
62   !! also need to force wgtname to include AGRIF nest number
63   TYPE         ::   WGT        !: Input weights related variables
64      CHARACTER(len = 256)                    ::   wgtname      ! current name of the NetCDF weight file
65      INTEGER , DIMENSION(2)                  ::   ddims        ! shape of input grid
66      INTEGER , DIMENSION(2)                  ::   botleft      ! top left corner of box in input grid containing
67                                                                ! current processor grid
68      INTEGER , DIMENSION(2)                  ::   topright     ! top right corner of box
69      INTEGER                                 ::   jpiwgt       ! width of box on input grid
70      INTEGER                                 ::   jpjwgt       ! height of box on input grid
71      INTEGER                                 ::   numwgt       ! number of weights (4=bilinear, 16=bicubic)
72      INTEGER                                 ::   nestid       ! for agrif, keep track of nest we're in
73      INTEGER                                 ::   offset       ! =0 when cyclic grid has coincident first/last columns,
74                                                                ! =1 when they assumed to be one grid spacing apart     
75                                                                ! =-1 otherwise
76      LOGICAL                                 ::   cyclic       ! east-west cyclic or not
77      INTEGER, DIMENSION(:,:,:), POINTER      ::   data_jpi     ! array of source integers
78      INTEGER, DIMENSION(:,:,:), POINTER      ::   data_jpj     ! array of source integers
79      REAL(wp), DIMENSION(:,:,:), POINTER     ::   data_wgt     ! array of weights on model grid
80      REAL(wp), DIMENSION(:,:,:), POINTER       ::   fly_dta      ! array of values on input grid
81      REAL(wp), DIMENSION(:,:,:), POINTER       ::   col2         ! temporary array for reading in columns
82   END TYPE WGT
83
84   INTEGER,     PARAMETER             ::   tot_wgts = 10
85   TYPE( WGT ), DIMENSION(tot_wgts)   ::   ref_wgts     ! array of wgts
86   INTEGER                            ::   nxt_wgt = 1  ! point to next available space in ref_wgts array
87
88!$AGRIF_END_DO_NOT_TREAT
89
90   PUBLIC   fld_read, fld_fill   ! called by sbc... modules
91
92   !!----------------------------------------------------------------------
93   !!   OPA 9.0 , LOCEAN-IPSL (2006)
94   !! $Id$
95   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
96   !!----------------------------------------------------------------------
97
98CONTAINS
99
100   SUBROUTINE fld_read( kt, kn_fsbc, sd )
101      !!---------------------------------------------------------------------
102      !!                    ***  ROUTINE fld_read  ***
103      !!                   
104      !! ** Purpose :   provide at each time step the surface ocean fluxes
105      !!                (momentum, heat, freshwater and runoff)
106      !!
107      !! ** Method  :   READ each input fields in NetCDF files using IOM
108      !!      and intepolate it to the model time-step.
109      !!         Several assumptions are made on the input file:
110      !!      blahblahblah....
111      !!----------------------------------------------------------------------
112      INTEGER  , INTENT(in   )               ::   kt        ! ocean time step
113      INTEGER  , INTENT(in   )               ::   kn_fsbc   ! sbc computation period (in time step)
114      TYPE(FLD), INTENT(inout), DIMENSION(:) ::   sd        ! input field related variables
115      !!
116      CHARACTER (LEN=34)                     ::   acomp     ! dummy weight name
117      INTEGER                                ::   kf, nf    ! dummy indices
118      INTEGER                                ::   imf       ! size of the structure sd
119      REAL(wp), DIMENSION(jpi,jpj)           ::   utmp, vtmp! temporary arrays for vector rotation
120
121      INTEGER  ::   jf         ! dummy indices
122      INTEGER  ::   jk         ! dummy indices
123      INTEGER  ::   ipk        ! number of vertical levels of sdjf%fdta ( 2D: ipk=1 ; 3D: ipk=jpk )
124      INTEGER  ::   kw         ! index into wgts array
125      INTEGER  ::   ireclast   ! last record to be read in the current year file
126      INTEGER  ::   isecend    ! number of second since Jan. 1st 00h of nit000 year at nitend
127      LOGICAL  ::   llnxtyr    ! open next year  file?
128      LOGICAL  ::   llnxtmth   ! open next month file?
129      LOGICAL  ::   llstop     ! stop is the file does not exist
130      REAL(wp) ::   ztinta     ! ratio applied to after  records when doing time interpolation
131      REAL(wp) ::   ztintb     ! ratio applied to before records when doing time interpolation
132      CHARACTER(LEN=1000) ::   clfmt   ! write format
133      !!---------------------------------------------------------------------
134      !
135      imf = SIZE( sd )
136      !                                         ! ===================== !
137      DO jf = 1, imf                            !    LOOP OVER FIELD    !
138         !                                      ! ===================== !
139         !
140         IF( kt == nit000 )   CALL fld_init( sd(jf) )
141         !
142         ! read/update the after data?
143         IF( nsec_year + nsec1jan000 > sd(jf)%nswap_sec ) THEN
144
145            IF( sd(jf)%ln_tint ) THEN         ! time interpolation: swap before record field
146!CDIR COLLAPSE
147               sd(jf)%fdta(:,:,:,1) = sd(jf)%fdta(:,:,:,2)
148               sd(jf)%rotn(1)     = sd(jf)%rotn(2)
149            ENDIF
150
151            ! update record informations
152            CALL fld_rec( sd(jf) )
153
154            ! do we have to change the year/month/day of the forcing field??
155            IF( sd(jf)%ln_tint ) THEN
156               ! if we do time interpolation we will need to open next year/month/day file before the end of the current one
157               ! if so, we are still before the end of the year/month/day when calling fld_rec so sd(jf)%nrec_a(1) will be
158               ! larger than the record number that should be read for current year/month/day (for ex. 13 for monthly mean file)
159
160               ! last record to be read in the current file
161               IF( sd(jf)%nfreqh == -1 ) THEN
162                  IF(     sd(jf)%cltype == 'monthly'   ) THEN  ;   ireclast = 1
163                  ELSE                                         ;   ireclast = 12
164                  ENDIF
165               ELSE                             
166                  IF(     sd(jf)%cltype == 'monthly'   ) THEN  ;   ireclast = 24 * nmonth_len(nmonth) / sd(jf)%nfreqh 
167                  ELSEIF( sd(jf)%cltype == 'daily'     ) THEN  ;   ireclast = 24                      / sd(jf)%nfreqh
168                  ELSE                                         ;   ireclast = 24 * nyear_len(     1 ) / sd(jf)%nfreqh 
169                  ENDIF
170               ENDIF
171             
172               ! do we need next file data?
173               IF( sd(jf)%nrec_a(1) > ireclast ) THEN
174
175                  sd(jf)%nrec_a(1) = 1              ! force to read the first record of the next file
176
177                  IF( .NOT. sd(jf)%ln_clim ) THEN   ! close the current file and open a new one.
178
179                     llnxtmth = sd(jf)%cltype == 'monthly' .OR. nday == nmonth_len(nmonth)      ! open next month file?
180                     llnxtyr  = sd(jf)%cltype == 'yearly'  .OR. (nmonth == 12 .AND. llnxtmth)   ! open next year  file?
181
182                     ! if the run finishes at the end of the current year/month/day, we will allow next year/month/day file to be
183                     ! not present. If the run continue further than the current year/month/day, next year/month/day file must exist
184                     isecend = nsec_year + nsec1jan000 + (nitend - kt) * NINT(rdttra(1))   ! second at the end of the run
185                     llstop = isecend > sd(jf)%nswap_sec                                   ! read more than 1 record of next year
186
187                     CALL fld_clopn( sd(jf), nyear  + COUNT((/llnxtyr /))                                           ,         &
188                        &                    nmonth + COUNT((/llnxtmth/)) - 12                 * COUNT((/llnxtyr /)),         &
189                        &                    nday   + 1                   - nmonth_len(nmonth) * COUNT((/llnxtmth/)), llstop )
190
191                     IF( sd(jf)%num == 0 .AND. .NOT. llstop ) THEN    ! next year file does not exist
192                        CALL ctl_warn('next year/month/day file: '//TRIM(sd(jf)%clname)//     &
193                                &     ' not present -> back to current year/month/day')
194                        CALL fld_clopn( sd(jf), nyear, nmonth, nday )       ! back to the current year/month/day
195                        sd(jf)%nrec_a(1) = ireclast     ! force to read the last record to be read in the current year file
196                     ENDIF
197
198                  ENDIF
199               ENDIF
200       
201            ELSE
202               ! if we are not doing time interpolation, we must change the year/month/day of the file just after switching
203               ! to the NEW year/month/day. If it is the case, we are at the beginning of the year/month/day when calling
204               ! fld_rec so sd(jf)%nrec_a(1) = 1
205               IF( sd(jf)%nrec_a(1) == 1 .AND. .NOT. sd(jf)%ln_clim )   CALL fld_clopn( sd(jf), nyear, nmonth, nday )
206            ENDIF
207
208            ! read after data
209            IF( LEN(TRIM(sd(jf)%wgtname)) > 0 ) THEN
210               CALL wgt_list( sd(jf), kw )
211               ipk = SIZE(sd(jf)%fnow,3)
212               IF( sd(jf)%ln_tint ) THEN
213                  CALL fld_interp( sd(jf)%num, sd(jf)%clvar , kw , ipk, sd(jf)%fdta(:,:,:,2) , sd(jf)%nrec_a(1) )
214               ELSE
215                  CALL fld_interp( sd(jf)%num, sd(jf)%clvar , kw , ipk, sd(jf)%fnow(:,:,:)   , sd(jf)%nrec_a(1) )
216               ENDIF
217            ELSE
218               SELECT CASE( SIZE(sd(jf)%fnow,3) )
219               CASE(1)   
220                  IF( sd(jf)%ln_tint ) THEN
221                     CALL iom_get( sd(jf)%num, jpdom_data, sd(jf)%clvar, sd(jf)%fdta(:,:,1,2), sd(jf)%nrec_a(1) )
222                  ELSE
223                     CALL iom_get( sd(jf)%num, jpdom_data, sd(jf)%clvar, sd(jf)%fnow(:,:,1)  , sd(jf)%nrec_a(1) )
224                  ENDIF
225               CASE(jpk)
226                  IF( sd(jf)%ln_tint ) THEN
227                     CALL iom_get( sd(jf)%num, jpdom_data, sd(jf)%clvar, sd(jf)%fdta(:,:,:,2), sd(jf)%nrec_a(1) )
228                  ELSE
229                     CALL iom_get( sd(jf)%num, jpdom_data, sd(jf)%clvar, sd(jf)%fnow(:,:,:)  , sd(jf)%nrec_a(1) )
230                  ENDIF
231               END SELECT
232            ENDIF
233            sd(jf)%rotn(2) = .FALSE.
234
235         ENDIF
236         !                                      ! ===================== !
237      END DO                                    !  END LOOP OVER FIELD  !
238      !                                         ! ===================== !
239
240      IF( kt == nit000 .AND. lwp ) CALL wgt_print()
241
242      !! Vector fields may need to be rotated onto the local grid direction
243      !! This has to happen before the time interpolations
244      !! (sga: following code should be modified so that pairs arent searched for each time
245
246      DO jf = 1, imf
247         !! find vector rotations required
248         IF( LEN(TRIM(sd(jf)%vcomp)) > 0 ) THEN
249             !! east-west component has symbolic name starting with 'U'
250             IF( sd(jf)%vcomp(1:1) == 'U' ) THEN
251                !! found an east-west component, look for the north-south component
252                !! which has same symbolic name but with 'U' replaced with 'V'
253                nf = LEN_TRIM( sd(jf)%vcomp )
254                IF( nf == 1) THEN
255                   acomp = 'V'
256                ELSE
257                   acomp = 'V' // sd(jf)%vcomp(2:nf)
258                ENDIF
259                kf = -1
260                DO nf = 1, imf
261                  IF( TRIM(sd(nf)%vcomp) == TRIM(acomp) ) kf = nf
262                END DO
263                IF( kf > 0 ) THEN
264                   !! fields jf,kf are two components which need to be rotated together
265                   IF( sd(jf)%ln_tint )THEN
266                      DO nf = 1,2
267                         !! check each time level of this pair
268                         IF( .NOT. sd(jf)%rotn(nf) .AND. .NOT. sd(kf)%rotn(nf) ) THEN
269                            utmp(:,:) = 0.0
270                            vtmp(:,:) = 0.0
271                            !
272                            ipk = SIZE( sd(kf)%fnow(:,:,:) ,3 )
273                            DO jk = 1,ipk
274                               CALL rot_rep( sd(jf)%fdta(:,:,jk,nf),sd(kf)%fdta(:,:,jk,nf),'T', 'en->i', utmp(:,:) )
275                               CALL rot_rep( sd(jf)%fdta(:,:,jk,nf),sd(kf)%fdta(:,:,jk,nf),'T', 'en->j', vtmp(:,:) )
276                               sd(jf)%fdta(:,:,jk,nf) = utmp(:,:)
277                               sd(kf)%fdta(:,:,jk,nf) = vtmp(:,:)
278                            ENDDO
279                            !
280                            sd(jf)%rotn(nf) = .TRUE.
281                            sd(kf)%rotn(nf) = .TRUE.
282                            IF( lwp .AND. kt == nit000 ) &
283                                      WRITE(numout,*) 'fld_read: vector pair (',  &
284                                                      TRIM(sd(jf)%clvar),',',TRIM(sd(kf)%clvar), &
285                                                      ') rotated on to model grid'
286                         ENDIF
287                      END DO
288                   ELSE 
289                      !! check each time level of this pair
290                      IF( .NOT. sd(jf)%rotn(nf) .AND. .NOT. sd(kf)%rotn(nf) ) THEN
291                         utmp(:,:) = 0.0
292                         vtmp(:,:) = 0.0
293                         !
294                         ipk = SIZE( sd(kf)%fnow(:,:,:) ,3 )
295                         DO jk = 1,ipk
296                            CALL rot_rep( sd(jf)%fnow(:,:,jk),sd(kf)%fnow(:,:,jk),'T', 'en->i', utmp(:,:) )
297                            CALL rot_rep( sd(jf)%fnow(:,:,jk),sd(kf)%fnow(:,:,jk),'T', 'en->j', vtmp(:,:) )
298                            sd(jf)%fnow(:,:,jk) = utmp(:,:)
299                            sd(kf)%fnow(:,:,jk) = vtmp(:,:)
300                         ENDDO
301                         !
302                         sd(jf)%rotn(nf) = .TRUE.
303                         sd(kf)%rotn(nf) = .TRUE.
304                         IF( lwp .AND. kt == nit000 ) &
305                                   WRITE(numout,*) 'fld_read: vector pair (',  &
306                                                   TRIM(sd(jf)%clvar),',',TRIM(sd(kf)%clvar), &
307                                                   ') rotated on to model grid'
308                      ENDIF
309                   ENDIF
310                ENDIF
311             ENDIF
312         ENDIF
313      END DO
314
315      !                                         ! ===================== !
316      DO jf = 1, imf                            !    LOOP OVER FIELD    !
317         !                                      ! ===================== !
318         !
319         ! update field at each kn_fsbc time-step
320         IF( MOD( kt-1, kn_fsbc ) == 0 ) THEN   
321            !
322            IF( sd(jf)%ln_tint ) THEN
323               IF(lwp .AND. kt - nit000 <= 100 ) THEN
324                  clfmt = "('fld_read: var ', a, ' kt = ', i8,' Y/M/D = ', i4.4,'/', i2.2,'/', i2.2," //   &
325                     &    "' records b/a: ', i4.4, '/', i4.4, ' (', f7.2,'/', f7.2, ' days)')"
326                  WRITE(numout, clfmt)  TRIM( sd(jf)%clvar ), kt, nyear, nmonth, nday,   &
327                     & 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
328               ENDIF
329               !
330               ztinta =  REAL( nsec_year + nsec1jan000 - sd(jf)%nrec_b(2), wp ) / REAL( sd(jf)%nrec_a(2) - sd(jf)%nrec_b(2), wp )
331               ztintb =  1. - ztinta
332!CDIR COLLAPSE
333               sd(jf)%fnow(:,:,:) = ztintb * sd(jf)%fdta(:,:,:,1) + ztinta * sd(jf)%fdta(:,:,:,2)
334            ELSE
335               IF(lwp .AND. kt - nit000 <= 100 ) THEN
336                  clfmt = "('fld_read: var ', a, ' kt = ', i8,' Y/M/D = ', i4.4,'/', i2.2,'/', i2.2," //   &
337                     &    "' record: ', i4.4, ' at ', f7.2, ' day')"
338                  WRITE(numout, clfmt) TRIM(sd(jf)%clvar), kt, nyear, nmonth, nday, sd(jf)%nrec_a(1), REAL(sd(jf)%nrec_a(2),wp)/rday
339               ENDIF
340!CDIR COLLAPSE
341            ENDIF
342            !
343         ENDIF
344
345         IF( kt == nitend )   CALL iom_close( sd(jf)%num )   ! Close the input files
346
347         !                                      ! ===================== !
348      END DO                                    !  END LOOP OVER FIELD  !
349      !                                         ! ===================== !
350   END SUBROUTINE fld_read
351
352
353   SUBROUTINE fld_init( sdjf )
354      !!---------------------------------------------------------------------
355      !!                    ***  ROUTINE fld_init  ***
356      !!
357      !! ** Purpose :  - if time interpolation, read before data
358      !!               - open current year file
359      !!
360      !! ** Method  :   
361      !!----------------------------------------------------------------------
362      TYPE(FLD), INTENT(inout) ::   sdjf        ! input field related variables
363      !!
364      LOGICAL :: llprevyr       ! are we reading previous year  file?
365      LOGICAL :: llprevmth      ! are we reading previous month file?
366      LOGICAL :: llprevday      ! are we reading previous day   file?
367      LOGICAL :: llprev         ! llprevyr .OR. llprevmth .OR. llprevday
368      INTEGER :: idvar          ! variable id
369      INTEGER :: inrec          ! number of record existing for this variable
370      INTEGER :: kwgt
371      INTEGER :: jk             !vertical loop variable
372      INTEGER :: ipk            !number of vertical levels of sdjf%fdta ( 2D: ipk=1 ; 3D: ipk=jpk )
373      CHARACTER(LEN=1000) ::   clfmt   ! write format
374      !!---------------------------------------------------------------------
375
376      ! some default definitions...
377      sdjf%num = 0   ! default definition for non-opened file
378      IF( sdjf%ln_clim )   sdjf%clname = TRIM( sdjf%clrootname )   ! file name defaut definition, never change in this case
379      llprevyr  = .FALSE.
380      llprevmth = .FALSE.
381      llprevday = .FALSE.
382           
383      ! define record informations
384      CALL fld_rec( sdjf )
385
386      IF( sdjf%ln_tint ) THEN ! we need to read the previous record and we will put it in the current record structure
387         
388         IF( sdjf%nrec_b(1) == 0  ) THEN   ! we redefine record sdjf%nrec_b(1) with the last record of previous year file
389            IF( sdjf%nfreqh == -1 ) THEN   ! monthly mean
390               IF( sdjf%cltype == 'monthly' ) THEN   ! monthly file
391                  sdjf%nrec_b(1) = 1                                                       ! force to read the unique record
392                  llprevmth = .TRUE.                                                       ! use previous month file?
393                  llprevyr  = llprevmth .AND. nmonth == 1                                  ! use previous year  file?
394               ELSE                                  ! yearly file
395                  sdjf%nrec_b(1) = 12                                                      ! force to read december mean
396                  llprevyr = .NOT. sdjf%ln_clim                                            ! use previous year  file?
397               ENDIF
398            ELSE   
399               IF( sdjf%cltype == 'monthly' ) THEN   ! monthly file
400                  sdjf%nrec_b(1) = 24 * nmonth_len(nmonth-1) / sdjf%nfreqh                 ! last record of previous month
401                  llprevmth = .NOT. sdjf%ln_clim                                           ! use previous month file?
402                  llprevyr  = llprevmth .AND. nmonth == 1                                  ! use previous year  file?
403               ELSEIF( sdjf%cltype == 'daily' ) THEN ! daily file
404                  sdjf%nrec_b(1) = 24 / sdjf%nfreqh                                        ! last record of previous day
405                  llprevday = .NOT. sdjf%ln_clim                                           ! use previous day   file?
406                  llprevmth = llprevday .AND. nday   == 1                                  ! use previous month file?
407                  llprevyr  = llprevmth .AND. nmonth == 1                                  ! use previous year  file?
408               ELSE                                  ! yearly file
409                  sdjf%nrec_b(1) = 24 * nyear_len(0) / sdjf%nfreqh                         ! last record of year month
410                  llprevyr = .NOT. sdjf%ln_clim                                            ! use previous year  file?
411               ENDIF
412            ENDIF
413         ENDIF
414         llprev = llprevyr .OR. llprevmth .OR. llprevday
415
416         CALL fld_clopn( sdjf, nyear  - COUNT((/llprevyr /))                                              ,               &
417            &                  nmonth - COUNT((/llprevmth/)) + 12                   * COUNT((/llprevyr /)),               &
418            &                  nday   - COUNT((/llprevday/)) + nmonth_len(nmonth-1) * COUNT((/llprevmth/)), .NOT. llprev )
419
420         ! if previous year/month/day file does not exist, we switch to the current year/month/day
421         IF( llprev .AND. sdjf%num == 0 ) THEN
422            CALL ctl_warn( 'previous year/month/day file: '//TRIM(sdjf%clname)//' not present -> back to current year/month/day')
423            ! we force to read the first record of the current year/month/day instead of last record of previous year/month/day
424            llprev = .false.
425            sdjf%nrec_b(1) = 1
426            CALL fld_clopn( sdjf, nyear, nmonth, nday )
427         ENDIF
428         
429         IF( llprev ) THEN   ! check if the last record sdjf%nrec_n(1) exists in the file
430            idvar = iom_varid( sdjf%num, sdjf%clvar )                                        ! id of the variable sdjf%clvar
431            IF( idvar <= 0 )   RETURN
432            inrec = iom_file( sdjf%num )%dimsz( iom_file( sdjf%num )%ndims(idvar), idvar )   ! size of the last dim of idvar
433            sdjf%nrec_b(1) = MIN( sdjf%nrec_b(1), inrec )   ! make sure we select an existing record
434         ENDIF
435
436         ! read before data into sdjf%fdta(:,:,2) because we will swap data in the following part of fld_read
437         
438         IF( LEN(TRIM(sdjf%wgtname)) > 0 ) THEN
439            CALL wgt_list( sdjf, kwgt )
440            ipk = SIZE(sdjf%fnow,3)
441            IF( sdjf%ln_tint ) THEN
442               CALL fld_interp( sdjf%num, sdjf%clvar, kwgt, ipk, sdjf%fdta(:,:,:,2), sdjf%nrec_a(1) )
443            ELSE
444               CALL fld_interp( sdjf%num, sdjf%clvar, kwgt, ipk, sdjf%fnow(:,:,:)  , sdjf%nrec_a(1) )
445            ENDIF
446         ELSE
447            write(narea+200,*)' sdjf%ln_tint SIZE(sdjf%fnow,3) ',sdjf%ln_tint,SIZE(sdjf%fnow,3) ; call flush(narea+200)
448            write(narea+200,*)' SIZE(sdjf%fdta,3)  SIZE(sdjf%fdta,4) ',SIZE(sdjf%fdta,3),SIZE(sdjf%fdta,4)  ; call flush(narea+200)
449            SELECT CASE( SIZE(sdjf%fnow,3) )
450            CASE(1)
451               IF( sdjf%ln_tint ) THEN
452                  CALL iom_get( sdjf%num, jpdom_data, sdjf%clvar, sdjf%fdta(:,:,1,2), sdjf%nrec_b(1) )
453               ELSE
454                  CALL iom_get( sdjf%num, jpdom_data, sdjf%clvar, sdjf%fnow(:,:,1)  , sdjf%nrec_b(1) )
455               ENDIF
456            CASE(jpk)
457               IF( sdjf%ln_tint ) THEN
458                  CALL iom_get( sdjf%num, jpdom_data, sdjf%clvar, sdjf%fdta(:,:,:,2), sdjf%nrec_b(1) )
459               ELSE
460                  CALL iom_get( sdjf%num, jpdom_data, sdjf%clvar, sdjf%fnow(:,:,:)  , sdjf%nrec_b(1) )
461               ENDIF
462            END SELECT
463            write(narea+200,*)' test1 ok ' ; call flush(narea+200)
464         ENDIF
465         sdjf%rotn(2) = .FALSE.
466
467         clfmt = "('fld_init : time-interpolation for ', a, ' read previous record = ', i4, ' at time = ', f7.2, ' days')"
468         IF(lwp) WRITE(numout, clfmt) TRIM(sdjf%clvar), sdjf%nrec_b(1), REAL(sdjf%nrec_b(2),wp)/rday
469
470         IF( llprev )   CALL iom_close( sdjf%num )   ! close previous year file (-> redefine sdjf%num to 0)
471
472      ENDIF
473
474
475      IF( sdjf%num == 0 )   CALL fld_clopn( sdjf, nyear, nmonth, nday )   ! make sure current year/month/day file is opened
476
477      sdjf%nswap_sec = nsec_year + nsec1jan000 - 1   ! force read/update the after data in the following part of fld_read
478     
479   END SUBROUTINE fld_init
480
481
482   SUBROUTINE fld_rec( sdjf )
483      !!---------------------------------------------------------------------
484      !!                    ***  ROUTINE fld_rec  ***
485      !!
486      !! ** Purpose :   compute nrec_a, nrec_b and nswap_sec
487      !!
488      !! ** Method  :   
489      !!----------------------------------------------------------------------
490      TYPE(FLD), INTENT(inout) ::   sdjf        ! input field related variables
491      !!
492      INTEGER  ::   irec        ! record number
493      INTEGER  ::   isecd       ! rday
494      REAL(wp) ::   ztmp        ! temporary variable
495      INTEGER  ::   ifreq_sec   ! frequency mean (in seconds)
496      !!----------------------------------------------------------------------
497      !
498      IF( sdjf%nfreqh == -1 ) THEN      ! monthly mean
499         !
500         IF( sdjf%ln_tint ) THEN                 ! time interpolation, shift by 1/2 record
501            !
502            !                  INT( ztmp )
503            !                     /|\
504            !                    1 |    *----
505            !                    0 |----(             
506            !                      |----+----|--> time
507            !                      0   /|\   1   (nday/nmonth_len(nmonth))
508            !                           |   
509            !                           |   
510            !       forcing record :  nmonth
511            !                           
512            ztmp  = 0.e0
513            IF(  REAL( nday, wp ) / REAL( nmonth_len(nmonth), wp ) .GT. 0.5 ) ztmp  = 1.0
514         ELSE
515            ztmp  = 0.e0
516         ENDIF
517         irec = nmonth + INT( ztmp )
518
519         IF( sdjf%ln_tint ) THEN   ;   sdjf%nswap_sec = nmonth_half(irec) + nsec1jan000   ! swap at the middle of the month
520         ELSE                      ;   sdjf%nswap_sec = nmonth_end (irec) + nsec1jan000   ! swap at the end    of the month
521         ENDIF
522
523         IF( sdjf%cltype == 'monthly' ) THEN
524
525            sdjf%nrec_b(:) = (/ 0, nmonth_half(irec - 1 ) + nsec1jan000 /)
526            sdjf%nrec_a(:) = (/ 1, nmonth_half(irec     ) + nsec1jan000 /)
527
528            IF( ztmp  == 1. ) THEN
529              sdjf%nrec_b(1) = 1
530              sdjf%nrec_a(1) = 2
531            ENDIF
532
533         ELSE
534
535            sdjf%nrec_a(:) = (/ irec, nmonth_half(irec) + nsec1jan000 /)   ! define after  record number and time
536            irec = irec - 1                                                ! move back to previous record
537            sdjf%nrec_b(:) = (/ irec, nmonth_half(irec) + nsec1jan000 /)   ! define before record number and time
538
539         ENDIF
540         !
541      ELSE                              ! higher frequency mean (in hours)
542         !
543         ifreq_sec = sdjf%nfreqh * 3600   ! frequency mean (in seconds)
544         ! number of second since the beginning of the file
545         IF(     sdjf%cltype == 'monthly' ) THEN   ;   ztmp = REAL(nsec_month,wp)   ! since 00h on the 1st day of the current month
546         ELSEIF( sdjf%cltype == 'daily'   ) THEN   ;   ztmp = REAL(nsec_day  ,wp)   ! since 00h of the current day
547         ELSE                                      ;   ztmp = REAL(nsec_year ,wp)   ! since 00h on Jan 1 of the current year
548         ENDIF
549         IF( sdjf%ln_tint ) THEN                ! time interpolation, shift by 1/2 record
550            !
551            !                  INT( ztmp )
552            !                     /|\
553            !                    2 |        *-----(
554            !                    1 |  *-----(
555            !                    0 |--(             
556            !                      |--+--|--+--|--+--|--> time
557            !                      0 /|\ 1 /|\ 2 /|\ 3 (nsec_year/ifreq_sec) or (nsec_month/ifreq_sec)
558            !                         |     |     |
559            !                         |     |     |
560            !       forcing record :  1     2     3
561            !                   
562            ztmp= ztmp / ifreq_sec + 0.5
563         ELSE                 
564            !
565            !                  INT( ztmp )
566            !                     /|\
567            !                    2 |           *-----(
568            !                    1 |     *-----(
569            !                    0 |-----(             
570            !                      |--+--|--+--|--+--|--> time
571            !                      0 /|\ 1 /|\ 2 /|\ 3 (nsec_year/ifreq_sec) or (nsec_month/ifreq_sec)
572            !                         |     |     |
573            !                         |     |     |
574            !       forcing record :  1     2     3
575            !                           
576            ztmp= ztmp / ifreq_sec
577         ENDIF
578         irec = 1 + INT( ztmp )
579
580         isecd = NINT(rday)
581         ! after record index and second since Jan. 1st 00h of nit000 year
582         sdjf%nrec_a(:) = (/ irec, ifreq_sec * irec - ifreq_sec / 2 + nsec1jan000 /)
583         IF( sdjf%cltype == 'monthly' )   &   ! add the number of seconds between 00h Jan 1 and the end of previous month
584            sdjf%nrec_a(2) = sdjf%nrec_a(2) + isecd * SUM(nmonth_len(1:nmonth -1))   ! ok if nmonth=1
585         IF( sdjf%cltype == 'daily'   )   &   ! add the number of seconds between 00h Jan 1 and the end of previous day
586            sdjf%nrec_a(2) = sdjf%nrec_a(2) + isecd * ( nday_year - 1 )
587
588         ! before record index and second since Jan. 1st 00h of nit000 year
589         irec = irec - 1.                           ! move back to previous record
590         sdjf%nrec_b(:) = (/ irec, ifreq_sec * irec - ifreq_sec / 2 + nsec1jan000 /)
591         IF( sdjf%cltype == 'monthly' )   &   ! add the number of seconds between 00h Jan 1 and the end of previous month
592            sdjf%nrec_b(2) = sdjf%nrec_b(2) + isecd * SUM(nmonth_len(1:nmonth -1))   ! ok if nmonth=1
593         IF( sdjf%cltype == 'daily'   )   &   ! add the number of seconds between 00h Jan 1 and the end of previous day
594            sdjf%nrec_b(2) = sdjf%nrec_b(2) + isecd * ( nday_year - 1 )
595
596         ! swapping time in second since Jan. 1st 00h of nit000 year
597         IF( sdjf%ln_tint ) THEN   ;   sdjf%nswap_sec =  sdjf%nrec_a(2)                     ! swap at the middle of the record
598         ELSE                      ;   sdjf%nswap_sec =  sdjf%nrec_a(2) + ifreq_sec / 2     ! swap at the end    of the record
599         ENDIF       
600         !
601      ENDIF
602      !
603   END SUBROUTINE fld_rec
604
605
606   SUBROUTINE fld_clopn( sdjf, kyear, kmonth, kday, ldstop )
607      !!---------------------------------------------------------------------
608      !!                    ***  ROUTINE fld_clopn  ***
609      !!
610      !! ** Purpose :   update the file name and open the file
611      !!
612      !! ** Method  :   
613      !!----------------------------------------------------------------------
614      TYPE(FLD), INTENT(inout)           ::   sdjf     ! input field related variables
615      INTEGER  , INTENT(in   )           ::   kyear    ! year value
616      INTEGER  , INTENT(in   )           ::   kmonth   ! month value
617      INTEGER  , INTENT(in   )           ::   kday     ! day value
618      LOGICAL  , INTENT(in   ), OPTIONAL ::   ldstop   ! stop if open to read a non-existing file (default = .TRUE.)
619
620      IF( sdjf%num /= 0 )   CALL iom_close( sdjf%num )   ! close file if already open
621      ! build the new filename if not climatological data
622      IF( .NOT. sdjf%ln_clim ) THEN   ;   WRITE(sdjf%clname, '(a,"_y",i4.4)' ) TRIM( sdjf%clrootname ), kyear    ! add year
623         IF( sdjf%cltype /= 'yearly' )    WRITE(sdjf%clname, '(a,"m" ,i2.2)' ) TRIM( sdjf%clname     ), kmonth   ! add month
624         IF( sdjf%cltype == 'daily'  )    WRITE(sdjf%clname, '(a,"d" ,i2.2)' ) TRIM( sdjf%clname     ), kday     ! add day
625      ELSE
626         ! build the new filename if climatological data
627         IF( sdjf%cltype == 'monthly' )   WRITE(sdjf%clname, '(a,"_m" ,i2.2)' ) TRIM( sdjf%clrootname ), kmonth   ! add month
628      ENDIF
629      CALL iom_open( sdjf%clname, sdjf%num, ldstop = ldstop, ldiof =  LEN(TRIM(sdjf%wgtname)) > 0 )
630      !
631   END SUBROUTINE fld_clopn
632
633
634   SUBROUTINE fld_fill( sdf, sdf_n, cdir, cdcaller, cdtitle, cdnam )
635      !!---------------------------------------------------------------------
636      !!                    ***  ROUTINE fld_fill  ***
637      !!
638      !! ** Purpose :   fill sdf with sdf_n and control print
639      !!
640      !! ** Method  :   
641      !!----------------------------------------------------------------------
642      TYPE(FLD)  , DIMENSION(:), INTENT(inout) ::   sdf        ! structure of input fields (file informations, fields read)
643      TYPE(FLD_N), DIMENSION(:), INTENT(in   ) ::   sdf_n      ! array of namelist information structures
644      CHARACTER(len=*)         , INTENT(in   ) ::   cdir       ! Root directory for location of flx files
645      CHARACTER(len=*)         , INTENT(in   ) ::   cdcaller   !
646      CHARACTER(len=*)         , INTENT(in   ) ::   cdtitle    !
647      CHARACTER(len=*)         , INTENT(in   ) ::   cdnam      !
648      !
649      INTEGER  ::   jf       ! dummy indices
650      !!---------------------------------------------------------------------
651
652      DO jf = 1, SIZE(sdf)
653         sdf(jf)%clrootname = TRIM( cdir )//TRIM( sdf_n(jf)%clname )
654         sdf(jf)%nfreqh     = sdf_n(jf)%nfreqh
655         sdf(jf)%clvar      = sdf_n(jf)%clvar
656         sdf(jf)%ln_tint    = sdf_n(jf)%ln_tint
657         sdf(jf)%ln_clim    = sdf_n(jf)%ln_clim
658         sdf(jf)%cltype     = sdf_n(jf)%cltype
659         sdf(jf)%wgtname = " "
660         IF( LEN( TRIM(sdf_n(jf)%wname) ) > 0 )   sdf(jf)%wgtname = TRIM( cdir )//TRIM( sdf_n(jf)%wname )
661         sdf(jf)%vcomp   = sdf_n(jf)%vcomp
662      END DO
663
664      IF(lwp) THEN      ! control print
665         WRITE(numout,*)
666         WRITE(numout,*) TRIM( cdcaller )//' : '//TRIM( cdtitle )
667         WRITE(numout,*) (/ ('~', jf = 1, LEN_TRIM( cdcaller ) ) /)
668         WRITE(numout,*) '          '//TRIM( cdnam )//' Namelist'
669         WRITE(numout,*) '          list of files and frequency (>0: in hours ; <0 in months)'
670         DO jf = 1, SIZE(sdf)
671            WRITE(numout,*) '               root filename: '  , TRIM( sdf(jf)%clrootname ),   &
672               &                          ' variable name: '  , TRIM( sdf(jf)%clvar      )
673            WRITE(numout,*) '               frequency: '      ,       sdf(jf)%nfreqh      ,   &
674               &                          ' time interp: '    ,       sdf(jf)%ln_tint     ,   &
675               &                          ' climatology: '    ,       sdf(jf)%ln_clim     ,   &
676               &                          ' weights    : '    , TRIM( sdf(jf)%wgtname    ),   &
677               &                          ' pairing    : '    , TRIM( sdf(jf)%vcomp      ),   &
678               &                          ' data type: '      ,       sdf(jf)%cltype
679            call flush(numout)
680         END DO
681      ENDIF
682     
683   END SUBROUTINE fld_fill
684
685
686   SUBROUTINE wgt_list( sd, kwgt )
687      !!---------------------------------------------------------------------
688      !!                    ***  ROUTINE wgt_list  ***
689      !!
690      !! ** Purpose :   search array of WGTs and find a weights file
691      !!                entry, or return a new one adding it to the end
692      !!                if it is a new entry, the weights data is read in and
693      !!                restructured (fld_weight)
694      !!
695      !! ** Method  :   
696      !!----------------------------------------------------------------------
697      TYPE( FLD ),      INTENT(in)    ::   sd        ! field with name of weights file
698      INTEGER,      INTENT(inout)     ::   kwgt      ! index of weights
699      !!
700      INTEGER                         ::   kw
701      INTEGER                         ::   nestid
702      LOGICAL                         ::   found
703      !!----------------------------------------------------------------------
704      !
705      !! search down linked list
706      !! weights filename is either present or we hit the end of the list
707      found = .FALSE.
708
709      !! because agrif nest part of filenames are now added in iom_open
710      !! to distinguish between weights files on the different grids, need to track
711      !! nest number explicitly
712      nestid = 0
713#if defined key_agrif
714      nestid = Agrif_Fixed()
715#endif
716      DO kw = 1, nxt_wgt-1
717         IF( TRIM(ref_wgts(kw)%wgtname) == TRIM(sd%wgtname) .AND. &
718             ref_wgts(kw)%nestid == nestid) THEN
719            kwgt = kw
720            found = .TRUE.
721            EXIT
722         ENDIF
723      END DO
724      IF( .NOT.found ) THEN
725         kwgt = nxt_wgt
726         CALL fld_weight( sd )
727      ENDIF
728
729   END SUBROUTINE wgt_list
730
731   SUBROUTINE wgt_print( )
732      !!---------------------------------------------------------------------
733      !!                    ***  ROUTINE wgt_print  ***
734      !!
735      !! ** Purpose :   print the list of known weights
736      !!
737      !! ** Method  :   
738      !!----------------------------------------------------------------------
739      !!
740      INTEGER                         ::   kw
741      !!----------------------------------------------------------------------
742      !
743
744      DO kw = 1, nxt_wgt-1
745         WRITE(numout,*) 'weight file:  ',TRIM(ref_wgts(kw)%wgtname)
746         WRITE(numout,*) '      ddims:  ',ref_wgts(kw)%ddims(1),ref_wgts(kw)%ddims(2)
747         WRITE(numout,*) '     numwgt:  ',ref_wgts(kw)%numwgt
748         WRITE(numout,*) '     jpiwgt:  ',ref_wgts(kw)%jpiwgt
749         WRITE(numout,*) '     jpjwgt:  ',ref_wgts(kw)%jpjwgt
750         WRITE(numout,*) '    botleft:  ',ref_wgts(kw)%botleft
751         WRITE(numout,*) '   topright:  ',ref_wgts(kw)%topright
752         IF( ref_wgts(kw)%cyclic ) THEN
753            WRITE(numout,*) '       cyclical'
754            IF( ref_wgts(kw)%offset > 0 ) WRITE(numout,*) '                 with offset'
755         ELSE
756            WRITE(numout,*) '       not cyclical'
757         ENDIF
758         IF( ASSOCIATED(ref_wgts(kw)%data_wgt) )  WRITE(numout,*) '       allocated'
759      END DO
760
761   END SUBROUTINE wgt_print
762
763   SUBROUTINE fld_weight( sd )
764      !!---------------------------------------------------------------------
765      !!                    ***  ROUTINE fld_weight  ***
766      !!
767      !! ** Purpose :   create a new WGT structure and fill in data from 
768      !!                file, restructuring as required
769      !!
770      !! ** Method  :   
771      !!----------------------------------------------------------------------
772      TYPE( FLD ),      INTENT(in)            ::   sd            ! field with name of weights file
773      !!
774      INTEGER                                 ::   jn            ! dummy loop indices
775      INTEGER                                 ::   inum          ! temporary logical unit
776      INTEGER                                 ::   id            ! temporary variable id
777      INTEGER                                 ::   ipk           ! temporary vertical dimension
778      CHARACTER (len=5)                       ::   aname
779      INTEGER , DIMENSION(3)                  ::   ddims
780      INTEGER , DIMENSION(jpi, jpj)           ::   data_src
781      REAL(wp), DIMENSION(jpi, jpj)           ::   data_tmp
782      REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::   line2, lines  ! temporary array to read 2 lineumns
783      CHARACTER (len=34)                      ::   lonvar
784      LOGICAL                                 ::   cyclical
785      REAL(wp)                                ::   resid, dlon   ! temporary array to read 2 lineumns
786      INTEGER                                 ::   offset        ! temporary integer
787      !!----------------------------------------------------------------------
788      !
789      IF( nxt_wgt > tot_wgts ) THEN
790        CALL ctl_stop("fld_weights: weights array size exceeded, increase tot_wgts")
791      ENDIF
792      !
793      !! new weights file entry, add in extra information
794      !! a weights file represents a 2D grid of a certain shape, so we assume that the current
795      !! input data file is representative of all other files to be opened and processed with the
796      !! current weights file
797
798      !! open input data file (non-model grid)
799      CALL iom_open( sd%clname, inum, ldiof =  LEN(TRIM(sd%wgtname)) > 0 )
800
801      !! get dimensions
802      id = iom_varid( inum, sd%clvar, ddims )
803
804      !! check for an east-west cyclic grid
805      !! try to guess name of longitude variable
806
807      lonvar = 'nav_lon'
808      id = iom_varid(inum, TRIM(lonvar), ldstop=.FALSE.)
809      IF( id <= 0 ) THEN
810         lonvar = 'lon'
811         id = iom_varid(inum, TRIM(lonvar), ldstop=.FALSE.)
812      ENDIF
813
814      offset = -1
815      cyclical = .FALSE.
816      IF( id > 0 ) THEN
817         !! found a longitude variable
818         !! now going to assume that grid is regular so we can read a single row
819
820         !! because input array is 2d, have to present iom with 2d array even though we only need 1d slice
821         !! worse, we cant pass line2(:,1) to iom_get since this is treated as a 1d array which doesnt match input file
822         ALLOCATE( lines(ddims(1),2) )
823         CALL iom_get(inum, jpdom_unknown, lonvar, lines(:,:), 1, kstart=(/1,1/), kcount=(/ddims(1),2/) )
824
825         !! find largest grid spacing
826         lines(1:ddims(1)-1,2) = lines(2:ddims(1),1) - lines(1:ddims(1)-1,1)
827         dlon = MAXVAL( lines(1:ddims(1)-1,2) )
828
829         resid = ABS(ABS(lines(ddims(1),1)-lines(1,1))-360.0)
830         IF( resid < rsmall ) THEN
831            !! end rows overlap in longitude
832            offset = 0
833            cyclical = .TRUE.
834         ELSEIF( resid < 2.0*dlon ) THEN
835            !! also call it cyclic if difference between end points is less than twice dlon from 360
836            offset = 1
837            cyclical = .TRUE.
838         ENDIF
839
840         DEALLOCATE( lines )
841
842      ELSE
843         !! guessing failed
844         !! read in first and last columns of data variable
845         !! since we dont know the name of the longitude variable (or even if there is one)
846         !! we assume that if these two columns are equal, file is cyclic east-west
847
848         !! because input array is 2d, have to present iom with 2d array even though we only need 1d slice
849         !! worse, we cant pass line2(1,:) to iom_get since this is treated as a 1d array which doesnt match input file
850         ALLOCATE( lines(2,ddims(2)), line2(2,ddims(2)) )
851         CALL iom_get(inum, jpdom_unknown, sd%clvar, line2(:,:), 1, kstart=(/1,1/), kcount=(/2,ddims(2)/) )
852         lines(2,:) = line2(1,:)
853
854         CALL iom_get(inum, jpdom_unknown, sd%clvar, line2(:,:), 1, kstart=(/ddims(1)-1,1/), kcount=(/2,ddims(2)/) )
855         lines(1,:) = line2(2,:)
856
857         resid = SUM( ABS(lines(1,:) - lines(2,:)) )
858         IF( resid < ddims(2)*rsmall ) THEN
859            offset = 0
860            cyclical = .TRUE.
861         ENDIF
862
863         DEALLOCATE( lines, line2 )
864      ENDIF
865
866      !! close it
867      CALL iom_close( inum )
868
869      !! now open the weights file
870
871      CALL iom_open ( sd%wgtname, inum )   ! interpolation weights
872      IF ( inum > 0 ) THEN
873
874         ref_wgts(nxt_wgt)%ddims(1) = ddims(1)
875         ref_wgts(nxt_wgt)%ddims(2) = ddims(2)
876         ref_wgts(nxt_wgt)%wgtname = sd%wgtname
877         ref_wgts(nxt_wgt)%offset = -1
878         ref_wgts(nxt_wgt)%cyclic = .FALSE.
879         IF( cyclical ) THEN
880            ref_wgts(nxt_wgt)%offset = offset
881            ref_wgts(nxt_wgt)%cyclic = .TRUE.
882         ENDIF
883         ref_wgts(nxt_wgt)%nestid = 0
884#if defined key_agrif
885         ref_wgts(nxt_wgt)%nestid = Agrif_Fixed()
886#endif
887         !! weights file is stored as a set of weights (wgt01->wgt04 or wgt01->wgt16)
888         !! for each weight wgtNN there is an integer array srcNN which gives the point in
889         !! the input data grid which is to be multiplied by the weight
890         !! they are both arrays on the model grid so the result of the multiplication is
891         !! added into an output array on the model grid as a running sum
892
893         !! two possible cases: bilinear (4 weights) or bicubic (16 weights)
894         id = iom_varid(inum, 'src05', ldstop=.FALSE.)
895         IF( id <= 0) THEN
896            ref_wgts(nxt_wgt)%numwgt = 4
897         ELSE
898            ref_wgts(nxt_wgt)%numwgt = 16
899         ENDIF
900
901         ALLOCATE( ref_wgts(nxt_wgt)%data_jpi(jpi,jpj,4) )
902         ALLOCATE( ref_wgts(nxt_wgt)%data_jpj(jpi,jpj,4) )
903         ALLOCATE( ref_wgts(nxt_wgt)%data_wgt(jpi,jpj,ref_wgts(nxt_wgt)%numwgt) )
904
905         DO jn = 1,4
906            aname = ' '
907            WRITE(aname,'(a3,i2.2)') 'src',jn
908            data_tmp(:,:) = 0
909            CALL iom_get ( inum, jpdom_unknown, aname, data_tmp(1:nlci,1:nlcj), &
910                           kstart=(/nimpp,njmpp/), kcount=(/nlci,nlcj/) )
911            data_src(:,:) = INT(data_tmp(:,:))
912            ref_wgts(nxt_wgt)%data_jpj(:,:,jn) = 1 + (data_src(:,:)-1) / ref_wgts(nxt_wgt)%ddims(1)
913            ref_wgts(nxt_wgt)%data_jpi(:,:,jn) = data_src(:,:) - ref_wgts(nxt_wgt)%ddims(1)*(ref_wgts(nxt_wgt)%data_jpj(:,:,jn)-1)
914         END DO
915
916         DO jn = 1, ref_wgts(nxt_wgt)%numwgt
917            aname = ' '
918            WRITE(aname,'(a3,i2.2)') 'wgt',jn
919            ref_wgts(nxt_wgt)%data_wgt(1:nlci,1:nlcj,jn) = 0.0
920            CALL iom_get ( inum, jpdom_unknown, aname, ref_wgts(nxt_wgt)%data_wgt(1:nlci,1:nlcj,jn), &
921                           kstart=(/nimpp,njmpp/), kcount=(/nlci,nlcj/) )
922         END DO
923         CALL iom_close (inum)
924 
925         ! find min and max indices in grid
926         ref_wgts(nxt_wgt)%botleft(1) = MINVAL(ref_wgts(nxt_wgt)%data_jpi(1:nlci,1:nlcj,:))
927         ref_wgts(nxt_wgt)%botleft(2) = MINVAL(ref_wgts(nxt_wgt)%data_jpj(1:nlci,1:nlcj,:))
928         ref_wgts(nxt_wgt)%topright(1) = MAXVAL(ref_wgts(nxt_wgt)%data_jpi(1:nlci,1:nlcj,:))
929         ref_wgts(nxt_wgt)%topright(2) = MAXVAL(ref_wgts(nxt_wgt)%data_jpj(1:nlci,1:nlcj,:))
930
931         ! and therefore dimensions of the input box
932         ref_wgts(nxt_wgt)%jpiwgt = ref_wgts(nxt_wgt)%topright(1) - ref_wgts(nxt_wgt)%botleft(1) + 1
933         ref_wgts(nxt_wgt)%jpjwgt = ref_wgts(nxt_wgt)%topright(2) - ref_wgts(nxt_wgt)%botleft(2) + 1
934
935         ! shift indexing of source grid
936         ref_wgts(nxt_wgt)%data_jpi(:,:,:) = ref_wgts(nxt_wgt)%data_jpi(:,:,:) - ref_wgts(nxt_wgt)%botleft(1) + 1
937         ref_wgts(nxt_wgt)%data_jpj(:,:,:) = ref_wgts(nxt_wgt)%data_jpj(:,:,:) - ref_wgts(nxt_wgt)%botleft(2) + 1
938
939         ! create input grid, give it a halo to allow gradient calculations
940         ! SA: +3 stencil is a patch to avoid out-of-bound computation in some configuration.
941         ! a more robust solution will be given in next release
942         ipk =  SIZE(sd%fnow,3)
943         ALLOCATE( ref_wgts(nxt_wgt)%fly_dta(ref_wgts(nxt_wgt)%jpiwgt+3, ref_wgts(nxt_wgt)%jpjwgt+3 ,ipk) )
944         IF( ref_wgts(nxt_wgt)%cyclic ) ALLOCATE( ref_wgts(nxt_wgt)%col2(2,ref_wgts(nxt_wgt)%jpjwgt+3,ipk) )
945
946         nxt_wgt = nxt_wgt + 1
947
948      ELSE
949         CALL ctl_stop( '    fld_weight : unable to read the file ' )
950      ENDIF
951
952   END SUBROUTINE fld_weight
953
954   SUBROUTINE fld_interp(num, clvar, kw, kk, dta, nrec)
955      !!---------------------------------------------------------------------
956      !!                    ***  ROUTINE fld_interp  ***
957      !!
958      !! ** Purpose :   apply weights to input gridded data to create data
959      !!                on model grid
960      !!
961      !! ** Method  :   
962      !!----------------------------------------------------------------------
963      INTEGER,          INTENT(in)                        ::   num                 ! stream number
964      CHARACTER(LEN=*), INTENT(in)                        ::   clvar               ! variable name
965      INTEGER,          INTENT(in)                        ::   kw                  ! weights number
966      INTEGER,          INTENT(in)                        ::   kk                  ! vertical dimension of kk
967      REAL(wp),         INTENT(inout), DIMENSION(jpi,jpj,kk) ::   dta              ! output field on model grid
968      INTEGER,          INTENT(in)                        ::   nrec                ! record number to read (ie time slice)
969      !!
970      INTEGER, DIMENSION(3)                               ::   rec1,recn           ! temporary arrays for start and length
971      INTEGER                                             ::  jk, jn, jm           ! loop counters
972      INTEGER                                             ::  ni, nj               ! lengths
973      INTEGER                                             ::  jpimin,jpiwid        ! temporary indices
974      INTEGER                                             ::  jpjmin,jpjwid        ! temporary indices
975      INTEGER                                             ::  jpi1,jpi2,jpj1,jpj2  ! temporary indices
976      !!----------------------------------------------------------------------
977      !
978
979      !! for weighted interpolation we have weights at four corners of a box surrounding
980      !! a model grid point, each weight is multiplied by a grid value (bilinear case)
981      !! or by a grid value and gradients at the corner point (bicubic case)
982      !! so we need to have a 4 by 4 subgrid surrounding each model point to cover both cases
983
984      !! sub grid where we already have weights
985      jpimin = ref_wgts(kw)%botleft(1)
986      jpjmin = ref_wgts(kw)%botleft(2)
987      jpiwid = ref_wgts(kw)%jpiwgt
988      jpjwid = ref_wgts(kw)%jpjwgt
989
990      !! what we need to read into sub grid in order to calculate gradients
991      rec1(1) = MAX( jpimin-1, 1 )
992      rec1(2) = MAX( jpjmin-1, 1 )
993      rec1(3) = 1
994      recn(1) = MIN( jpiwid+2, ref_wgts(kw)%ddims(1)-rec1(1)+1 )
995      recn(2) = MIN( jpjwid+2, ref_wgts(kw)%ddims(2)-rec1(2)+1 )
996      recn(3) = kk
997
998      !! where we need to read it to
999      jpi1 = 2 + rec1(1) - jpimin
1000      jpj1 = 2 + rec1(2) - jpjmin
1001      jpi2 = jpi1 + recn(1) - 1
1002      jpj2 = jpj1 + recn(2) - 1
1003
1004      ref_wgts(kw)%fly_dta(:,:,:) = 0.0
1005      SELECT CASE( SIZE(ref_wgts(kw)%fly_dta(jpi1:jpi2,jpj1:jpj2,:),3) )
1006      CASE(1)
1007           CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%fly_dta(jpi1:jpi2,jpj1:jpj2,1), nrec, rec1, recn)
1008      CASE(jpk) 
1009           CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%fly_dta(jpi1:jpi2,jpj1:jpj2,:), nrec, rec1, recn)
1010      END SELECT 
1011
1012      !! first four weights common to both bilinear and bicubic
1013      !! note that we have to offset by 1 into fly_dta array because of halo
1014      dta(:,:,:) = 0.0
1015      DO jk = 1,4
1016        DO jn = 1, nlcj
1017          DO jm = 1,nlci
1018            ni = ref_wgts(kw)%data_jpi(jm,jn,jk)
1019            nj = ref_wgts(kw)%data_jpj(jm,jn,jk)
1020            dta(jm,jn,:) = dta(jm,jn,:) + ref_wgts(kw)%data_wgt(jm,jn,jk) * ref_wgts(kw)%fly_dta(ni+1,nj+1,jk)
1021          END DO
1022        END DO
1023      END DO
1024
1025      IF (ref_wgts(kw)%numwgt .EQ. 16) THEN
1026
1027        !! fix up halo points that we couldnt read from file
1028        IF( jpi1 == 2 ) THEN
1029           ref_wgts(kw)%fly_dta(jpi1-1,:,:) = ref_wgts(kw)%fly_dta(jpi1,:,:)
1030        ENDIF
1031        IF( jpi2 + jpimin - 1 == ref_wgts(kw)%ddims(1)+1 ) THEN
1032           ref_wgts(kw)%fly_dta(jpi2+1,:,:) = ref_wgts(kw)%fly_dta(jpi2,:,:)
1033        ENDIF
1034        IF( jpj1 == 2 ) THEN
1035           ref_wgts(kw)%fly_dta(:,jpj1-1,:) = ref_wgts(kw)%fly_dta(:,jpj1,:)
1036        ENDIF
1037        IF( jpj2 + jpjmin - 1 == ref_wgts(kw)%ddims(2)+1 .AND. jpj2 .lt. jpjwid+2 ) THEN
1038           ref_wgts(kw)%fly_dta(:,jpj2+1,:) = 2.0*ref_wgts(kw)%fly_dta(:,jpj2,:) - ref_wgts(kw)%fly_dta(:,jpj2-1,:)
1039        ENDIF
1040
1041        !! if data grid is cyclic we can do better on east-west edges
1042        !! but have to allow for whether first and last columns are coincident
1043        IF( ref_wgts(kw)%cyclic ) THEN
1044           rec1(2) = MAX( jpjmin-1, 1 )
1045           recn(1) = 2
1046           recn(2) = MIN( jpjwid+2, ref_wgts(kw)%ddims(2)-rec1(2)+1 )
1047           jpj1 = 2 + rec1(2) - jpjmin
1048           jpj2 = jpj1 + recn(2) - 1
1049           IF( jpi1 == 2 ) THEN
1050              rec1(1) = ref_wgts(kw)%ddims(1) - 1
1051              SELECT CASE( SIZE( ref_wgts(kw)%col2(:,jpj1:jpj2,:),3) )
1052              CASE(1)
1053                   CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col2(:,jpj1:jpj2,1), nrec, rec1, recn)
1054              CASE(jpk)         
1055                   CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col2(:,jpj1:jpj2,:), nrec, rec1, recn)
1056              END SELECT     
1057              ref_wgts(kw)%fly_dta(jpi1-1,jpj1:jpj2,:) = ref_wgts(kw)%col2(ref_wgts(kw)%offset+1,jpj1:jpj2,:)
1058           ENDIF
1059           IF( jpi2 + jpimin - 1 == ref_wgts(kw)%ddims(1)+1 ) THEN
1060              rec1(1) = 1
1061              SELECT CASE( SIZE( ref_wgts(kw)%col2(:,jpj1:jpj2,:),3) )
1062              CASE(1)
1063                   CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col2(:,jpj1:jpj2,1), nrec, rec1, recn)
1064              CASE(jpk)
1065                   CALL iom_get( num, jpdom_unknown, clvar, ref_wgts(kw)%col2(:,jpj1:jpj2,:), nrec, rec1, recn)
1066              END SELECT
1067              ref_wgts(kw)%fly_dta(jpi2+1,jpj1:jpj2,:) = ref_wgts(kw)%col2(2-ref_wgts(kw)%offset,jpj1:jpj2,:)
1068           ENDIF
1069        ENDIF
1070
1071        ! gradient in the i direction
1072        DO jk = 1,4
1073          DO jn = 1, nlcj
1074            DO jm = 1,nlci
1075              ni = ref_wgts(kw)%data_jpi(jm,jn,jk)
1076              nj = ref_wgts(kw)%data_jpj(jm,jn,jk)
1077              dta(jm,jn,:) = dta(jm,jn,:) + ref_wgts(kw)%data_wgt(jm,jn,jk+4) * 0.5 *         &
1078                               (ref_wgts(kw)%fly_dta(ni+2,nj+1,:) - ref_wgts(kw)%fly_dta(ni,nj+1,:))
1079            END DO
1080          END DO
1081        END DO
1082
1083        ! gradient in the j direction
1084        DO jk = 1,4
1085          DO jn = 1, nlcj
1086            DO jm = 1,nlci
1087              ni = ref_wgts(kw)%data_jpi(jm,jn,jk)
1088              nj = ref_wgts(kw)%data_jpj(jm,jn,jk)
1089              dta(jm,jn,:) = dta(jm,jn,:) + ref_wgts(kw)%data_wgt(jm,jn,jk+8) * 0.5 *         &
1090                               (ref_wgts(kw)%fly_dta(ni+1,nj+2,:) - ref_wgts(kw)%fly_dta(ni+1,nj,:))
1091            END DO
1092          END DO
1093        END DO
1094
1095        ! gradient in the ij direction
1096        DO jk = 1,4
1097          DO jn = 1, jpj
1098            DO jm = 1,jpi
1099              ni = ref_wgts(kw)%data_jpi(jm,jn,jk)
1100              nj = ref_wgts(kw)%data_jpj(jm,jn,jk)
1101              dta(jm,jn,:) = dta(jm,jn,:) + ref_wgts(kw)%data_wgt(jm,jn,jk+12) * 0.25 * ( &
1102                               (ref_wgts(kw)%fly_dta(ni+2,nj+2,:) - ref_wgts(kw)%fly_dta(ni  ,nj+2,:)) -   &
1103                               (ref_wgts(kw)%fly_dta(ni+2,nj  ,:) - ref_wgts(kw)%fly_dta(ni  ,nj  ,:)))
1104            END DO
1105          END DO
1106        END DO
1107
1108      END IF
1109
1110   END SUBROUTINE fld_interp
1111 
1112END MODULE fldread
Note: See TracBrowser for help on using the repository browser.