source: tags/ORCHIDEE_4_1/ORCHIDEE/src_driver/readdim2.f90 @ 7852

Last change on this file since 7852 was 7750, checked in by josefine.ghattas, 22 months ago

Bug correction for use of daily forcing, see ticket #861

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 109.0 KB
Line 
1!  ==============================================================================================================================\n
2!  MODULE       : readdim2
3!
4!  CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6!  LICENCE      : IPSL (2006)
7!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        This module contains subroutines for reading the forcing file for the dim2_driver.
10!!
11!!
12!!\n DESCRIPTION  : This module contains subroutines for reading the forcing file for the dim2_driver.
13!!                  Following subroutines are public and called from dim2_driver :
14!!                    - forcing_info : Open the forcing file and return information about the grid in the forcing file.
15!!                                     Prepare for a zoom if needed.
16!!                                     Initialization of parallelization related to the grid.
17!!                    - forcing_read : Return the forcing data for the current time step of the model. The forcing file will
18!!                                     be read if it has not already been done for the current time-step in the forcing file.
19!!                    - forcing_grid : Calculate the longitudes and latitudes of the model grid.
20!!
21!! RECENT CHANGE(S): None
22!!
23!! REFERENCE(S) : None
24!!   
25!! SVN     :
26!! $HeadURL$
27!! $Date$
28!! $Revision$
29!! \n
30!_ ================================================================================================================================
31
32MODULE readdim2
33
34   USE ioipsl_para
35   USE weather
36   USE TIMER
37   USE constantes
38   USE time
39   USE solar
40   USE grid
41   USE mod_orchidee_para
42
43   IMPLICIT NONE
44
45   PRIVATE
46   PUBLIC  :: forcing_read, forcing_info, forcing_grid
47
48   INTEGER, SAVE                            :: iim_full, jjm_full, llm_full, ttm_full
49   INTEGER, SAVE                            :: iim_zoom, jjm_zoom
50   INTEGER, SAVE                            :: iim_g_begin,jjm_g_begin,iim_g_end,jjm_g_end
51   REAL, SAVE, ALLOCATABLE, DIMENSION(:,:)  :: data_full, lon_full, lat_full
52   REAL, SAVE, ALLOCATABLE, DIMENSION(:)    :: lev_full
53   INTEGER, SAVE, ALLOCATABLE, DIMENSION(:) :: itau, i_index, j_index,j_index_g
54   INTEGER, SAVE                            :: i_test, j_test
55   INTEGER, SAVE                            :: printlev_loc   !! Local printlev
56   LOGICAL, SAVE                            :: allow_weathergen, interpol, daily_interpol
57   LOGICAL, SAVE, PUBLIC                    :: weathergen, is_watchout
58   REAL, SAVE                               :: merid_res, zonal_res
59   LOGICAL, SAVE                            :: have_zaxis=.FALSE.
60!-
61!- Heigh controls and data
62!-
63   LOGICAL, SAVE                            :: zfixed, zsigma, zhybrid, zlevels, zheight 
64   LOGICAL, SAVE                            :: zsamelev_uv 
65   REAL, SAVE                               :: zlev_fixed, zlevuv_fixed 
66   REAL, SAVE                               :: zhybrid_a, zhybrid_b 
67   REAL, SAVE                               :: zhybriduv_a, zhybriduv_b 
68   ! Trying to find a way that calculates solar angle for driver files
69   ! with high resolution (short timesteps).  3600.0 is what the value
70   ! originally was, but I do not know where that came from.  I tried
71   ! 1799.0 for FLUXNET forcing files, which results in a solar angle,
72   ! but it also caused some problems with SWDown values.  Keeping this
73   ! at 3600 now, and moving it as a parameter up here to make it clear.
74   REAL, PARAMETER                          :: dt_cutoff=3600.0
75
76CONTAINS
77
78!! ==============================================================================================================================\n
79!! SUBROUTINE   : forcing_info
80!!
81!>\BRIEF        Open the forcing file and return information about the grid in the forcing file.
82!!
83!!\n DESCRIPTION : This subroutine will get all the information from the forcing file and prepare for the zoom if needed.
84!!                 It returns to the caller the sizes of the data it will receive at the forcing_read call.
85!!                 This is important so that the caller can allocate the right space.
86!!
87!!
88!! RECENT CHANGE(S): None
89!!
90!! MAIN OUTPUT VARIABLE(S):
91!!
92!! REFERENCE(S) :
93!!
94!_ ================================================================================================================================
95  SUBROUTINE forcing_info(filename, iim, jjm, llm, tm, date0, dt_force, force_id)
96
97    IMPLICIT NONE
98
99!! 0.1 Input variables
100    CHARACTER(LEN=*), INTENT(in) :: filename     !! Name of the file to be opened
101
102!! 0.2 Output variables
103    INTEGER, INTENT(out)         :: iim          !! Size in x of the forcing data
104    INTEGER, INTENT(out)         :: jjm          !! Size in y of the forcing data
105    INTEGER, INTENT(out)         :: llm          !! Number of levels in the forcing data (not yet used)
106    INTEGER, INTENT(out)         :: tm           !! Time dimension of the forcing
107    REAL, INTENT(out)            :: date0        !! The date at which the forcing file starts (julian days)
108    REAL, INTENT(out)            :: dt_force     !! Time-step of the forcing file in seconds
109    INTEGER, INTENT(out)         :: force_id     !! Id of the forcing file
110
111!! 0.3 Local variables
112    CHARACTER(LEN=20)                  :: calendar_str
113    CHARACTER(LEN=200)                 :: printstr       !! temporary character string to contain error message
114    REAL                               :: juld_1, juld_2
115    REAL, ALLOCATABLE, DIMENSION(:,:)  :: fcontfrac
116    REAL, ALLOCATABLE, DIMENSION(:,:)  :: qair
117    LOGICAL                            :: contfrac_exists=.FALSE.
118    INTEGER                            :: NbPoint
119    INTEGER                            :: i_test,j_test
120    INTEGER                            :: i,j,ind,ttm_part
121    INTEGER, ALLOCATABLE, DIMENSION(:) :: index_l
122    REAL, ALLOCATABLE, DIMENSION(:,:)  :: lon, lat
123    REAL, ALLOCATABLE, DIMENSION(:)    :: lev, levuv
124
125    !-
126    CALL flininfo(filename,  iim_full, jjm_full, llm_full, ttm_full, force_id)
127    !-
128    IF ( printlev_loc>=3 ) WRITE(numout,*) 'forcing_info : Details from forcing file :', &
129         iim_full, jjm_full, llm_full, ttm_full
130    !-
131    IF ( llm_full < 1 ) THEN
132       have_zaxis = .FALSE.
133    ELSE
134       have_zaxis = .TRUE.
135    ENDIF
136    IF ( printlev_loc>=3 ) WRITE(numout,*) 'have_zaxis : ', llm_full, have_zaxis
137    !-
138    ttm_part = 2
139    ALLOCATE(itau(ttm_part))
140    ALLOCATE(data_full(iim_full, jjm_full),lon_full(iim_full, jjm_full),&
141         & lat_full(iim_full, jjm_full))
142    ALLOCATE(lev_full(llm_full))
143    !-
144    lev_full(:) = zero
145    !-
146    dt_force=zero
147    CALL flinopen &
148         &  (filename, .FALSE., iim_full, jjm_full, llm_full, lon_full, lat_full, &
149         &   lev_full, ttm_part, itau, date0, dt_force, force_id)
150    IF ( dt_force == zero ) THEN
151       dt_force = itau(2) - itau(1) 
152       itau(:) = itau(:) / dt_force
153    ENDIF
154    !  WRITE(numout,*) "forcing_info : Forcing time step out of flinopen : ",dt_force
155    !-
156    !- What are the alowed options for the temportal interpolation
157    !-
158    !Config Key   = ALLOW_WEATHERGEN
159    !Config Desc  = Allow weather generator to create data
160    !Config If    = [-]
161    !Config Def   = n
162    !Config Help  = This flag allows the forcing-reader to generate
163    !Config         synthetic data if the data in the file is too sparse
164    !Config         and the temporal resolution would not be enough to
165    !Config         run the model.
166    !Config Units = [FLAG]
167    !-
168    allow_weathergen = .FALSE.
169    CALL getin_p('ALLOW_WEATHERGEN',allow_weathergen)
170    !-
171    !- The calendar was set by the forcing file. If no "calendar" attribute was
172    !- found then it is assumed to be gregorian,
173    !MM => FALSE !! it is NOT assumed anything !
174    !- else it is what ever is written in this attribute.
175    !-
176    CALL ioget_calendar(calendar_str)
177    i=INDEX(calendar_str,ACHAR(0))
178    IF ( i > 0 ) THEN
179       calendar_str(i:20)=' '
180    ENDIF
181    !  WRITE(numout,*) "forcing_info : Calendar used : ",calendar_str
182    IF ( calendar_str == 'XXXX' ) THEN
183       IF (printlev_loc >= 1) WRITE(numout,*) "forcing_info : The calendar was not found in the forcing file."
184       IF (allow_weathergen) THEN
185          ! Then change the calendar
186          CALL ioconf_calendar("noleap") 
187       ELSE
188          IF ( printlev_loc>=1 ) WRITE(numout,*) "forcing_info : We will force it to gregorian by default."
189          CALL ioconf_calendar("gregorian") !! = 365.2425 ; "noleap" = 365.0; "360d"; "julian"=365.25
190       ENDIF
191    ENDIF
192    IF (printlev_loc >= 1) WRITE(numout,*) "readdim2 : Calendar used by the model : ",calendar_str
193    IF (ttm_full .GE. 2) THEN
194       juld_1 = itau2date(itau(1), date0, dt_force)
195       juld_2 = itau2date(itau(2), date0, dt_force)
196    ELSE
197       juld_1 = 0
198       juld_2 = 0
199       CALL ipslerr_p ( 3, 'forcing_info','What is that only one time step in the forcing file ?', &
200            &         ' That can not be right.','verify forcing file.')
201    ENDIF
202    !-
203    !- Initialize one_year / one_day
204    CALL ioget_calendar (one_year, one_day)
205    !-
206    !- What is the distance between the two first states. From this we will deduce what is
207    !- to be done.
208    weathergen = .FALSE.
209    interpol = .FALSE.
210    daily_interpol = .FALSE.
211    is_watchout = .FALSE.
212    !-
213    IF ( ABS(ABS(juld_2-juld_1)-30.) .LE. 2.) THEN
214       IF ( allow_weathergen ) THEN
215          weathergen = .TRUE.
216          IF (printlev_loc >= 1) WRITE(numout,*) 'Using weather generator.' 
217       ELSE
218          CALL ipslerr_p ( 3, 'forcing_info', &
219               &         'This seems to be a monthly file.', &
220               &         'We should use a weather generator with this file.', &
221               &         'This should be allowed in the run.def')
222       ENDIF
223    ELSEIF (( ABS(juld_1-juld_2) .LE. 1./4.) .OR. ( ABS(juld_1-juld_2) .EQ. 1.)) THEN
224       interpol = .TRUE.
225       IF (printlev_loc >= 1) WRITE(numout,*) 'We will interpolate between the forcing data time steps.' 
226       IF ( ABS(juld_1-juld_2) .EQ. 1.) THEN
227          daily_interpol = .TRUE.
228       ENDIF
229    ELSE
230       ! Using the weather generator with data other than monthly ones probably
231       ! needs some thinking.
232       WRITE(numout,*) 'The time step is not suitable:',ABS(juld_1-juld_2),' days.'
233       CALL ipslerr_p ( 3, 'forcing_info','The time step is not suitable.', &
234            &         '','We cannot do anything with these forcing data.')
235    ENDIF
236    !-
237    !- redefine the forcing time step if the weather generator is activated
238    !-
239    IF ( weathergen ) THEN
240       !Config Key   = DT_WEATHGEN
241       !Config Desc  = Calling frequency of weather generator
242       !Config If    = ALLOW_WEATHERGEN
243       !Config Def   = 1800.
244       !Config Help  = Determines how often the weather generator
245       !Config         is called (time step in s). Should be equal
246       !Config         to or larger than Sechiba's time step (say,
247       !Config         up to 6 times Sechiba's time step or so).
248       !Config Units = [seconds]
249       dt_force = 1800.
250       CALL getin_p('DT_WEATHGEN',dt_force)
251    ENDIF
252    !-
253    !- Define the zoom
254    !-
255    !Config Key   = LIMIT_WEST
256    !Config Desc  = Western limit of region
257    !Config If    = [-]
258    !Config Def   = -180.
259    !Config Help  = Western limit of the region we are
260    !Config         interested in. Between -180 and +180 degrees
261    !Config         The model will use the smalest regions from
262    !Config         region specified here and the one of the forcing file.
263    !Config Units = [Degrees]
264    !-
265    limit_west = -180.
266    CALL getin_p('LIMIT_WEST',limit_west)
267    !-
268    !Config Key   = LIMIT_EAST
269    !Config Desc  = Eastern limit of region
270    !Config If    = [-]
271    !Config Def   = 180.
272    !Config Help  = Eastern limit of the region we are
273    !Config         interested in. Between -180 and +180 degrees
274    !Config         The model will use the smalest regions from
275    !Config         region specified here and the one of the forcing file.
276    !Config Units = [Degrees]
277    !-
278    limit_east = 180.
279    CALL getin_p('LIMIT_EAST',limit_east)
280    !-
281    !Config Key   = LIMIT_NORTH
282    !Config Desc  = Northern limit of region
283    !Config If    = [-]
284    !Config Def   = 90.
285    !Config Help  = Northern limit of the region we are
286    !Config         interested in. Between +90 and -90 degrees
287    !Config         The model will use the smalest regions from
288    !Config         region specified here and the one of the forcing file.
289    !Config Units = [Degrees]
290    !-
291    limit_north = 90.
292    CALL getin_p('LIMIT_NORTH',limit_north)
293    !-
294    !Config Key   = LIMIT_SOUTH
295    !Config Desc  = Southern limit of region
296    !Config If    = [-]
297    !Config Def   = -90.
298    !Config Help  = Southern limit of the region we are
299    !Config         interested in. Between 90 and -90 degrees
300    !Config         The model will use the smalest regions from
301    !Config         region specified here and the one of the forcing file.
302    !Config Units = [Degrees]
303    !-
304    limit_south = -90.
305    CALL getin_p('LIMIT_SOUTH',limit_south)
306    !-
307    !- Calculate domain size
308    !-
309
310    IF ( interpol ) THEN
311       !-
312       !- If we use temporal interpolation, then we cannot change the resolution (yet?)
313       !-
314       ALLOCATE(i_index(iim_full), j_index(jjm_full),j_index_g(jjm_full))
315       IF (is_root_prc) THEN
316
317          CALL domain_size (limit_west, limit_east, limit_north, limit_south,&
318               &         iim_full, jjm_full, lon_full, lat_full, iim_zoom, jjm_zoom,&
319               &         i_index, j_index_g)
320
321          j_index(:)=j_index_g(:)
322
323          ALLOCATE(qair(iim_full,jjm_full))
324          CALL flinget_buffer (force_id,'Qair',iim_full, jjm_full, 1, ttm_full,  1, 1, data_full)
325          CALL forcing_zoom(data_full, qair)
326
327          ALLOCATE(fcontfrac(iim_zoom,jjm_zoom))
328          CALL flinquery_var(force_id, 'contfrac', contfrac_exists)
329          IF ( contfrac_exists ) THEN
330             IF (printlev_loc >= 1) WRITE(numout,*) "contfrac exist in the forcing file."
331             CALL flinget_buffer (force_id,'contfrac',iim_full, jjm_full, 1, ttm_full,  1, 1, data_full)
332             CALL forcing_zoom(data_full, fcontfrac)
333             IF (printlev_loc >= 2) WRITE(numout,*) "fcontfrac min/max :", &
334                  MINVAL(fcontfrac(1:iim_zoom,1:jjm_zoom)),MAXVAL(fcontfrac(1:iim_zoom,1:jjm_zoom))
335          ELSE
336             fcontfrac(:,:)=1.
337          ENDIF
338
339          DO i=1,iim_zoom
340             DO j=1,jjm_zoom
341                IF ( fcontfrac(i,j) <= EPSILON(1.) ) THEN
342                   qair(i,j) = 999999.
343                ENDIF
344             ENDDO
345          ENDDO
346
347          DEALLOCATE(fcontfrac)
348
349          ALLOCATE(index_l(iim_zoom*jjm_zoom))
350          !- In this point is returning the global NbPoint with the global index
351          CALL forcing_landind(iim_zoom,jjm_zoom,qair,NbPoint,index_l,i_test,j_test)
352          !
353          ! Work out the vertical layers to be used
354          !
355          CALL forcing_vertical_ioipsl(force_id) 
356       ELSE
357          ALLOCATE(index_l(1))
358       ENDIF
359
360       ! Initiate global grid and parallelism
361       CALL bcast(iim_zoom)
362       CALL bcast(jjm_zoom)
363       CALL bcast(NbPoint)
364       CALL grid_set_glo(iim_zoom,jjm_zoom,NbPoint)
365       CALL grid_allocate_glo(4)
366
367       ! Check consistency in the number of mpi processors and the number of land points
368       ! in order to prevent an exception 
369       IF (NbPoint < mpi_size) THEN
370          WRITE(printstr,*) 'The number of landpoints found (', NbPoint, &
371               ') is less than the number of processors selected (', mpi_size,')' 
372          CALL ipslerr_p(3, 'forcing_info', 'Wrong parallelization options', &
373               TRIM(printstr), & 
374               'Decrease the number of processors for the current grid') 
375       ENDIF
376       
377       !
378       !- global index index_g is the index_l of root proc
379       IF (is_root_prc) index_g(:)=index_l(1:NbPoint)
380
381       DEALLOCATE(index_l)
382
383       !
384       ! Distribute to all processors the information on the forcing
385       !
386       CALL bcast(index_g)
387       CALL Init_orchidee_data_para_driver(nbp_glo,index_g)
388       CALL init_ioipsl_para
389
390       ! Initialize printlev_loc
391       printlev_loc=get_printlev('readdim2')
392       
393       IF (printlev_loc >= 2) WRITE(numout,*) 'Standard PRINTLEV= ', printlev
394       IF (printlev_loc >= 2) WRITE(numout,*) 'Local PRINTLEV_readdim2= ', printlev_loc
395
396!     CALL Init_writeField_p
397
398       CALL bcast(jjm_zoom)
399       CALL bcast(i_index)
400       CALL bcast(j_index_g)
401       CALL bcast(zfixed) 
402       CALL bcast(zsigma) 
403       CALL bcast(zhybrid) 
404       CALL bcast(zlevels) 
405       CALL bcast(zheight) 
406       CALL bcast(zsamelev_uv) 
407       CALL bcast(zlev_fixed) 
408       CALL bcast(zlevuv_fixed) 
409       CALL bcast(zhybrid_a) 
410       CALL bcast(zhybrid_b) 
411       CALL bcast(zhybriduv_a) 
412       CALL bcast(zhybriduv_b) 
413       ind=0
414       DO j=1,jjm_zoom
415          IF ( (j >= jj_begin) .AND. (j <= jj_end) ) THEN
416             ind=ind+1
417             j_index(ind)=j_index_g(j)
418          ENDIF
419       ENDDO
420
421       jjm_zoom=jj_nb
422       iim_zoom=iim_g
423
424       !-
425       !- If we use the weather generator, then we read zonal and meridional resolutions
426       !- This should be unified one day...
427       !-
428    ELSEIF ( weathergen ) THEN
429       !-
430       !Config Key   = MERID_RES
431       !Config Desc  = North-South Resolution
432       !Config Def   = 2.
433       !Config If    = ALLOW_WEATHERGEN
434       !Config Help  = North-South Resolution of the region we are
435       !Config         interested in.
436       !Config Units = [Degrees]
437       !-
438       merid_res = 2.
439       CALL getin_p('MERID_RES',merid_res)
440       !-
441       !Config Key   = ZONAL_RES
442       !Config Desc  = East-West Resolution
443       !Config Def   = 2.
444       !Config If    = ALLOW_WEATHERGEN
445       !Config Help  = East-West Resolution of the region we are
446       !Config         interested in. In degrees
447       !Config Units = [Degrees]
448       !-
449       zonal_res = 2.
450       CALL getin_p('ZONAL_RES',zonal_res)
451       !-
452       !- Number of time steps is meaningless in this case
453       !-
454       !    ttm_full = HUGE( ttm_full )
455       !MM Number (realistic) of time steps for half hour dt
456       ttm_full = NINT(one_year * 86400. / dt_force)
457       !-
458       IF (is_root_prc) THEN
459
460          !- In this point is returning the global NbPoint with the global index
461          CALL weathgen_domain_size (limit_west,limit_east,limit_north,limit_south, &
462               zonal_res,merid_res,iim_zoom,jjm_zoom)
463          ALLOCATE(index_l(iim_zoom*jjm_zoom))
464       ENDIF
465       CALL bcast(iim_zoom)
466       CALL bcast(jjm_zoom)
467
468       ALLOCATE(lon(iim_zoom,jjm_zoom))
469       ALLOCATE(lat(iim_zoom,jjm_zoom))
470       ALLOCATE(lev(llm_full),levuv(llm_full))
471       
472       ! We need lon and lat now for weathgen_init
473       CALL forcing_grid (iim_zoom,jjm_zoom,llm_full,lon,lat,init_f=.TRUE.)
474       CALL forcing_vertical_ioipsl(-1) 
475
476       IF (is_root_prc) THEN
477          CALL weathgen_init &
478               &        (filename,dt_force,force_id,iim_zoom,jjm_zoom, &
479               &         zonal_res,merid_res,lon,lat,index_l,NbPoint)
480!!$,&
481!!$               &         i_index,j_index_g)
482       ELSE
483          ALLOCATE(index_l(1))
484          index_l(1)=1
485       ENDIF
486
487       CALL bcast(NbPoint)
488       CALL grid_set_glo(iim_zoom,jjm_zoom,NbPoint)
489       CALL grid_allocate_glo(4)
490
491       !
492       !- global index index_g is the index_l of root proc
493       IF (is_root_prc) index_g(:)=index_l(1:NbPoint)
494
495       DEALLOCATE(index_l)
496
497     CALL bcast(index_g)
498     CALL Init_orchidee_data_para_driver(nbp_glo,index_g)
499     CALL init_ioipsl_para
500!     CALL Init_writeField_p
501     CALL bcast(jjm_zoom)
502!!$       CALL bcast(i_index)
503!!$       CALL bcast(j_index_g)
504
505!!$       ind=0
506!!$       DO j=1,jjm_zoom
507!!$          IF ( (j >= jj_begin) .AND. (j <= jj_end) ) THEN
508!!$             ind=ind+1
509!!$             j_index(ind)=j_index_g(j)
510!!$          ENDIF
511!!$       ENDDO
512
513       jjm_zoom=jj_nb
514       iim_zoom=iim_g
515       !
516       CALL weathgen_read_file(force_id,iim_zoom,jjm_zoom)
517
518       !-
519    ELSE
520       !-
521       CALL ipslerr_p(3,'forcing_info','Neither interpolation nor weather generator is specified.','','')
522       !-
523    ENDIF
524    !-
525    !- Transfer the right information to the caller
526    !-
527    iim = iim_zoom
528    jjm = jjm_zoom
529    llm = 1
530    tm = ttm_full
531    !-
532    IF ( printlev_loc>=3 ) WRITE(numout,*) 'forcing_info : end : ', iim,jjm, llm,tm
533    !-
534  END SUBROUTINE forcing_info
535
536
537!! ==============================================================================================================================\n
538!! SUBROUTINE   : forcing_read
539!!
540!>\BRIEF        Return forcing data for the current time step
541!!
542!!\n DESCRIPTION : Return the forcing data for the current time step of the model. The forcing file will
543!!                 be read if it has not already been done for the current time-step in the forcing file.
544!!
545!! RECENT CHANGE(S): None
546!!
547!! MAIN OUTPUT VARIABLE(S):
548!!
549!! REFERENCE(S) :
550!!
551!_ ================================================================================================================================
552SUBROUTINE forcing_read &
553  & (filename, rest_id, lrstread, lrstwrite, &
554  &  itauin, istp, itau_split, split, nb_spread, lwdown_cons, swdown_cons, date0,   &
555  &  dt_force, iim, jjm, lon, lat, zlev, zlevuv, ttm, &
556  &  swdown, coszang, precip, snowf, tair, u, v, qair, pb, lwdown, &
557  &  fcontfrac, fneighbours, fresolution, &
558  &  SWnet, Eair, petAcoef, peqAcoef, petBcoef, peqBcoef, cdrag, ccanopy, &
559  &  kindex, nbindex, force_id)
560
561  IMPLICIT NONE
562
563    !! 0. Variable and parameter declaration
564    !! 0.1 Input variables
565   CHARACTER(LEN=*), INTENT(IN) :: filename   !! name of the file to be opened
566   INTEGER, INTENT(IN) :: force_id            !! FLINCOM file id. It is used to close the file at the end of the run.
567   INTEGER, INTENT(IN) :: rest_id             !! ID of restart file
568   LOGICAL, INTENT(IN) :: lrstread            !! read restart file?
569   LOGICAL, INTENT(IN) :: lrstwrite           !! write restart file?
570   INTEGER, INTENT(IN) :: itauin              !! time step for which we need the data
571   INTEGER, INTENT(IN) :: istp                !! time step for restart file
572   INTEGER, INTENT(IN) :: itau_split          !! Current step between 2 forcing times-step (it decides if it is time to read)
573   INTEGER, INTENT(IN) :: split               !! The number of time steps between two time-steps of the forcing
574   INTEGER, INTENT(IN) :: nb_spread           !! Over how many time steps do we spread the precipitation
575   LOGICAL, INTENT(IN) :: lwdown_cons         !! Flag to conserve lwdown radiation from forcing
576   LOGICAL, INTENT(IN) :: swdown_cons         !! Flag to conserve swdown radiation from forcing
577   REAL, INTENT(IN)    :: date0               !! The date at which the forcing file starts (julian days)
578   REAL, INTENT(IN)    :: dt_force            !! time-step of the forcing file in seconds
579   INTEGER, INTENT(IN) :: iim                 !! Size of the grid in x
580   INTEGER, INTENT(IN) :: jjm                 !! Size of the grid in y
581   INTEGER, INTENT(IN) :: ttm                 !! number of time steps in all in the forcing file
582   REAL,DIMENSION(iim,jjm), INTENT(IN) :: lon !! Longitudes
583   REAL,DIMENSION(iim,jjm), INTENT(IN) :: lat !! Latitudes
584
585    !! 0.2 Output variables
586   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: zlev        !! First Levels if it exists (ie if watchout file)
587   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: zlevuv      !! First Levels of the wind (equal precedent, if it exists)
588   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: swdown      !! Downward solar radiation (W/m^2)
589   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: coszang     !! Cosine of the solar zenith angle (unitless)
590   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: precip      !! Precipitation (Rainfall) (kg/m^2s)
591   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: snowf       !! Snowfall (kg/m^2s)
592   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: tair        !! 1st level (2m ? in off-line) air temperature (K)
593   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: u           !! 1st level (2m/10m ? in off-line) (in theory !) wind speed (m/s)
594   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: v           !! 1st level (2m/10m ? in off-line) (in theory !) wind speed (m/s)
595   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: qair        !! 1st level (2m ? in off-line) humidity (kg/kg)
596   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: pb          !! Surface pressure (Pa)
597   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: lwdown      !! Downward long wave radiation (W/m^2)
598   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: fcontfrac   !! Continental fraction (no unit)
599   REAL,DIMENSION(iim,jjm,2), INTENT(OUT) :: fresolution     !! resolution in x and y dimensions for each points
600   INTEGER,DIMENSION(iim,jjm,8), INTENT(OUT) :: fneighbours  !! land neighbours
601
602   !! From a WATCHOUT file :
603   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: SWnet       !! Net surface short-wave flux
604   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: Eair        !! Air potential energy
605   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: petAcoef    !! Coeficients A from the PBL resolution for T
606   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: peqAcoef    !! Coeficients A from the PBL resolution for q
607   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: petBcoef    !! Coeficients B from the PBL resolution for T
608   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: peqBcoef    !! Coeficients B from the PBL resolution for q
609   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: cdrag       !! Surface drag
610   REAL,DIMENSION(iim,jjm), INTENT(OUT) :: ccanopy     !! CO2 concentration in the canopy
611
612    !! 0.3 Modified variable
613   INTEGER, INTENT(INOUT) :: nbindex                   !! Number of land points
614   INTEGER,DIMENSION(iim*jjm), INTENT(INOUT) :: kindex !! Index of all land-points in the data (used for the gathering)
615
616    !! 0.4 Local variables
617   INTEGER :: ik,i,j
618
619   IF ( interpol ) THEN
620
621     CALL forcing_read_interpol &
622         (filename, itauin, itau_split, split, nb_spread, lwdown_cons, swdown_cons, date0,   &
623          dt_force, iim, jjm, lon, lat, zlev, zlevuv, ttm, &
624          swdown, coszang, precip, snowf, tair, u, v, qair, pb, lwdown, &
625          fcontfrac, fneighbours, fresolution, &
626          SWnet, Eair, petAcoef, peqAcoef, petBcoef, peqBcoef, cdrag, ccanopy, &
627          kindex, nbindex, force_id)
628
629   ELSEIF ( weathergen ) THEN
630
631      IF (lrstread) THEN
632         fcontfrac(:,:) = 1.0
633         IF (printlev_loc >= 2) WRITE(numout,*) 'contfrac : ', MINVAL(fcontfrac), MAXVAL(fcontfrac)
634      ENDIF
635
636      IF ( (itauin == 0).AND.(itau_split == 0) ) THEN
637         ! Initialization of weathgen_main
638         CALL weathgen_main (istp, istp, filename, force_id, iim, jjm, 1, &
639              rest_id, lrstread, lrstwrite, &
640              limit_west, limit_east, limit_north, limit_south, &
641              zonal_res, merid_res, lon, lat, date0, dt_force, &
642              kindex, nbindex, &
643              swdown, precip, snowf, tair, u, v, qair, pb, lwdown)
644      ELSE
645         CALL weathgen_main (itauin, istp, filename, force_id, iim, jjm, 1, &
646              rest_id, lrstread, lrstwrite, &
647              limit_west, limit_east, limit_north, limit_south, &
648              zonal_res, merid_res, lon, lat, date0, dt_force, &
649              kindex, nbindex, &
650              swdown, precip, snowf, tair, u, v, qair, pb, lwdown)
651      ENDIF
652
653      IF ( (itauin == 0).AND.(itau_split == 0) ) THEN
654         !---
655         !--- Allocate grid stuff
656         !---
657         CALL grid_init ( nbindex, 4, regular_lonlat, "ForcingGrid" )
658         !---
659         !--- Compute
660         !---
661         CALL grid_stuff(nbp_glo, iim_g, jjm_g, lon_g, lat_g, index_g)
662         !CALL grid_stuff (nbindex, iim, jjm, lon, lat, kindex)
663         DO ik=1,nbindex
664         
665            j = ((kindex(ik)-1)/iim) + 1
666            i = (kindex(ik) - (j-1)*iim)
667            !-
668            !- Store variable to help describe the grid
669            !- once the points are gathered.
670            !-
671            fneighbours(i,j,:) = neighbours(ik,:)
672            !
673            fresolution(i,j,:) = resolution(ik,:)
674         ENDDO
675
676         ! Initialization of height levels done at first call
677         zlev_fixed = 2.0
678         CALL getin_p('HEIGHT_LEV1', zlev_fixed)
679         
680         zlevuv_fixed = 10.0
681         CALL getin_p('HEIGHT_LEVW', zlevuv_fixed)
682
683      ENDIF
684
685      !- Always set fixed height levels for case weathergen
686      zlev(:,:)=zlev_fixed             !level for t and q
687      zlevuv(:,:)=zlevuv_fixed         !level for u and v
688
689   ELSE
690
691      CALL ipslerr_p(3,'forcing_read','Neither interpolation nor weather generator is specified.','','')
692
693   ENDIF
694
695   IF (.NOT. is_watchout) THEN
696      ! We have to compute Potential air energy
697      WHERE(tair(:,:) < val_exp) 
698         eair(:,:) = cp_air*tair(:,:)+cte_grav*zlev(:,:)
699      ENDWHERE
700   ENDIF
701
702END SUBROUTINE forcing_read
703
704!! ==============================================================================================================================\n
705!! SUBROUTINE   : forcing_read_interpol
706!!
707!>\BRIEF       
708!!
709!!\n DESCRIPTION :
710!!
711!! RECENT CHANGE(S): None
712!!
713!! MAIN OUTPUT VARIABLE(S):
714!!
715!! REFERENCE(S) :
716!!
717!_ ================================================================================================================================
718SUBROUTINE forcing_read_interpol &
719  & (filename, itauin, itau_split, split, nb_spread, lwdown_cons, swdown_cons, date0,   &
720  &  dt_force, iim, jjm, lon, lat, zlev, zlevuv, ttm, swdown, coszang, rainf, snowf, tair, &
721  &  u, v, qair, pb, lwdown, &
722  &  fcontfrac, fneighbours, fresolution, &
723  &  SWnet, Eair, petAcoef, peqAcoef, petBcoef, peqBcoef, cdrag, ccanopy, &
724  &  kindex, nbindex, force_id)
725!---------------------------------------------------------------------
726!- filename   : name of the file to be opened
727!- itauin     : time step for which we need the data
728!- itau_split : Where are we within the splitting
729!-              of the time-steps of the forcing files
730!-              (it decides IF we READ or not)
731!- split      : The number of time steps we do
732!-              between two time-steps of the forcing
733!- nb_spread  : Over how many time steps do we spread the precipitation
734!- lwdown_cons: flag that decides if lwdown radiation should be conserved.
735!- swdown_cons: flag that decides if swdown radiation should be conserved.
736!- date0      : The date at which the forcing file starts (julian days)
737!- dt_force   : time-step of the forcing file in seconds
738!- iim        : Size of the grid in x
739!- jjm        : size of the grid in y
740!- lon        : Longitudes
741!- lat        : Latitudes
742!- zlev       : First Levels if it exists (ie if watchout file)
743!- zlevuv     : First Levels of the wind (equal precedent, if it exists)
744!- ttm        : number of time steps in all in the forcing file
745!- swdown     : Downward solar radiation (W/m^2)
746!- coszang    : Cosine of the solar zenith angle (unitless)
747!- rainf      : Rainfall (kg/m^2s)
748!- snowf      : Snowfall (kg/m^2s)
749!- tair       : 2m air temperature (K)
750!- u and v    : 2m (in theory !) wind speed (m/s)
751!- qair       : 2m humidity (kg/kg)
752!- pb         : Surface pressure (Pa)
753!- lwdown     : Downward long wave radiation (W/m^2)
754!- fcontfrac  : Continental fraction (no unit)
755!- fneighbours: land neighbours
756!- fresolution: resolution in x and y dimensions for each points
757!-
758!- From a WATCHOUT file :
759!- SWnet      : Net surface short-wave flux
760!- Eair       : Air potential energy
761!- petAcoef   : Coeficients A from the PBL resolution for T
762!- peqAcoef   : Coeficients A from the PBL resolution for q
763!- petBcoef   : Coeficients B from the PBL resolution for T
764!- peqBcoef   : Coeficients B from the PBL resolution for q
765!- cdrag      : Surface drag
766!- ccanopy    : CO2 concentration in the canopy
767!-
768!- kindex     : Index of all land-points in the data
769!-              (used for the gathering)
770!- nbindex    : Number of land points
771!- force_id   : FLINCOM file id.
772!-              It is used to close the file at the end of the run.
773!---------------------------------------------------------------------
774   IMPLICIT NONE
775!-
776   INTEGER,PARAMETER :: lm=1
777!-
778!- Input variables
779!-
780   CHARACTER(LEN=*) :: filename
781   INTEGER :: itauin, itau_split, split, nb_spread
782   LOGICAL, INTENT(IN) :: lwdown_cons, swdown_cons
783   REAL    :: date0, dt_force
784   INTEGER :: iim, jjm, ttm
785   REAL,DIMENSION(:,:),INTENT(IN) :: lon, lat   !- LOCAL data array (size=iim,jjm)
786   INTEGER, INTENT(IN) :: force_id
787!-
788!- Output variables
789!-
790   REAL,DIMENSION(:,:),INTENT(OUT) :: zlev, zlevuv, &  !- LOCAL data array (size=iim,jjm)
791  &  swdown, coszang, rainf, snowf, tair, u, v, qair, pb, lwdown, &
792  &  fcontfrac
793   REAL,DIMENSION(:,:,:),INTENT(OUT) :: fresolution    !- LOCAL data array (size=iim,jjm,2)
794   INTEGER,DIMENSION(:,:,:),INTENT(OUT) :: fneighbours !- LOCAL data array (size=iim,jjm,8)
795   ! for watchout files
796   REAL,DIMENSION(:,:),INTENT(OUT) :: &
797  &  SWnet, Eair, petAcoef, peqAcoef, petBcoef, peqBcoef, cdrag, ccanopy
798   INTEGER,DIMENSION(:),INTENT(INOUT) :: kindex    !- LOCAL index of the map
799   INTEGER, INTENT(INOUT) :: nbindex
800!-
801!- Local variables
802!-
803   INTEGER, SAVE :: last_read=0
804   INTEGER, SAVE :: itau_read, itau_read_nm1=0, itau_read_n=0
805   REAL,SAVE,ALLOCATABLE,DIMENSION(:,:) :: &
806  &  zlev_nm1, zlevuv_nm1, swdown_nm1, rainf_nm1, snowf_nm1, tair_nm1, u_nm1, v_nm1, qair_nm1, & 
807  &  pb_nm1, lwdown_nm1, & 
808  &  zlev_n, zlevuv_n, swdown_n, rainf_n, snowf_n, tair_n, u_n, v_n, qair_n, &
809  &  pb_n, lwdown_n, mean_coszang
810
811   REAL,SAVE,ALLOCATABLE,DIMENSION(:,:) :: &
812  &  startday_n, startday_nm1, daylength_n, daylength_nm1, tmax_n, tmax_nm1, tmin_nm1, tmin_nm2, tmin_n,   &
813  &  qsatta, qsattmin_n, qsattmin_nm1, qmin_n, qmin_nm1, qmax_n, qmax_nm1, qsa
814   REAL,SAVE    :: hour
815
816!  just for grid stuff if the forcing file is a watchout file
817   REAL, ALLOCATABLE, DIMENSION(:,:) :: tmpdata
818   ! variables to be read in watchout files
819   REAL,SAVE,ALLOCATABLE,DIMENSION(:,:) :: &
820  &  SWnet_nm1, Eair_nm1, petAcoef_nm1, peqAcoef_nm1, petBcoef_nm1, peqBcoef_nm1, cdrag_nm1, ccanopy_nm1, &
821  &  SWnet_n, Eair_n, petAcoef_n, peqAcoef_n, petBcoef_n, peqBcoef_n, cdrag_n, ccanopy_n
822   REAL, SAVE :: julian_for ! Date of the forcing to be read
823   REAL :: julian, ss, rw
824!jur,
825   REAL, SAVE :: julian0    ! First day of this year
826   INTEGER :: yy, mm, dd, is, i, j, ik
827   REAL(r_std), DIMENSION(2) :: min_resol, max_resol
828   REAL(r_std), DIMENSION(1,1) :: lon_temp  ! Only used in a special case
829!  if Wind_N and Wind_E are in the file (and not just Wind)
830   LOGICAL, SAVE :: wind_N_exists=.FALSE.
831   LOGICAL       :: wind_E_exists=.FALSE.
832   LOGICAL, SAVE :: contfrac_exists=.FALSE.
833   LOGICAL, SAVE :: neighbours_exists=.FALSE.
834   LOGICAL, SAVE :: initialized = .FALSE.
835!  to bypass FPE problem on integer convertion with missing_value heigher than precision
836   INTEGER, PARAMETER                         :: undef_int = 999999999
837!---------------------------------------------------------------------
838
839   itau_read = MOD((itauin-1),ttm)+1
840
841   IF (printlev_loc >= 5) THEN
842      WRITE(numout,*) &
843           " FORCING READ : itauin, itau_read, itau_split : ",&
844           itauin, itau_read, itau_split
845   ENDIF
846
847!-
848!- This part initializes the reading of the forcing. As you can see
849!- we only go through here if both time steps are zero.
850!-
851   IF ( (itau_read == 0).AND.(itau_split == 0) ) THEN
852!-
853!- Tests on forcing file type
854     CALL flinquery_var(force_id, 'Wind_N', wind_N_exists)
855     IF ( wind_N_exists ) THEN
856        CALL flinquery_var(force_id, 'Wind_E', wind_E_exists)
857        IF ( .NOT. wind_E_exists ) THEN
858           CALL ipslerr_p(3,'forcing_read_interpol', &
859   &             'Variable Wind_E does not exist in forcing file', &
860   &             'But variable Wind_N exists.','Please, rename Wind_N to Wind;') 
861        ENDIF
862     ENDIF
863     CALL flinquery_var(force_id, 'levels', is_watchout)
864     IF ( is_watchout ) THEN
865        WRITE(numout,*) "Read a Watchout File."
866     ENDIF
867     CALL flinquery_var(force_id, 'contfrac', contfrac_exists)
868!-
869     IF (printlev_loc >= 5) WRITE(numout,*) 'ALLOCATE all the memory needed'
870!-
871     ALLOCATE &
872    &  (swdown_nm1(iim,jjm), rainf_nm1(iim,jjm), snowf_nm1(iim,jjm), &
873    &   tair_nm1(iim,jjm), u_nm1(iim,jjm), v_nm1(iim,jjm), qair_nm1(iim,jjm), &
874    &   pb_nm1(iim,jjm), lwdown_nm1(iim,jjm))
875     ALLOCATE &
876    &  (swdown_n(iim,jjm), rainf_n(iim,jjm), snowf_n(iim,jjm), &
877    &   tair_n(iim,jjm), u_n(iim,jjm), v_n(iim,jjm), qair_n(iim,jjm), &
878    &   pb_n(iim,jjm), lwdown_n(iim,jjm))
879
880     IF(daily_interpol) THEN
881        ALLOCATE &
882       &  (startday_n(iim,jjm), startday_nm1(iim,jjm), daylength_n(iim,jjm), &
883       &   daylength_nm1(iim,jjm), tmax_n(iim,jjm), tmax_nm1(iim,jjm), tmin_n(iim,jjm), &
884       &   tmin_nm1(iim,jjm), tmin_nm2(iim,jjm), qsatta(iim,jjm), qsattmin_n(iim,jjm), qsattmin_nm1(iim,jjm), &
885       &   qmin_n(iim,jjm), qmin_nm1(iim,jjm), qmax_n(iim,jjm), qmax_nm1(iim,jjm), qsa(iim,jjm) )
886     ENDIF
887
888
889     ALLOCATE &
890    &  (zlev_nm1(iim,jjm), zlev_n(iim,jjm), zlevuv_nm1(iim,jjm), zlevuv_n(iim,jjm), &
891    &   SWnet_nm1(iim,jjm), Eair_nm1(iim,jjm), cdrag_nm1(iim,jjm), ccanopy_nm1(iim,jjm), &
892    &   petAcoef_nm1(iim,jjm), peqAcoef_nm1(iim,jjm), petBcoef_nm1(iim,jjm), peqBcoef_nm1(iim,jjm), &
893    &   SWnet_n(iim,jjm), Eair_n(iim,jjm), cdrag_n(iim,jjm), ccanopy_n(iim,jjm), &
894    &   petAcoef_n(iim,jjm), peqAcoef_n(iim,jjm), petBcoef_n(iim,jjm), peqBcoef_n(iim,jjm))
895     ALLOCATE &
896    &  (mean_coszang(iim,jjm))
897!-
898     IF (printlev_loc >= 5) WRITE(numout,*) 'Memory ALLOCATED'
899!-
900!- We need for the driver surface air temperature and humidity before the
901!- the loop starts. Thus we read it here.
902!-     
903     CALL forcing_just_read (iim, jjm, zlev, zlevuv, ttm, 1, 1, &
904          &  swdown, rainf, snowf, tair, &
905          &  u, v, qair, pb, lwdown, &
906          &  SWnet, Eair, petAcoef, peqAcoef, petBcoef, peqBcoef, cdrag, ccanopy, &
907          &  force_id, wind_N_exists)
908!----
909
910!-- First in case it's not a watchout file
911     IF ( .NOT. is_watchout ) THEN
912        IF ( contfrac_exists ) THEN
913           IF (printlev_loc >= 1) WRITE(numout,*) "contfrac exist in the forcing file."
914           CALL flinget_buffer (force_id,'contfrac',iim_full, jjm_full, llm_full, ttm,  1, 1, data_full)
915           CALL forcing_zoom(data_full, fcontfrac)
916           IF (printlev_loc >= 2) WRITE(numout,*) "fcontfrac min/max :", &
917                MINVAL(fcontfrac(1:iim_zoom,jjm_zoom)),MAXVAL(fcontfrac(1:iim_zoom,jjm_zoom))
918           !
919           ! We need to make sure that when we gather the points we pick all
920           ! the points where contfrac is above 0. Thus we prepare tair for
921           ! subroutine forcing_landind
922           !
923           DO i=1,iim
924              DO j=1,jjm
925                 IF ( j==1 .AND. i<ii_begin) fcontfrac(i,j)=0.     ! bande de recouvrement du scatter2D
926                 IF ( j==jjm .AND. i>ii_end) fcontfrac(i,j)=0.     ! => on mets les données qu'on veut pas du noeud à missing_value
927                 IF ( fcontfrac(i,j) <= EPSILON(1.) ) THEN
928                    tair(i,j) = 999999.
929                 ENDIF
930              ENDDO
931           ENDDO
932        ELSE
933           fcontfrac(:,:) = 1.0
934        ENDIF
935        !---
936        !--- Create the index table
937        !---
938        !--- This job return a LOCAL kindex
939        CALL forcing_landind(iim, jjm, tair, nbindex, kindex, i_test, j_test)
940#ifdef CPP_PARA
941        ! We keep previous function forcing_landind, only to get a valid (i_test,j_test)
942        ! Force nbindex points for parallel computation
943        nbindex=nbp_loc
944        CALL scatter(index_g,kindex(1:nbindex))
945        kindex(1:nbindex)=kindex(1:nbindex)-(jj_begin-1)*iim_g
946#endif
947        ik=MAX(nbindex/2,1)
948        j_test = (((kindex(ik)-1)/iim) + 1)
949        i_test = (kindex(ik) - (j_test-1)*iim)
950        IF (printlev_loc >= 5) THEN
951           WRITE(numout,*) 'New test point is : ', i_test, j_test
952        ENDIF
953        !---
954        !--- Allocate grid stuff
955        !---
956        CALL grid_init ( nbindex, 4, regular_lonlat, "ForcingGrid" )
957        !---
958        !--- All grid variables
959        !---
960        CALL grid_stuff(nbp_glo, iim_g, jjm_g, lon_g, lat_g, index_g)
961        DO ik=1,nbindex
962           !
963           j = ((kindex(ik)-1)/iim) + 1
964           i = (kindex(ik) - (j-1)*iim)
965           !-
966           !- Store variable to help describe the grid
967           !- once the points are gathered.
968              !-
969           fneighbours(i,j,:) = neighbours(ik,:)
970           !
971           fresolution(i,j,:) = resolution(ik,:)
972        ENDDO
973     ELSE
974!-- Second, in case it is a watchout file
975        ALLOCATE (tmpdata(iim,jjm))
976        tmpdata(:,:) = 0.0
977!--
978        IF ( .NOT. contfrac_exists ) THEN
979           CALL ipslerr_p (3,'forcing_read_interpol', &
980 &          'Could get contfrac variable in a watchout file :',TRIM(filename), &
981 &          '(Problem with file ?)')
982        ENDIF
983        CALL flinget_buffer (force_id,'contfrac',iim_full, jjm_full, llm_full, ttm,  1, 1, data_full)
984        CALL forcing_zoom(data_full, fcontfrac)
985        !
986        ! We need to make sure that when we gather the points we pick all
987        ! the points where contfrac is above 0. Thus we prepare tair for
988        ! subroutine forcing_landind
989        !
990        DO i=1,iim
991           DO j=1,jjm
992              IF ( j==1 .AND. i<ii_begin) fcontfrac(i,j)=0.
993              IF ( j==jjm .AND. i>ii_end) fcontfrac(i,j)=0.
994              IF ( fcontfrac(i,j) <= EPSILON(1.) ) THEN
995                 tair(i,j) = 999999.
996              ENDIF
997           ENDDO
998        ENDDO
999
1000        !---
1001        !--- Create the index table
1002        !---
1003        !--- This job return a LOCAL kindex
1004        CALL forcing_landind(iim, jjm, tair, nbindex, kindex, i_test, j_test)
1005#ifdef CPP_PARA
1006        ! We keep previous function forcing_landind, only to get a valid (i_test,j_test)
1007        ! Force nbindex points for parallel computation
1008        nbindex=nbp_loc
1009        CALL scatter(index_g,kindex)
1010        kindex(:)=kindex(:)-offset
1011!        kindex(:)=kindex(:)-(jj_begin-1)*iim_g
1012#endif
1013        ik=MAX(nbindex/2,1)
1014        j_test = (((kindex(ik)-1)/iim) + 1)
1015        i_test = (kindex(ik) - (j_test-1)*iim)
1016        IF (printlev_loc >= 5) THEN
1017           WRITE(numout,*) 'New test point is : ', i_test, j_test
1018        ENDIF
1019        !---
1020        !--- Allocate grid stuff
1021        !---
1022        CALL grid_init ( nbindex, 4, regular_lonlat, "ForcingGrid" )
1023        neighbours(:,:) = -1
1024        resolution(:,:) = 0.
1025        min_resol(:) = 1.e6
1026        max_resol(:) = -1.
1027        !---
1028        !--- All grid variables
1029        !---
1030        !-
1031        !- Get variables to help describe the grid
1032        CALL flinquery_var(force_id, 'neighboursNN', neighbours_exists)
1033        IF ( .NOT. neighbours_exists ) THEN
1034           CALL ipslerr_p (3,'forcing_read_interpol', &
1035 &          'Could get neighbours in a watchout file :',TRIM(filename), &
1036 &          '(Problem with file ?)')
1037        ELSE
1038           IF (printlev_loc >= 2) WRITE(numout,*) "Watchout file contains neighbours and resolutions."
1039        ENDIF
1040        !
1041        fneighbours(:,:,:) = undef_int
1042        !
1043        !- once the points are gathered.
1044        CALL flinget_buffer (force_id,'neighboursNN',iim_full, jjm_full, llm_full, ttm,  1, 1, data_full)
1045        CALL forcing_zoom(data_full, tmpdata)
1046        WHERE(tmpdata(:,:) < undef_int)
1047           fneighbours(:,:,1) = NINT(tmpdata(:,:))
1048        ENDWHERE
1049        !
1050        CALL flinget_buffer (force_id,'neighboursNE',iim_full, jjm_full, llm_full, ttm,  1, 1, data_full)
1051        CALL forcing_zoom(data_full, tmpdata)
1052        WHERE(tmpdata(:,:) < undef_int)
1053           fneighbours(:,:,2) = NINT(tmpdata(:,:))
1054        ENDWHERE
1055        !
1056        CALL flinget_buffer (force_id,'neighboursEE',iim_full, jjm_full, llm_full, ttm,  1, 1, data_full)
1057        CALL forcing_zoom(data_full, tmpdata)
1058        WHERE(tmpdata(:,:) < undef_int)
1059           fneighbours(:,:,3) = NINT(tmpdata(:,:))
1060        ENDWHERE
1061        !
1062        CALL flinget_buffer (force_id,'neighboursSE',iim_full, jjm_full, llm_full, ttm,  1, 1, data_full)
1063        CALL forcing_zoom(data_full, tmpdata)
1064        WHERE(tmpdata(:,:) < undef_int)
1065           fneighbours(:,:,4) = NINT(tmpdata(:,:))
1066        ENDWHERE
1067        !
1068        CALL flinget_buffer (force_id,'neighboursSS',iim_full, jjm_full, llm_full, ttm,  1, 1, data_full)
1069        CALL forcing_zoom(data_full, tmpdata)
1070        WHERE(tmpdata(:,:) < undef_int)
1071           fneighbours(:,:,5) = NINT(tmpdata(:,:))
1072        ENDWHERE
1073        !
1074        CALL flinget_buffer (force_id,'neighboursSW',iim_full, jjm_full, llm_full, ttm,  1, 1, data_full)
1075        CALL forcing_zoom(data_full, tmpdata)
1076        WHERE(tmpdata(:,:) < undef_int)
1077           fneighbours(:,:,6) = NINT(tmpdata(:,:))
1078        ENDWHERE
1079        !
1080        CALL flinget_buffer (force_id,'neighboursWW',iim_full, jjm_full, llm_full, ttm,  1, 1, data_full)
1081        CALL forcing_zoom(data_full, tmpdata)
1082        WHERE(tmpdata(:,:) < undef_int)
1083           fneighbours(:,:,7) = NINT(tmpdata(:,:))
1084        ENDWHERE
1085        !
1086        CALL flinget_buffer (force_id,'neighboursNW',iim_full, jjm_full, llm_full, ttm,  1, 1, data_full)
1087        CALL forcing_zoom(data_full, tmpdata)
1088        WHERE(tmpdata(:,:) < undef_int)
1089           fneighbours(:,:,8) = NINT(tmpdata(:,:))
1090        ENDWHERE
1091        !
1092        ! now, resolution of the grid
1093        CALL flinget_buffer (force_id,'resolutionX',iim_full, jjm_full, llm_full, ttm,  1, 1, data_full)
1094        CALL forcing_zoom(data_full, tmpdata)
1095        fresolution(:,:,1) = tmpdata(:,:)
1096        !
1097        CALL flinget_buffer (force_id,'resolutionY',iim_full, jjm_full, llm_full, ttm,  1, 1, data_full)
1098        CALL forcing_zoom(data_full, tmpdata)
1099        fresolution(:,:,2) = tmpdata(:,:)
1100        !
1101        DO ik=1,nbindex
1102           !
1103           j = ((kindex(ik)-1)/iim) + 1
1104           i = (kindex(ik) - (j-1)*iim)
1105           !-
1106           !- Store variable to help describe the grid
1107           !- once the points are gathered.
1108           !-
1109           neighbours(ik,:) = fneighbours(i,j,:) 
1110           !
1111           resolution(ik,:) = fresolution(i,j,:)
1112           !
1113       
1114        ENDDO
1115        CALL gather(neighbours,neighbours_g)
1116        CALL gather(resolution,resolution_g)
1117        min_resol(1) = MINVAL(resolution(:,1))
1118        min_resol(2) = MAXVAL(resolution(:,2))
1119        max_resol(1) = MAXVAL(resolution(:,1))
1120        max_resol(2) = MAXVAL(resolution(:,2))
1121        !
1122        area(:) = resolution(:,1)*resolution(:,2)
1123        CALL gather(area,area_g)
1124!--
1125        DEALLOCATE (tmpdata)
1126     ENDIF
1127     IF (printlev_loc >= 2) WRITE(numout,*) 'contfrac : ', MINVAL(fcontfrac), MAXVAL(fcontfrac)
1128!---
1129   ENDIF
1130!---
1131   IF (printlev_loc >= 5) THEN
1132      WRITE(numout,*) &
1133           & 'The dates : ',itau_read,itau_split,itau_read_nm1,itau_read_n
1134   ENDIF
1135
1136
1137!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
1138!--- With the use of ORCHIDEE-CN-CAN, the solar angle needs to be provided at every timestep.
1139!--- Calculation of the absorption of light in the canopy (and therefore GPP) depends on this angle.
1140!--- Previously, the solar angle was not always computer (for example, for driver files
1141!--- with timesteps of less than half an hour.  The other problem, though, is that driver file
1142!--- time (often local time) does not always match ORCHIDEE time (UTC) for a single site.
1143!--- We treat this specific case here.  We may still have problems with daily_interpol, I believe.
1144!--- If dt_force is less than dt_cutoff (previously set to 3600), the solar angle will not
1145!--- be calculated below.
1146   IF ( dt_force .LE. dt_cutoff )  THEN
1147
1148      ! First, the case we have tested.  The forcing file timestep equals the model timestep.
1149      IF(split .EQ. 1)THEN
1150         IF(iim .EQ. 1 .AND. jjm .EQ. 1)THEN
1151
1152            julian_for = itau2date(itau_read-1, date0, dt_force)
1153            CALL ju2ymds (julian_for, yy, mm, dd, ss)
1154           
1155            ! first day of this year
1156            CALL ymds2ju (yy,1,1,0.0, julian0)
1157            !-----
1158            IF (printlev_loc >=3) THEN
1159               WRITE(numout,*) 'Forcing for Julian day ',julian_for,'is read'
1160               WRITE(numout,*) 'Date for this day ',yy,' / ',mm,' / ',dd,"  ",ss
1161            ENDIF
1162           
1163            julian = julian_for+dt_force/one_day
1164            ! By temporarily setting the longitude to zero degrees, we force UTC.
1165            lon_temp(:,:)=0.0_r_std
1166            CALL solarang (julian, julian0, iim, jjm, lon_temp, lat, coszang)
1167         ELSE
1168            CALL ipslerr_p(3,'forcing_read_interpol', &
1169                 'The forcing file is high frequency but not a single point!', &
1170                 'Not sure how to deal with this in regards to the solar angle.',&
1171                 'Continuing may result in points with low or zero GPP.') 
1172         ENDIF
1173      ELSE
1174         CALL ipslerr_p(3,'forcing_read_interpol', &
1175              'The forcing file is high frequency but not the same as the model timestep!', &
1176              'Not sure how to deal with this in regards to the solar angle.',&
1177              'Continuing may result in points with low or zero GPP.') 
1178      ENDIF
1179   ENDIF
1180!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
1181
1182!---
1183!--- Here we do the work in case only interpolation is needed.
1184!---
1185   IF ( initialized .AND. interpol ) THEN
1186!---
1187      IF ( daily_interpol ) THEN
1188
1189         IF (split > 1) THEN
1190            IF ( itau_split <= (split/2.) ) THEN
1191               rw = REAL(itau_split+split/2.)/split
1192            ELSE
1193               rw = REAL(itau_split-split/2.)/split
1194            ENDIF
1195         ELSE
1196            rw = 1.
1197         ENDIF
1198
1199         IF ((last_read == 0) .OR. ( rw==(1./split)) ) THEN
1200   !---
1201   !-----   Start or Restart
1202            IF (last_read == 0) THEN
1203               ! Case of a restart or a shift in the forcing file.
1204               IF (itau_read > 1) THEN
1205                  itau_read_nm1=itau_read-1
1206                  CALL forcing_just_read (iim, jjm, zlev_nm1, zlevuv_nm1, ttm, itau_read_nm1, itau_read_nm1, &
1207                       &  swdown_nm1, rainf_nm1, snowf_nm1, tmin_nm1, &
1208                       &  u_nm1, v_nm1, qair_nm1, pb_nm1, lwdown_nm1, &
1209                       &  SWnet_nm1, Eair_nm1, petAcoef_nm1, peqAcoef_nm1, petBcoef_nm1, peqBcoef_nm1, cdrag_nm1, ccanopy_nm1, &
1210                       &  force_id, wind_N_exists)
1211                  CALL forcing_just_read_tmax (iim, jjm, ttm, itau_read_nm1, itau_read_nm1, tmax_nm1, force_id )
1212               ! Case of a simple start.
1213               ELSE
1214                  itau_read_nm1 = un
1215                  IF (printlev_loc >= 2) WRITE(numout,*) "we will use the forcing of the first day to initialize "
1216                  CALL forcing_just_read (iim, jjm, zlev_nm1, zlevuv_nm1, ttm, itau_read_nm1, itau_read_nm1, &
1217                       &  swdown_nm1, rainf_nm1, snowf_nm1, tmin_nm1, &
1218                       &  u_nm1, v_nm1, qair_nm1, pb_nm1, lwdown_nm1, &
1219                       &  SWnet_nm1, Eair_nm1, petAcoef_nm1, peqAcoef_nm1, petBcoef_nm1, peqBcoef_nm1, cdrag_nm1, ccanopy_nm1, &
1220                       &  force_id, wind_N_exists)
1221                  CALL forcing_just_read_tmax (iim, jjm, ttm, itau_read_nm1, itau_read_nm1, tmax_nm1, force_id )
1222               ENDIF
1223               tmin_nm2(:,:)=tmin_nm1(:,:)
1224
1225               IF ( dt_force .GT. dt_cutoff ) THEN
1226                  mean_coszang(:,:) = 0.0
1227                  daylength_n(:,:) = 0.
1228                  DO is=1,split
1229                     !MM we compute mean SWdown between t and t+Dt then I take t+Dt/2.
1230                     julian_for = itau2date(itau_read-1, date0, dt_force)
1231                     julian = julian_for+((is-0.5)/split)*dt_force/one_day
1232                     ! first day of this year
1233                     CALL ymds2ju (yy,1,1,0.0, julian0)
1234      !!$               julian = julian_for+(FLOAT(is)/split)*dt_force/one_day
1235                     CALL solarang (julian, julian0, iim, jjm, lon*0, lat, coszang)
1236                     mean_coszang(:,:) = mean_coszang(:,:)+coszang(:,:)
1237                     WHERE( coszang(:,:) > 0. ) 
1238                        daylength_n(:,:)=daylength_n(:,:)+1./split*24
1239                     ENDWHERE
1240                  ENDDO
1241                  mean_coszang(:,:) = mean_coszang(:,:)/split
1242                  daylength_nm1(:,:)=daylength_n(:,:)
1243      !            WRITE(*,*) "mean_coszang =",MAXVAL(mean_coszang)
1244               ENDIF
1245            ELSE
1246   !-----   Normal mode : copy old step
1247               swdown_nm1(:,:) = swdown_n(:,:)
1248               rainf_nm1(:,:) = rainf_n(:,:)
1249               snowf_nm1(:,:)  = snowf_n(:,:) 
1250               tair_nm1(:,:)   = tair_n(:,:)
1251               u_nm1(:,:)      = u_n(:,:)
1252               v_nm1(:,:)      = v_n(:,:)
1253               qair_nm1(:,:)   = qair_n(:,:)
1254               pb_nm1(:,:)     = pb_n(:,:)
1255               lwdown_nm1(:,:) = lwdown_n(:,:)
1256               tmin_nm2(:,:)   = tmin_nm1(:,:)
1257               tmin_nm1(:,:)   = tmin_n(:,:)
1258               tmax_nm1(:,:)   = tmax_n(:,:)
1259
1260               IF (is_watchout) THEN
1261                  zlev_nm1(:,:)   = zlev_n(:,:)
1262                  zlevuv_nm1(:,:) = zlevuv_n(:,:)
1263                  ! Net surface short-wave flux
1264                  SWnet_nm1(:,:) = SWnet_n(:,:)
1265                  ! Air potential energy
1266                  Eair_nm1(:,:)   = Eair_n(:,:)
1267                  ! Coeficients A from the PBL resolution for T
1268                  petAcoef_nm1(:,:) = petAcoef_n(:,:)
1269                  ! Coeficients A from the PBL resolution for q
1270                  peqAcoef_nm1(:,:) = peqAcoef_n(:,:)
1271                  ! Coeficients B from the PBL resolution for T
1272                  petBcoef_nm1(:,:) = petBcoef_n(:,:)
1273                  ! Coeficients B from the PBL resolution for q
1274                  peqBcoef_nm1(:,:) = peqBcoef_n(:,:)
1275                  ! Surface drag
1276                  cdrag_nm1(:,:) = cdrag_n(:,:)
1277                  ! CO2 concentration in the canopy
1278                  ccanopy_nm1(:,:) = ccanopy_n(:,:)
1279               ENDIF
1280               itau_read_nm1 = itau_read_n
1281            ENDIF
1282   !-----
1283   !-----
1284            IF(last_read==0)THEN
1285               itau_read_n = itau_read
1286            ELSE
1287               itau_read_n = itau_read+1
1288            ENDIF
1289
1290            IF (itau_read_n > ttm) THEN
1291               WRITE(numout,*) 'WARNING --WARNING --WARNING --WARNING '
1292               WRITE(numout,*) &
1293                    &  'WARNING : We are going back to the start of the file'
1294               itau_read_n =1
1295            ENDIF
1296            IF (printlev_loc >= 5) THEN
1297               WRITE(numout,*) &
1298                    & 'The dates 2 : ',itau_read,itau_split,itau_read_nm1,itau_read_n
1299            ENDIF
1300   !-----
1301   !----- Get a reduced julian day !
1302   !----- This is needed because we lack the precision on 32 bit machines.
1303   !-----
1304            IF ( dt_force .GT. dt_cutoff ) THEN
1305               julian_for = itau2date(itau_read-1, date0, dt_force)
1306               CALL ju2ymds (julian_for, yy, mm, dd, ss)
1307   
1308               ! first day of this year
1309               CALL ymds2ju (yy,1,1,0.0, julian0)
1310   !-----
1311               IF (printlev_loc >= 5) THEN
1312                  WRITE(numout,*) 'Forcing for Julian day ',julian_for,'is read'
1313                  WRITE(numout,*) 'Date for this day ',yy,' / ',mm,' / ',dd,"  ",ss
1314               ENDIF
1315            ENDIF
1316   !-----
1317            CALL forcing_just_read (iim, jjm, zlev_n, zlevuv_n, ttm, itau_read_n, itau_read_n, &
1318                 &  swdown_n, rainf_n, snowf_n, tmin_n, &
1319                 &  u_n, v_n, qair_n, pb_n, lwdown_n, &
1320                 &  SWnet_n, Eair_n, petAcoef_n, peqAcoef_n, petBcoef_n, peqBcoef_n, cdrag_n, ccanopy_n, &
1321                 &  force_id, wind_N_exists)
1322            CALL forcing_just_read_tmax (iim, jjm, ttm, itau_read_n, itau_read_n, tmax_n, force_id )
1323
1324   !---
1325            last_read = itau_read_n
1326   !-----
1327   !----- Compute mean solar angle for the comming period
1328   !-----
1329            IF (printlev_loc >= 5) WRITE(numout,*) 'Going into  solarang', split, one_day
1330   !-----
1331
1332   !-----
1333         ENDIF
1334   !---
1335         IF ( itau_split == 1. ) THEN
1336            IF ( dt_force .GT. dt_cutoff ) THEN
1337               mean_coszang(:,:) = 0.0
1338               daylength_nm1(:,:)=daylength_n(:,:)
1339               daylength_n(:,:) = 0.
1340               DO is=1,split
1341                  !MM we compute mean SWdown between t and t+Dt then I take t+Dt/2.
1342                  julian = julian_for+((is-0.5)/split)*dt_force/one_day
1343   !!$               julian = julian_for+(FLOAT(is)/split)*dt_force/one_day
1344                  ! first day of this year
1345                  CALL ymds2ju (yy,1,1,0.0, julian0)
1346                  CALL solarang (julian, julian0, iim, jjm, lon*0, lat, coszang)
1347                  mean_coszang(:,:) = mean_coszang(:,:)+coszang(:,:)
1348                  WHERE( coszang(:,:) > 0. ) 
1349                     daylength_n(:,:)=daylength_n(:,:)+1./split*24
1350                  ENDWHERE
1351               ENDDO
1352               mean_coszang(:,:) = mean_coszang(:,:)/split
1353   !            WRITE(*,*) "mean_coszang =",MAXVAL(mean_coszang)
1354            ENDIF
1355         ENDIF
1356 
1357   !--- Do the interpolation
1358         IF (printlev_loc >= 5) WRITE(numout,*) 'Doing the interpolation between time steps'
1359   !---
1360
1361         IF (printlev_loc >= 5) WRITE(numout,*) 'Coeff of interpollation : ',rw
1362   !---
1363
1364         pb(:,:) = (pb_n(:,:)-pb_nm1(:,:))*rw + pb_nm1(:,:)
1365         u(:,:)  = (u_n(:,:)-u_nm1(:,:))*rw + u_nm1(:,:)
1366         v(:,:)  = (v_n(:,:)-v_nm1(:,:))*rw + v_nm1(:,:)
1367
1368   !--- Take care of the height of the vertical levels
1369         zlev(:,:) = (zlev_n(:,:)-zlev_nm1(:,:))*rw + zlev_nm1(:,:) 
1370         zlevuv(:,:) = (zlevuv_n(:,:)-zlevuv_nm1(:,:))*rw + zlevuv_nm1(:,:) 
1371
1372         hour=REAL(itau_split)/split*24
1373         startday_n(:,:)=12.-daylength_n(:,:)/2.
1374         startday_nm1(:,:)=12.-daylength_nm1(:,:)/2.
1375
1376         WHERE ( ( hour >= startday_n(:,:) ) .AND. ( hour > 12) .AND. ( hour <= 14) )
1377            tair(:,:)=(tmax_nm1(:,:)-tmin_nm1(:,:))/2 * ( sin(pi/(14-startday_n(:,:))*(hour-0.5* &
1378           &    (14.-startday_n(:,:))-startday_n(:,:))) )+ (tmax_nm1(:,:)+tmin_nm1(:,:))/2.
1379         ELSEWHERE( ( hour >= startday_n(:,:) ) .AND. ( hour <= 12) )
1380            tair(:,:)=(tmax_n(:,:)-tmin_n(:,:))/2 * ( sin(pi/(14-startday_n(:,:))*(hour-0.5* &
1381           &    (14.-startday_n(:,:))-startday_n(:,:))) )+ (tmax_n(:,:)+tmin_n(:,:))/2.
1382         ELSEWHERE ( hour < startday_n(:,:) )
1383            tair(:,:)=(tmax_nm1(:,:)-tmin_n(:,:))/2.*sin(pi/(24.-14.+startday_nm1(:,:) )* &
1384           &    (hour + 24.+0.5*(24.-14.+startday_nm1(:,:) )-14.))+(tmax_nm1(:,:)+tmin_n(:,:))/2.
1385         ELSEWHERE
1386            tair(:,:)=(tmax_nm1(:,:)-tmin_n(:,:))/2.*sin(pi/(24.-14.+startday_n(:,:))*(hour+0.5* &
1387           &    (24.-14.+startday_n(:,:))-14.))+(tmax_nm1(:,:)+tmin_n(:,:))/2.
1388         ENDWHERE
1389
1390         CALL weathgen_qsat_2d (iim,jjm,tmin_n,pb,qsattmin_n)
1391         CALL weathgen_qsat_2d (iim,jjm,tmin_nm1,pb,qsattmin_nm1)
1392         CALL weathgen_qsat_2d (iim,jjm,tair,pb,qsatta)
1393
1394         !---
1395         qmin_nm1(:,:) = MIN(qair_nm1(:,:),0.99*qsattmin_nm1(:,:))
1396         qmin_n(:,:) = MIN(qair_n(:,:),0.99*qsattmin_n(:,:))
1397         qmax_nm1(:,:) = (qair_nm1(:,:)-qmin_nm1(:,:)) + qair_nm1(:,:)
1398         qmax_n(:,:) = (qair_n(:,:)-qmin_n(:,:)) + qair_n(:,:)
1399
1400         qsa(:,:)  = 0.99*qsatta(:,:)
1401
1402
1403         WHERE ( ( hour >= startday_n(:,:) ) .AND. ( hour > 12) .AND. ( hour <= 14) )
1404            qair(:,:)=MIN(qsa(:,:),(qmax_nm1(:,:)-qmin_nm1(:,:))/2 * ( sin(pi/(14-startday_n(:,:))*(hour-0.5* &
1405           &    (14.-startday_n(:,:))-startday_n(:,:))) )+ (qmax_nm1(:,:)+qmin_nm1(:,:))/2.)
1406         ELSEWHERE( ( hour >= startday_n(:,:) ) .AND. ( hour <= 12) )
1407            qair(:,:)=MIN(qsa(:,:),(qmax_n(:,:)-qmin_n(:,:))/2 * ( sin(pi/(14-startday_n(:,:))*(hour-0.5* &
1408           &    (14.-startday_n(:,:))-startday_n(:,:))) )+ (qmax_n(:,:)+qmin_n(:,:))/2.)
1409         ELSEWHERE ( hour < startday_n(:,:) )
1410            qair(:,:)=MIN(qsa(:,:),(qmax_nm1(:,:)-qmin_n(:,:))/2.*sin(pi/(24.-14.+startday_nm1(:,:) )* &
1411           &    (hour + 24.+0.5*(24.-14.+startday_nm1(:,:) )-14.))+(qmax_nm1(:,:)+qmin_n(:,:))/2.)
1412         ELSEWHERE
1413            qair(:,:)=MIN(qsa(:,:),(qmax_nm1(:,:)-qmin_n(:,:))/2.*sin(pi/(24.-14.+startday_n(:,:))*(hour+0.5* &
1414           &    (24.-14.+startday_n(:,:))-14.))+(qmax_nm1(:,:)+qmin_n(:,:))/2.)
1415         ENDWHERE
1416
1417         IF (is_watchout) THEN
1418            SWnet(:,:) = (SWnet_n(:,:)-SWnet_nm1(:,:))*rw + SWnet_nm1(:,:)
1419            Eair(:,:) = (Eair_n(:,:)-Eair_nm1(:,:))*rw + Eair_nm1(:,:)
1420            petAcoef(:,:) = (petAcoef_n(:,:)-petAcoef_nm1(:,:))*rw + petAcoef_nm1(:,:)
1421            peqAcoef(:,:) = (peqAcoef_n(:,:)-peqAcoef_nm1(:,:))*rw + peqAcoef_nm1(:,:)
1422            petBcoef(:,:) = (petBcoef_n(:,:)-petBcoef_nm1(:,:))*rw + petBcoef_nm1(:,:)
1423            peqBcoef(:,:) = (peqBcoef_n(:,:)-peqBcoef_nm1(:,:))*rw + peqBcoef_nm1(:,:)
1424            cdrag(:,:) = (cdrag_n(:,:)-cdrag_nm1(:,:))*rw + cdrag_nm1(:,:)
1425            ccanopy(:,:) = (ccanopy_n(:,:)-ccanopy_nm1(:,:))*rw + ccanopy_nm1(:,:)
1426         ENDIF
1427   !---
1428   !--- Here we need to allow for an option
1429   !--- where radiative energy is conserved
1430   !---
1431         IF ( lwdown_cons ) THEN
1432            lwdown(:,:) = lwdown_n(:,:)
1433         ELSE
1434            lwdown(:,:) = (lwdown_n(:,:)-lwdown_nm1(:,:))*rw + lwdown_nm1(:,:)
1435         ENDIF
1436   !---
1437   !--- For the solar radiation we decompose the mean value
1438   !--- using the zenith angle of the sun, conservative approach under 2000W/m2
1439   !----
1440         IF (printlev_loc >= 5) WRITE(numout,*) 'Ready to deal with the solar radiation'
1441   !----
1442
1443         ! We compute mean SWdown between t and t+Dt then we take t+Dt/2.
1444         julian = julian_for + (itau_split-0.5)/split*dt_force/one_day
1445!!$         julian = julian_for + rw*dt_force/one_day
1446         IF (printlev_loc >= 5) THEN
1447            WRITE(numout,'(a,f20.10,2I3)') &
1448                 &  'JULIAN BEFORE SOLARANG : ',julian,itau_split,split
1449         ENDIF
1450 
1451         CALL solarang(julian, julian0, iim, jjm, lon*0, lat, coszang)
1452 
1453         WHERE ((mean_coszang(:,:) > 0.) .AND. (hour <= 12 ))
1454            swdown(:,:) = swdown_n(:,:) *coszang(:,:)/mean_coszang(:,:)
1455         ELSEWHERE ((mean_coszang(:,:) > 0.) .AND. (hour > 12 ))
1456            swdown(:,:) = swdown_nm1(:,:) *coszang(:,:)/mean_coszang(:,:)
1457         ELSEWHERE
1458            swdown(:,:) = 0.0
1459         END WHERE
1460 
1461         WHERE (swdown(:,:) > 2000. )
1462            swdown(:,:) = 2000.
1463         END WHERE
1464   
1465     
1466         IF (printlev_loc >= 5) THEN
1467            WRITE(numout,*) '__ Forcing read at ',itau_split,' :',i_test, j_test
1468            WRITE(numout,*) 'SWdown  : ',swdown_nm1(i_test, j_test), &
1469                 &           ' < ', swdown(i_test, j_test), ' < ', swdown_n(i_test, j_test)
1470            IF (is_watchout) THEN
1471               WRITE(numout,*) 'SWnet  : ',swnet_nm1(i_test, j_test), &
1472                    &           ' < ', swnet(i_test, j_test), ' < ', swnet_n(i_test, j_test)
1473               WRITE(numout,*) 'levels  :',zlev_nm1(i_test, j_test), &
1474                    &           ' < ', zlev(i_test, j_test), ' < ', zlev_n(i_test, j_test)
1475               WRITE(numout,*) 'EAIR  :',Eair_nm1(i_test, j_test), &
1476                    &           ' < ', eair(i_test, j_test), ' < ', Eair_n(i_test, j_test)
1477            ENDIF
1478            WRITE(numout,*) 'TAIR  :',tair_nm1(i_test, j_test), &
1479                 &           ' < ', tair(i_test, j_test), ' < ', tair_n(i_test, j_test)
1480            WRITE(numout,*) 'QAIR  :',qair_nm1(i_test, j_test), &
1481                 &           ' < ', qair(i_test, j_test), ' < ', qair_n(i_test, j_test)
1482            WRITE(numout,*) 'U  :',u_nm1(i_test, j_test), &
1483                 &           ' < ', u(i_test, j_test), ' < ', u_n(i_test, j_test)
1484            WRITE(numout,*) 'V  :',v_nm1(i_test, j_test), &
1485                 &           ' < ', v(i_test, j_test), ' < ', v_n(i_test, j_test)
1486         ENDIF
1487   !---
1488   !--- For precip we suppose that the rain
1489   !--- is the sum over the next 6 hours
1490   !---
1491         WHERE ((itau_split <= nb_spread).AND.(hour<=12).AND.(tair(:,:)>=273.15)) 
1492            rainf(:,:) = rainf_n(:,:) *(split/REAL(nb_spread))
1493            snowf(:,:) = 0.0
1494         ELSEWHERE ((itau_split <= nb_spread).AND.(hour<=12).AND.(tair(:,:)<273.15)) 
1495            snowf(:,:) = rainf_n(:,:) *(split/REAL(nb_spread))
1496            rainf(:,:) = 0.0
1497         ELSEWHERE ((itau_split <= nb_spread).AND.(hour>12).AND.(tair(:,:)>=273.15)) 
1498            rainf(:,:) = rainf_nm1(:,:) *(split/REAL(nb_spread))
1499            snowf(:,:) = 0.0
1500         ELSEWHERE ((itau_split <= nb_spread).AND.(hour>12).AND.(tair(:,:)<273.15)) 
1501            snowf(:,:) = rainf_nm1(:,:) *(split/REAL(nb_spread))
1502            rainf(:,:) = 0.0
1503         ELSEWHERE
1504            snowf(:,:) = 0.0
1505            rainf(:,:) = 0.0
1506         ENDWHERE
1507
1508         IF (printlev_loc >= 5) THEN
1509            WRITE(numout,*) '__ Forcing read at ',itau_split,' :'
1510            WRITE(numout,*) 'Rainf  : ',rainf_nm1(i_test, j_test), &
1511                 &           ' < ', rainf(i_test, j_test), ' < ', rainf_n(i_test, j_test)
1512            WRITE(numout,*) 'Snowf  : ',snowf_nm1(i_test, j_test), &
1513                 &           ' < ', snowf(i_test, j_test), ' < ', snowf_n(i_test, j_test)
1514         ENDIF
1515   !---
1516
1517      ELSE ! If not daily_interpol
1518         
1519         IF (itau_read /= last_read) THEN
1520   !---
1521   !-----   Start or Restart
1522            IF (itau_read_n == 0) THEN
1523               ! Case of a restart or a shift in the forcing file.
1524               IF (itau_read > 1) THEN
1525                  itau_read_nm1=itau_read-1
1526                  CALL forcing_just_read (iim, jjm, zlev_nm1, zlevuv_nm1, ttm, itau_read_nm1, itau_read_nm1, &
1527                       &  swdown_nm1, rainf_nm1, snowf_nm1, tair_nm1, &
1528                       &  u_nm1, v_nm1, qair_nm1, pb_nm1, lwdown_nm1, &
1529                       &  SWnet_nm1, Eair_nm1, petAcoef_nm1, peqAcoef_nm1, petBcoef_nm1, peqBcoef_nm1, cdrag_nm1, ccanopy_nm1, &
1530                       &  force_id, wind_N_exists)
1531               ! Case of a simple start.
1532               ELSE IF (dt_force*ttm > one_day-1. ) THEN
1533                  ! if the forcing file contains at least 24 hours,
1534                  ! we will use the last forcing step of the first day
1535                  ! as initiale condition to prevent first shift off reading.
1536                  itau_read_nm1 = NINT (one_day/dt_force)
1537                  IF (printlev_loc >= 1) WRITE(numout,*) "The forcing file contains 24 hours :",dt_force*ttm,one_day-1.
1538                  IF (printlev_loc >= 1) WRITE(numout,*) "We will use the last forcing step of the first day : itau_read_nm1 ",&
1539                       itau_read_nm1
1540                  CALL forcing_just_read (iim, jjm, zlev_nm1, zlevuv_nm1, ttm, itau_read_nm1, itau_read_nm1, &
1541                       &  swdown_nm1, rainf_nm1, snowf_nm1, tair_nm1, &
1542                       &  u_nm1, v_nm1, qair_nm1, pb_nm1, lwdown_nm1, &
1543                       &  SWnet_nm1, Eair_nm1, petAcoef_nm1, peqAcoef_nm1, petBcoef_nm1, peqBcoef_nm1, cdrag_nm1, ccanopy_nm1, &
1544                       &  force_id, wind_N_exists)
1545               ELSE
1546                  ! if the forcing file contains less than 24 hours,
1547                  ! just say error !
1548                  CALL ipslerr_p(3,'forcing_read_interpol', &
1549      &             'The forcing file contains less than 24 hours !', &
1550      &             'We can''t intialize interpolation with such a file.','') 
1551               ENDIF
1552            ELSE
1553   !-----   Normal mode : copy old step
1554               swdown_nm1(:,:) = swdown_n(:,:)
1555               rainf_nm1(:,:) = rainf_n(:,:)
1556               snowf_nm1(:,:)  = snowf_n(:,:) 
1557               tair_nm1(:,:)   = tair_n(:,:)
1558               u_nm1(:,:)      = u_n(:,:)
1559               v_nm1(:,:)      = v_n(:,:)
1560               qair_nm1(:,:)   = qair_n(:,:)
1561               pb_nm1(:,:)     = pb_n(:,:)
1562               lwdown_nm1(:,:) = lwdown_n(:,:)
1563               IF (is_watchout) THEN
1564                  zlev_nm1(:,:)   = zlev_n(:,:)
1565                  ! Net surface short-wave flux
1566                  SWnet_nm1(:,:) = SWnet_n(:,:)
1567                  ! Air potential energy
1568                  Eair_nm1(:,:)   = Eair_n(:,:)
1569                  ! Coeficients A from the PBL resolution for T
1570                  petAcoef_nm1(:,:) = petAcoef_n(:,:)
1571                  ! Coeficients A from the PBL resolution for q
1572                  peqAcoef_nm1(:,:) = peqAcoef_n(:,:)
1573                  ! Coeficients B from the PBL resolution for T
1574                  petBcoef_nm1(:,:) = petBcoef_n(:,:)
1575                  ! Coeficients B from the PBL resolution for q
1576                  peqBcoef_nm1(:,:) = peqBcoef_n(:,:)
1577                  ! Surface drag
1578                  cdrag_nm1(:,:) = cdrag_n(:,:)
1579                  ! CO2 concentration in the canopy
1580                  ccanopy_nm1(:,:) = ccanopy_n(:,:)
1581               ENDIF
1582               itau_read_nm1 = itau_read_n
1583            ENDIF
1584   !-----
1585            itau_read_n = itau_read
1586            IF (itau_read_n > ttm) THEN
1587               WRITE(numout,*) 'WARNING --WARNING --WARNING --WARNING '
1588               WRITE(numout,*) &
1589                    &  'WARNING : We are going back to the start of the file'
1590               itau_read_n =1
1591            ENDIF
1592            IF (printlev_loc >= 5) THEN
1593               WRITE(numout,*) &
1594                    & 'The dates 2 : ',itau_read,itau_split,itau_read_nm1,itau_read_n
1595            ENDIF
1596   !-----
1597   !----- Get a reduced julian day !
1598   !----- This is needed because we lack the precision on 32 bit machines.
1599   !-----
1600            IF ( dt_force .GT. dt_cutoff ) THEN
1601               julian_for = itau2date(itau_read-1, date0, dt_force)
1602               CALL ju2ymds (julian_for, yy, mm, dd, ss)
1603   
1604               ! first day of this year
1605               CALL ymds2ju (yy,1,1,0.0, julian0)
1606   !-----
1607               IF (printlev_loc >= 5) THEN
1608                  WRITE(numout,*) 'Forcing for Julian day ',julian_for,'is read'
1609                  WRITE(numout,*) 'Date for this day ',yy,' / ',mm,' / ',dd,"  ",ss
1610               ENDIF
1611            ENDIF
1612   !-----
1613            CALL forcing_just_read (iim, jjm, zlev_n, zlevuv_n, ttm, itau_read_n, itau_read_n, &
1614                 &  swdown_n, rainf_n, snowf_n, tair_n, &
1615                 &  u_n, v_n, qair_n, pb_n, lwdown_n, &
1616                 &  SWnet_n, Eair_n, petAcoef_n, peqAcoef_n, petBcoef_n, peqBcoef_n, cdrag_n, ccanopy_n, &
1617                 &  force_id, wind_N_exists)
1618   !---
1619            last_read = itau_read_n
1620   !-----
1621   !----- Compute mean solar angle for the comming period
1622   !-----
1623            IF (printlev_loc >= 5) WRITE(numout,*) 'Going into  solarang', split, one_day
1624   !-----
1625            IF ( dt_force .GT. dt_cutoff ) THEN
1626               mean_coszang(:,:) = 0.0
1627               DO is=1,split
1628                  !MM we compute mean SWdown between t and t+Dt then I take t+Dt/2.
1629                  julian = julian_for+((is-0.5)/split)*dt_force/one_day
1630                  ! first day of this year
1631                  CALL ymds2ju (yy,1,1,0.0, julian0)
1632   !!$               julian = julian_for+(FLOAT(is)/split)*dt_force/one_day
1633                  CALL solarang (julian, julian0, iim, jjm, lon, lat, coszang)
1634                  mean_coszang(:,:) = mean_coszang(:,:)+coszang(:,:)
1635               ENDDO
1636               mean_coszang(:,:) = mean_coszang(:,:)/split
1637   !            WRITE(*,*) "mean_coszang =",MAXVAL(mean_coszang)
1638            ENDIF
1639   !-----
1640         ENDIF
1641   !---
1642   !--- Do the interpolation
1643         IF (printlev_loc >= 5) WRITE(numout,*) 'Doing the interpolation between time steps'
1644   !---
1645         IF (split > 1) THEN
1646            rw = REAL(itau_split)/split
1647         ELSE
1648            rw = 1.
1649         ENDIF
1650         IF (printlev_loc >= 5) WRITE(numout,*) 'Coeff of interpollation : ',rw
1651   !---
1652         qair(:,:) = (qair_n(:,:)-qair_nm1(:,:))*rw + qair_nm1(:,:)
1653         tair(:,:) = (tair_n(:,:)-tair_nm1(:,:))*rw + tair_nm1(:,:)
1654         pb(:,:) = (pb_n(:,:)-pb_nm1(:,:))*rw + pb_nm1(:,:)
1655         u(:,:)  = (u_n(:,:)-u_nm1(:,:))*rw + u_nm1(:,:)
1656         v(:,:)  = (v_n(:,:)-v_nm1(:,:))*rw + v_nm1(:,:)
1657         IF (is_watchout) THEN
1658            zlev(:,:) = (zlev_n(:,:)-zlev_nm1(:,:))*rw + zlev_nm1(:,:)
1659            zlevuv(:,:) = zlev(:,:)
1660            SWnet(:,:) = (SWnet_n(:,:)-SWnet_nm1(:,:))*rw + SWnet_nm1(:,:)
1661            Eair(:,:) = (Eair_n(:,:)-Eair_nm1(:,:))*rw + Eair_nm1(:,:)
1662            petAcoef(:,:) = (petAcoef_n(:,:)-petAcoef_nm1(:,:))*rw + petAcoef_nm1(:,:)
1663            peqAcoef(:,:) = (peqAcoef_n(:,:)-peqAcoef_nm1(:,:))*rw + peqAcoef_nm1(:,:)
1664            petBcoef(:,:) = (petBcoef_n(:,:)-petBcoef_nm1(:,:))*rw + petBcoef_nm1(:,:)
1665            peqBcoef(:,:) = (peqBcoef_n(:,:)-peqBcoef_nm1(:,:))*rw + peqBcoef_nm1(:,:)
1666            cdrag(:,:) = (cdrag_n(:,:)-cdrag_nm1(:,:))*rw + cdrag_nm1(:,:)
1667            ccanopy(:,:) = (ccanopy_n(:,:)-ccanopy_nm1(:,:))*rw + ccanopy_nm1(:,:)
1668         ENDIF
1669   !---
1670   !--- Here we need to allow for an option
1671   !--- where radiative energy is conserved
1672   !---
1673         IF ( lwdown_cons ) THEN
1674            lwdown(:,:) = lwdown_n(:,:)
1675         ELSE
1676            lwdown(:,:) = (lwdown_n(:,:)-lwdown_nm1(:,:))*rw + lwdown_nm1(:,:)
1677         ENDIF
1678   !---
1679   !--- For the solar radiation we decompose the mean value
1680   !--- using the zenith angle of the sun if the time step in the forcing data is
1681   !---- more than an hour. Else we use the standard linera interpolation
1682   !----
1683         IF (printlev_loc >= 5) WRITE(numout,*) 'Ready to deal with the solar radiation'
1684   !----
1685         IF ( dt_force .GT. dt_cutoff ) THEN
1686
1687            ! In this case solar radiation will be conserved
1688 
1689            ! We compute mean SWdown between t and t+Dt then we take t+Dt/2.
1690            julian = julian_for + (itau_split-0.5)/split*dt_force/one_day
1691   !!$         julian = julian_for + rw*dt_force/one_day
1692            IF (printlev_loc >= 5) THEN
1693               WRITE(numout,'(a,f20.10,2I3)') &
1694                    &  'JULIAN BEFORE SOLARANG : ',julian,itau_split,split
1695            ENDIF
1696   !---
1697            CALL solarang(julian, julian0, iim, jjm, lon, lat, coszang)
1698   !---
1699            WHERE (mean_coszang(:,:) > 0.)
1700               swdown(:,:) = swdown_n(:,:) *coszang(:,:)/mean_coszang(:,:)
1701            ELSEWHERE
1702               swdown(:,:) = 0.0
1703            END WHERE
1704   !---
1705            WHERE (swdown(:,:) > 2000. )
1706               swdown(:,:) = 2000.
1707            END WHERE
1708   !---
1709         ELSE ! If dt_force < 3600 (1h)
1710
1711            IF ( swdown_cons ) THEN
1712               ! Conserve swdown radiation
1713               swdown(:,:) = swdown_n(:,:)
1714            ELSE
1715               swdown(:,:) = (swdown_n(:,:)-swdown_nm1(:,:))*rw + swdown_nm1(:,:)
1716            ENDIF
1717   !---
1718         ENDIF
1719   !---
1720         IF (printlev_loc >= 5) THEN
1721            WRITE(numout,*) '__ Forcing read at ',itau_split,' :',i_test, j_test
1722            WRITE(numout,*) 'SWdown  : ',swdown_nm1(i_test, j_test), &
1723                 &           ' < ', swdown(i_test, j_test), ' < ', swdown_n(i_test, j_test)
1724            IF (is_watchout) THEN
1725               WRITE(numout,*) 'SWnet  : ',swnet_nm1(i_test, j_test), &
1726                    &           ' < ', swnet(i_test, j_test), ' < ', swnet_n(i_test, j_test)
1727               WRITE(numout,*) 'levels  :',zlev_nm1(i_test, j_test), &
1728                    &           ' < ', zlev(i_test, j_test), ' < ', zlev_n(i_test, j_test)
1729               WRITE(numout,*) 'EAIR  :',Eair_nm1(i_test, j_test), &
1730                    &           ' < ', eair(i_test, j_test), ' < ', Eair_n(i_test, j_test)
1731            ENDIF
1732            WRITE(numout,*) 'TAIR  :',tair_nm1(i_test, j_test), &
1733                 &           ' < ', tair(i_test, j_test), ' < ', tair_n(i_test, j_test)
1734            WRITE(numout,*) 'QAIR  :',qair_nm1(i_test, j_test), &
1735                 &           ' < ', qair(i_test, j_test), ' < ', qair_n(i_test, j_test)
1736            WRITE(numout,*) 'U  :',u_nm1(i_test, j_test), &
1737                 &           ' < ', u(i_test, j_test), ' < ', u_n(i_test, j_test)
1738            WRITE(numout,*) 'V  :',v_nm1(i_test, j_test), &
1739                 &           ' < ', v(i_test, j_test), ' < ', v_n(i_test, j_test)
1740         ENDIF
1741   !---
1742   !--- For precip we suppose that the rain
1743   !--- is the sum over the next 6 hours
1744   !---
1745         IF (itau_split <= nb_spread) THEN
1746            rainf(:,:) = rainf_n(:,:)*(split/REAL(nb_spread))
1747            snowf(:,:) = snowf_n(:,:)*(split/REAL(nb_spread))
1748         ELSE
1749            rainf(:,:) = 0.0
1750            snowf(:,:) = 0.0
1751         ENDIF
1752         IF (printlev_loc >= 5) THEN
1753            WRITE(numout,*) '__ Forcing read at ',itau_split,' :'
1754            WRITE(numout,*) 'Rainf  : ',rainf_nm1(i_test, j_test), &
1755                 &           ' < ', rainf(i_test, j_test), ' < ', rainf_n(i_test, j_test)
1756            WRITE(numout,*) 'Snowf  : ',snowf_nm1(i_test, j_test), &
1757                 &           ' < ', snowf(i_test, j_test), ' < ', snowf_n(i_test, j_test)
1758         ENDIF
1759   !---
1760      ENDIF ! (daily_interpol)
1761   ENDIF
1762!---
1763!--- Here we might put the call to the weather generator ... one day.
1764!--- Pour le moment, le branchement entre interpolation et generateur de temps
1765!--- est fait au-dessus.
1766!---
1767!-   IF ( initialized .AND. weathergen ) THEN
1768!-      ....
1769!-   ENDIF
1770!---
1771!--- At this point the code should be initialized. If not we have a problem !
1772!---
1773   IF ( (itau_read == 0).AND.(itau_split == 0) ) THEN
1774!---
1775      initialized = .TRUE.
1776!---
1777   ELSE
1778      IF ( .NOT. initialized ) THEN
1779         WRITE(numout,*) 'Why is the code forcing_read not initialized ?'
1780         WRITE(numout,*) 'Have you called it with both time-steps set to zero ?'
1781         CALL ipslerr_p(3,'forcing_read_interpol','Pb in initialization','','')
1782      ENDIF
1783   ENDIF
1784
1785END SUBROUTINE forcing_read_interpol
1786
1787
1788!! ==============================================================================================================================\n
1789!! SUBROUTINE   : forcing_just_read
1790!!
1791!>\BRIEF       
1792!!
1793!!\n DESCRIPTION :
1794!!
1795!! RECENT CHANGE(S): None
1796!!
1797!! MAIN OUTPUT VARIABLE(S):
1798!!
1799!! REFERENCE(S) :
1800!!
1801!_ ================================================================================================================================
1802SUBROUTINE forcing_just_read &
1803  & (iim, jjm, zlev, zlev_uv, ttm, itb, ite, &
1804  &  swdown, rainf, snowf, tair, &
1805  &  u, v, qair, pb, lwdown, &
1806  &  SWnet, Eair, petAcoef, peqAcoef, petBcoef, peqBcoef, cdrag, ccanopy, &
1807  &  force_id, wind_N_exists)
1808!---------------------------------------------------------------------
1809!- iim        : Size of the grid in x
1810!- jjm        : size of the grid in y
1811!- zlev       : height of the varibales T and Q
1812!- zlev_uv    : height of the varibales U and V
1813!- ttm        : number of time steps in all in the forcing file
1814!- itb, ite   : index of respectively begin and end of read for each variable
1815!- swdown     : Downward solar radiation (W/m^2)
1816!- rainf      : Rainfall (kg/m^2s)
1817!- snowf      : Snowfall (kg/m^2s)
1818!- tair       : 2m air temperature (K)
1819!- u and v    : 2m (in theory !) wind speed (m/s)
1820!- qair       : 2m humidity (kg/kg)
1821!- pb         : Surface pressure (Pa)
1822!- lwdown     : Downward long wave radiation (W/m^2)
1823!-
1824!- From a WATCHOUT file :
1825!- SWnet      : Net surface short-wave flux
1826!- Eair       : Air potential energy
1827!- petAcoef   : Coeficients A from the PBL resolution for T
1828!- peqAcoef   : Coeficients A from the PBL resolution for q
1829!- petBcoef   : Coeficients B from the PBL resolution for T
1830!- peqBcoef   : Coeficients B from the PBL resolution for q
1831!- cdrag      : Surface drag
1832!- ccanopy    : CO2 concentration in the canopy
1833!- force_id   : FLINCOM file id.
1834!-              It is used to close the file at the end of the run.
1835!- wind_N_exists : if Wind_N and Wind_E are in the file (and not just Wind)
1836!---------------------------------------------------------------------
1837   IMPLICIT NONE
1838!-
1839   INTEGER, INTENT(in) :: iim, jjm, ttm
1840   INTEGER, INTENT(in) :: itb, ite
1841   REAL, DIMENSION(iim,jjm), INTENT(out) ::  zlev, zlev_uv, &
1842  &  swdown, rainf, snowf, tair, u, v, qair, pb, lwdown
1843   ! for watchout files
1844   REAL, DIMENSION(iim,jjm), INTENT(out) :: &
1845  &  SWnet, Eair, petAcoef, peqAcoef, petBcoef, peqBcoef, cdrag, ccanopy
1846   INTEGER, INTENT(in) :: force_id
1847!  if Wind_N and Wind_E are in the file (and not just Wind)
1848   LOGICAL, INTENT(in) :: wind_N_exists
1849   INTEGER :: i, j 
1850   REAL :: rau 
1851
1852!-
1853!---------------------------------------------------------------------
1854   IF ( daily_interpol ) THEN
1855      CALL flinget_buffer (force_id,'Tmin'  , iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1856      CALL forcing_zoom(data_full, tair)
1857      CALL flinget_buffer (force_id,'precip' , iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1858      CALL forcing_zoom(data_full, rainf)
1859   ELSE
1860      CALL flinget_buffer (force_id,'Tair'  , iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1861      CALL forcing_zoom(data_full, tair)
1862      CALL flinget_buffer (force_id,'Snowf' , iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1863      CALL forcing_zoom(data_full, snowf)
1864      CALL flinget_buffer (force_id,'Rainf' , iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1865      CALL forcing_zoom(data_full, rainf)
1866   ENDIF
1867
1868
1869   CALL flinget_buffer (force_id,'SWdown', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1870   CALL forcing_zoom(data_full, swdown)
1871   CALL flinget_buffer (force_id,'LWdown', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1872   CALL forcing_zoom(data_full, lwdown)
1873
1874   CALL flinget_buffer (force_id,'PSurf' , iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1875   CALL forcing_zoom(data_full, pb)
1876   CALL flinget_buffer (force_id,'Qair'  , iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1877   CALL forcing_zoom(data_full, qair)
1878!---
1879   IF ( wind_N_exists ) THEN
1880      CALL flinget_buffer (force_id,'Wind_N', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1881      CALL forcing_zoom(data_full, u)
1882      CALL flinget_buffer (force_id,'Wind_E', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1883      CALL forcing_zoom(data_full, v)
1884   ELSE
1885      CALL flinget_buffer (force_id,'Wind',   iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1886      CALL forcing_zoom(data_full, u)
1887      v=0.0
1888   ENDIF
1889
1890!-
1891!- Deal with the height of the atmospheric forcing varibles
1892!-
1893!----
1894   IF ( zheight ) THEN
1895      zlev(:,:) = zlev_fixed 
1896   ELSE IF ( zsigma .OR. zhybrid ) THEN
1897      DO i=1,iim 
1898         DO j=1,jjm 
1899            IF ( tair(i,j) < val_exp ) THEN
1900               rau = pb(i,j)/(cte_molr*tair(i,j)) 
1901                 
1902               zlev(i,j) =  (pb(i,j) - (zhybrid_a + zhybrid_b*pb(i,j)))/(rau * cte_grav) 
1903            ELSE
1904               zlev(i,j) = 0.0 
1905            ENDIF
1906         ENDDO
1907      ENDDO
1908   ELSE IF ( zlevels ) THEN
1909      CALL flinget_buffer (force_id,'Levels', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full) 
1910      CALL forcing_zoom(data_full, zlev) 
1911   ELSE
1912      CALL ipslerr(3, 'forcing_just_read','No case for the vertical levels was specified.', & 
1913           &         'We cannot determine the height for T and Q.','stop readdim2') 
1914   ENDIF
1915   
1916   IF ( zsamelev_uv ) THEN
1917      zlev_uv(:,:) = zlev(:,:) 
1918   ELSE
1919      IF ( zheight ) THEN
1920         zlev_uv(:,:) = zlevuv_fixed 
1921      ELSE IF ( zsigma .OR. zhybrid ) THEN
1922         DO i=1,iim 
1923            DO j=1,jjm 
1924               IF ( tair(i,j) < val_exp ) THEN
1925                  rau = pb(i,j)/(cte_molr*tair(i,j)) 
1926                 
1927                  zlev_uv(i,j) =  (pb(i,j) - (zhybriduv_a + zhybriduv_b*pb(i,j)))/(rau * cte_grav) 
1928               ELSE
1929                  zlev_uv(i,j) = 0.0 
1930               ENDIF
1931            ENDDO
1932         ENDDO
1933      ELSE IF ( zlevels ) THEN
1934         CALL flinget_buffer (force_id,'Levels_uv', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full) 
1935         CALL forcing_zoom(data_full, zlev_uv) 
1936      ELSE
1937         CALL ipslerr(3, 'forcing_just_read','No case for the vertical levels was specified.', & 
1938              &         'We cannot determine the height for U and V.','stop readdim2') 
1939      ENDIF
1940   ENDIF
1941   !----
1942   IF ( is_watchout ) THEN
1943      CALL flinget_buffer (force_id,'levels', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1944      CALL forcing_zoom(data_full, zlev)
1945      !
1946      ! If we are in WATHCOUT it means T,Q are at the same height as U,V
1947      !
1948      zlev_uv(:,:) = zlev(:,:) 
1949      ! Net surface short-wave flux
1950      CALL flinget_buffer (force_id,'SWnet', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1951      CALL forcing_zoom(data_full, SWnet)
1952      ! Air potential energy
1953      CALL flinget_buffer (force_id,'Eair', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1954      CALL forcing_zoom(data_full, Eair)
1955      ! Coeficients A from the PBL resolution for T
1956      CALL flinget_buffer (force_id,'petAcoef', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1957      CALL forcing_zoom(data_full, petAcoef)
1958      ! Coeficients A from the PBL resolution for q
1959      CALL flinget_buffer (force_id,'peqAcoef', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1960      CALL forcing_zoom(data_full, peqAcoef)
1961      ! Coeficients B from the PBL resolution for T
1962      CALL flinget_buffer (force_id,'petBcoef', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1963      CALL forcing_zoom(data_full, petBcoef)
1964      ! Coeficients B from the PBL resolution for q
1965      CALL flinget_buffer (force_id,'peqBcoef', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1966      CALL forcing_zoom(data_full, peqBcoef)
1967      ! Surface drag
1968      CALL flinget_buffer (force_id,'cdrag', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1969      CALL forcing_zoom(data_full, cdrag)
1970      ! CO2 concentration in the canopy
1971      CALL flinget_buffer (force_id,'ccanopy', iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
1972      CALL forcing_zoom(data_full, ccanopy)
1973   ENDIF
1974!
1975!----
1976     IF (printlev_loc >= 5) WRITE(numout,*) 'Variables have been extracted between ',itb,&
1977          ' and ',ite,' iterations of the forcing file.'
1978!-------------------------
1979END SUBROUTINE forcing_just_read
1980
1981
1982!! ==============================================================================================================================\n
1983!! SUBROUTINE   : forcing_just_read_tmax
1984!!
1985!>\BRIEF       
1986!!
1987!!\n DESCRIPTION :
1988!!
1989!! RECENT CHANGE(S): None
1990!!
1991!! MAIN OUTPUT VARIABLE(S):
1992!!
1993!! REFERENCE(S) :
1994!!
1995!_ ================================================================================================================================
1996SUBROUTINE forcing_just_read_tmax &
1997  & (iim, jjm, ttm, itb, ite, tmax, force_id )
1998!---------------------------------------------------------------------
1999!- iim        : Size of the grid in x
2000!- jjm        : size of the grid in y
2001!- ttm        : number of time steps in all in the forcing file
2002!- itb, ite   : index of respectively begin and end of read for each variable
2003!- tmax       : 2m air temperature (K)
2004!- force_id   : FLINCOM file id.
2005!-              It is used to close the file at the end of the run.
2006!---------------------------------------------------------------------
2007   IMPLICIT NONE
2008!-
2009   INTEGER, INTENT(in) :: iim, jjm, ttm
2010   INTEGER, INTENT(in) :: itb, ite
2011   REAL, DIMENSION(iim,jjm), INTENT(out) ::  tmax
2012   INTEGER, INTENT(in) :: force_id
2013!-
2014!---------------------------------------------------------------------
2015   CALL flinget_buffer (force_id,'Tmax'  , iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
2016   CALL forcing_zoom(data_full, tmax)
2017!-------------------------
2018END SUBROUTINE forcing_just_read_tmax
2019
2020
2021!! ==============================================================================================================================\n
2022!! SUBROUTINE   : forcing_landind
2023!!
2024!>\BRIEF       
2025!!
2026!!\n DESCRIPTION : This subroutine finds the indices of the land points over which the land
2027!!                 surface scheme is going to run.
2028!!
2029!! RECENT CHANGE(S): None
2030!!
2031!! MAIN OUTPUT VARIABLE(S):
2032!!
2033!! REFERENCE(S) :
2034!!
2035!_ ================================================================================================================================
2036SUBROUTINE forcing_landind(iim, jjm, tair, nbindex, kindex, i_test, j_test)
2037!---
2038!---
2039!---
2040  IMPLICIT NONE
2041!-
2042!- ARGUMENTS
2043!-
2044  INTEGER, INTENT(IN) :: iim, jjm
2045  REAL, INTENT(IN)    :: tair(iim,jjm)
2046  INTEGER, INTENT(OUT) :: i_test, j_test, nbindex
2047  INTEGER, INTENT(OUT) :: kindex(iim*jjm)
2048!-
2049!- LOCAL
2050  INTEGER :: i, j, ig
2051!-
2052!-
2053  ig = 0
2054  i_test = 0
2055  j_test = 0
2056!---
2057  IF (MINVAL(tair(:,:)) < 100.) THEN
2058!----- In this case the 2m temperature is in Celsius
2059     DO j=1,jjm
2060        DO i=1,iim
2061           IF (tair(i,j) < 100.) THEN
2062              ig = ig+1
2063              kindex(ig) = (j-1)*iim+i
2064              !
2065              !  Here we find at random a land-point on which we can do
2066              !  some printouts for test.
2067              !
2068              IF (ig .GT. (iim*jjm)/2 .AND. i_test .LT. 1) THEN
2069                 i_test = i
2070                 j_test = j
2071                 IF (printlev_loc >= 5) THEN
2072                    WRITE(numout,*) 'The test point chosen for output is : ', i_test, j_test
2073                 ENDIF
2074              ENDIF
2075           ENDIF
2076        ENDDO
2077     ENDDO
2078  ELSE 
2079!----- 2m temperature is in Kelvin
2080     DO j=1,jjm
2081        DO i=1,iim
2082           IF (tair(i,j) < 500.) THEN
2083              ig = ig+1
2084              kindex(ig) = (j-1)*iim+i
2085              !
2086              !  Here we find at random a land-point on which we can do
2087              !  some printouts for test.
2088              !
2089              IF (ig .GT. (iim*jjm)/2 .AND. i_test .LT. 1) THEN
2090                 i_test = i
2091                 j_test = j
2092                 IF (printlev_loc >= 5) THEN
2093                    WRITE(numout,*) 'The test point chosen for output is : ', i_test, j_test
2094                 ENDIF
2095              ENDIF
2096           ENDIF
2097        ENDDO
2098     ENDDO
2099  ENDIF
2100
2101  nbindex = ig
2102
2103END SUBROUTINE forcing_landind
2104
2105
2106!! ==============================================================================================================================\n
2107!! SUBROUTINE   : forcing_grid
2108!!
2109!>\BRIEF       
2110!!
2111!!\n DESCRIPTION : This subroutine calculates the longitudes and latitudes of the model grid.
2112!!
2113!! RECENT CHANGE(S): None
2114!!
2115!! MAIN OUTPUT VARIABLE(S):
2116!!
2117!! REFERENCE(S) :
2118!!
2119!_ ================================================================================================================================
2120SUBROUTINE forcing_grid(iim,jjm,llm,lon,lat,init_f)
2121
2122  IMPLICIT NONE
2123
2124  INTEGER, INTENT(in)                   :: iim, jjm, llm
2125  LOGICAL, INTENT(in)                   :: init_f
2126  REAL, DIMENSION(iim,jjm), INTENT(out) :: lon, lat
2127!-
2128  INTEGER :: i,j
2129!-
2130!- Should be unified one day
2131!-
2132  IF ( printlev_loc>=3 ) WRITE(numout,*) 'forcing_grid : options : ', weathergen, interpol
2133!-
2134  IF ( weathergen ) THEN
2135     IF (init_f) THEN
2136        DO i = 1, iim
2137           lon(i,:) = limit_west + merid_res/2. + &
2138                FLOAT(i-1)*(limit_east-limit_west)/FLOAT(iim)
2139        ENDDO
2140        !-
2141        DO j = 1, jjm
2142           lat(:,j) = limit_north - zonal_res/2. - &
2143                FLOAT(j-1)*(limit_north-limit_south)/FLOAT(jjm)
2144        ENDDO
2145     ELSE
2146        IF (is_root_prc) THEN
2147           DO i = 1, iim_g
2148              lon_g(i,:) = limit_west + merid_res/2. + &
2149                   FLOAT(i-1)*(limit_east-limit_west)/FLOAT(iim_g)
2150           ENDDO
2151           !-
2152           DO j = 1, jjm_g
2153              lat_g(:,j) = limit_north - zonal_res/2. - &
2154                   FLOAT(j-1)*(limit_north-limit_south)/FLOAT(jjm_g)
2155           ENDDO
2156        ENDIF
2157        CALL bcast(lon_g)
2158        CALL bcast(lat_g)
2159        lon=lon_g(:,jj_para_begin(mpi_rank):jj_para_end(mpi_rank))
2160        lat=lat_g(:,jj_para_begin(mpi_rank):jj_para_end(mpi_rank))
2161     ENDIF
2162!-
2163  ELSEIF ( interpol ) THEN
2164!-
2165    CALL forcing_zoom(lon_full, lon)
2166    IF ( printlev_loc>=3 ) WRITE(numout,*) 'forcing_grid : out of zoom on lon'
2167    CALL forcing_zoom(lat_full, lat)
2168    IF ( printlev_loc>=3 ) WRITE(numout,*) 'forcing_grid : out of zoom on lat'
2169 
2170 ELSE
2171    CALL ipslerr_p(3,'forcing_grid','Neither interpolation nor weather generator is specified.','','')
2172 ENDIF
2173 
2174 IF ( printlev_loc>=3 ) WRITE(numout,*) 'forcing_grid : ended'
2175 
2176END SUBROUTINE forcing_grid
2177
2178
2179!! ==============================================================================================================================\n
2180!! SUBROUTINE   : forcing_zoom
2181!!
2182!>\BRIEF        This subroutine extracts the region of data over which we wish to run the model.
2183!!
2184!!\n DESCRIPTION : This subroutine extracts the region of data over which we wish to run the model.
2185!!
2186!! RECENT CHANGE(S): None
2187!!
2188!! MAIN OUTPUT VARIABLE(S):
2189!!
2190!! REFERENCE(S) :
2191!!
2192!_ ================================================================================================================================
2193SUBROUTINE forcing_zoom(x_f, x_z)
2194
2195  IMPLICIT NONE
2196!-
2197  REAL, DIMENSION(iim_full, jjm_full), INTENT(IN) :: x_f
2198  REAL, DIMENSION(iim_zoom, jjm_zoom), INTENT(OUT) :: x_z
2199
2200  INTEGER :: i,j
2201!-
2202  DO i=1,iim_zoom
2203     DO j=1,jjm_zoom
2204        x_z(i,j) = x_f(i_index(i),j_index(j))
2205     ENDDO
2206  ENDDO
2207!-
2208END SUBROUTINE forcing_zoom
2209
2210
2211!! ==============================================================================================================================\n
2212!! SUBROUTINE   : forcing_vertical_ioipsl
2213!!
2214!>\BRIEF       
2215!!
2216!!\n DESCRIPTION : This subroutine explores the forcing file to decide what information is available
2217!!                 on the vertical coordinate.
2218!!
2219!! RECENT CHANGE(S): None
2220!!
2221!! MAIN OUTPUT VARIABLE(S):
2222!!
2223!! REFERENCE(S) :
2224!!
2225!_ ================================================================================================================================
2226SUBROUTINE forcing_vertical_ioipsl(force_id)
2227
2228  INTEGER, INTENT(IN) :: force_id
2229
2230  LOGICAL :: var_exists, vara_exists, varb_exists, varuv_exists
2231  LOGICAL :: foundvar
2232  LOGICAL :: levlegacy
2233
2234  !
2235  !- Set all the defaults
2236  !
2237  zfixed=.FALSE.
2238  zsigma=.FALSE.
2239  zhybrid=.FALSE.
2240  zlevels=.FALSE.
2241  zheight=.FALSE.
2242  zsamelev_uv = .TRUE.
2243  levlegacy = .FALSE.
2244  !
2245  foundvar = .FALSE.
2246  !
2247  !- We have a forcing file to explore so let us see if we find any of the conventions
2248  !- which allow us to find the height of T,Q,U and V.
2249  !
2250  IF ( force_id > 0 ) THEN
2251     !
2252     ! Case for sigma levels
2253     !
2254     IF ( .NOT. foundvar ) THEN
2255        CALL flinquery_var(force_id, 'Sigma', var_exists)
2256        CALL flinquery_var(force_id, 'Sigma_uv', varuv_exists)
2257        IF ( var_exists ) THEN
2258           foundvar = .TRUE.
2259           zsigma = .TRUE.
2260           IF ( varuv_exists ) zsamelev_uv = .FALSE.
2261        ENDIF
2262     ENDIF
2263     !
2264     ! Case for Hybrid levels
2265     !
2266     IF ( .NOT. foundvar ) THEN
2267        CALL flinquery_var(force_id, 'HybSigA', vara_exists)
2268        IF ( vara_exists ) THEN
2269           CALL flinquery_var(force_id, 'HybSigB', varb_exists)
2270           IF ( varb_exists ) THEN
2271              var_exists=.TRUE.
2272           ELSE
2273              CALL ipslerr ( 3, 'forcing_vertical_ioipsl','Missing the B coefficient for', &
2274                   &         'Hybrid vertical levels for T and Q','stop readdim2')
2275           ENDIF
2276        ENDIF
2277        CALL flinquery_var(force_id, 'HybSigA_uv', vara_exists)
2278        IF ( vara_exists ) THEN
2279           CALL flinquery_var(force_id, 'HybSigB_uv', varb_exists)
2280           IF ( varb_exists ) THEN
2281              varuv_exists=.TRUE.
2282           ELSE
2283              CALL ipslerr ( 3, 'forcing_vertical_ioipsl','Missing the B coefficient for', &
2284                   &         'Hybrid vertical levels for U and V','stop readdim2')
2285           ENDIF
2286        ENDIF
2287        IF ( var_exists ) THEN
2288           foundvar = .TRUE.
2289           zhybrid = .TRUE.
2290           IF ( varuv_exists ) zsamelev_uv = .FALSE.
2291        ENDIF
2292     ENDIF
2293     !
2294     ! Case for levels (i.e. a 2d time varying field with the height in meters)
2295     !
2296     IF ( .NOT. foundvar ) THEN
2297        CALL flinquery_var(force_id, 'Levels', var_exists)
2298        CALL flinquery_var(force_id, 'Levels_uv', varuv_exists)
2299        IF ( var_exists ) THEN
2300           foundvar = .TRUE.
2301           zlevels = .TRUE.
2302           IF ( varuv_exists ) zsamelev_uv = .FALSE.
2303        ENDIF
2304     ENDIF
2305     !
2306     ! Case where a fixed height is provided in meters
2307     !
2308     IF ( .NOT. foundvar ) THEN
2309        CALL flinquery_var(force_id, 'Height_Lev1', var_exists)
2310        CALL flinquery_var(force_id, 'Height_Levuv', varuv_exists)
2311       IF ( var_exists ) THEN
2312           foundvar = .TRUE.
2313           zheight = .TRUE.
2314           IF ( varuv_exists ) zsamelev_uv = .FALSE.
2315        ENDIF
2316     ENDIF
2317     !
2318     ! Case where a fixed height is provided in meters in the lev variable
2319     !
2320     IF ( .NOT. foundvar ) THEN
2321        CALL flinquery_var(force_id, 'lev', var_exists)
2322        IF ( var_exists ) THEN
2323           foundvar = .TRUE.
2324           zheight = .TRUE.
2325           levlegacy = .TRUE.
2326        ENDIF
2327     ENDIF
2328     !
2329  ENDIF
2330  !
2331  ! We found forcing variables so we need to extract the values if we are dealing with constant values (i.e. all
2332  ! except the case zlevels
2333  !
2334  IF ( foundvar .AND. .NOT. zlevels ) THEN
2335     !
2336     IF ( zheight ) THEN
2337        !
2338        ! Constant height
2339        !
2340        IF ( levlegacy ) THEN
2341           CALL flinget (force_id,'lev',1, 1, 1, 1,  1, 1, zlev_fixed)
2342        ELSE
2343           CALL flinget (force_id,'Height_Lev1',1, 1, 1, 1,  1, 1, zlev_fixed)
2344           IF ( .NOT. zsamelev_uv ) THEN
2345              CALL flinget (force_id,'Height_Levuv',1, 1, 1, 1,  1, 1, zlevuv_fixed)
2346           ENDIF
2347        ENDIF
2348        IF (printlev_loc >= 1) WRITE(numout,*) "forcing_vertical_ioipsl : case ZLEV : Read from forcing file :", &
2349             zlev_fixed, zlevuv_fixed
2350        !
2351     ELSE IF ( zsigma .OR. zhybrid ) THEN
2352        !
2353        ! Sigma or hybrid levels
2354        !
2355        IF ( zsigma ) THEN
2356           CALL flinget (force_id,'Sigma',1, 1, 1, 1,  1, 1, zhybrid_b)
2357           zhybrid_a = zero
2358           IF ( .NOT. zsamelev_uv ) THEN
2359              CALL flinget (force_id,'Sigma_uv',1, 1, 1, 1,  1, 1, zhybriduv_b)
2360              zhybriduv_a = zero
2361           ENDIF
2362        ELSE
2363           CALL flinget (force_id,'HybSigB',1, 1, 1, 1,  1, 1, zhybrid_b)
2364           CALL flinget (force_id,'HybSigA',1, 1, 1, 1,  1, 1, zhybrid_a)
2365           IF ( .NOT. zsamelev_uv ) THEN
2366              CALL flinget (force_id,'HybSigB_uv',1, 1, 1, 1,  1, 1, zhybriduv_b)
2367              CALL flinget (force_id,'HybSigA_uv',1, 1, 1, 1,  1, 1, zhybriduv_a)
2368           ENDIF
2369        ENDIF
2370        IF (printlev_loc >= 1) WRITE(numout,*) "forcing_vertical_ioipsl : case Pressure coordinates : "
2371        IF (printlev_loc >= 1) WRITE(numout,*) "Read from forcing file :", zhybrid_b, zhybrid_a, zhybriduv_b, zhybriduv_a
2372     ELSE
2373        !
2374        ! Why are we here ???
2375        !
2376        CALL ipslerr ( 3, 'forcing_vertical_ioipsl','What is the option used to describe the height of', &
2377             &         'the atmospheric forcing ?','Please check your forcing file.')
2378     ENDIF
2379  ENDIF
2380  !
2381  !- We have no forcing file to explore or we did not find anything. So revert back to the run.def and
2382  !- read what has been specified by the user.
2383  !
2384  IF ( force_id < 0 .OR. .NOT. foundvar ) THEN
2385     !
2386     !-
2387     !Config Key   = HEIGHT_LEV1
2388     !Config Desc  = Height at which T and Q are given
2389     !Config Def   = 2.0
2390     !Config If    = offline mode
2391     !Config Help  = The atmospheric variables (temperature and specific
2392     !Config         humidity) are measured at a specific level.
2393     !Config         The height of this level is needed to compute
2394     !Config         correctly the turbulent transfer coefficients.
2395     !Config         Look at the description of the forcing
2396     !Config         DATA for the correct value.
2397     !Config Units = [m]
2398     !-
2399     zlev_fixed = 2.0
2400     CALL getin('HEIGHT_LEV1', zlev_fixed)
2401
2402     !-
2403     !Config Key  = HEIGHT_LEVW
2404     !Config Desc = Height at which the wind is given
2405     !Config Def  = 10.0
2406     !Config If   = offline mode
2407     !Config Help = The height at which wind is needed to compute
2408     !Config        correctly the turbulent transfer coefficients.
2409     !Config Units= [m]
2410     !-
2411     zlevuv_fixed = 10.0
2412     CALL getin('HEIGHT_LEVW', zlevuv_fixed)
2413
2414     zheight = .TRUE.
2415
2416     IF ( ABS(zlevuv_fixed-zlev_fixed) > EPSILON(zlev_fixed)) THEN
2417        zsamelev_uv = .FALSE.
2418     ELSE
2419        zsamelev_uv = .TRUE.
2420     ENDIF
2421
2422     CALL ipslerr ( 2, 'forcing_vertical_ioipsl','The height of the atmospheric forcing variables', &
2423          &         'was not found in the netCDF file.','Thus the values in run.def were used ... or their defaults.')
2424  ENDIF
2425
2426END SUBROUTINE forcing_vertical_ioipsl
2427
2428
2429!! ==============================================================================================================================\n
2430!! SUBROUTINE   : domain_size
2431!!
2432!>\BRIEF       
2433!!
2434!!\n DESCRIPTION :
2435!!
2436!! RECENT CHANGE(S): None
2437!!
2438!! MAIN OUTPUT VARIABLE(S):
2439!!
2440!! REFERENCE(S) :
2441!!
2442!_ ================================================================================================================================
2443SUBROUTINE domain_size (limit_west, limit_east, limit_north, limit_south, &
2444     &  iim_f, jjm_f, lon, lat, iim, jjm, iind, jind)
2445 
2446  IMPLICIT NONE
2447  !
2448  ! ARGUMENTS
2449  !
2450  REAL, INTENT(inout)  :: limit_west,limit_east,limit_north,limit_south
2451  INTEGER, INTENT(in)  :: iim_f, jjm_f
2452  REAL, INTENT(in)     :: lon(iim_f, jjm_f), lat(iim_f, jjm_f)
2453  INTEGER, INTENT(out) :: iim,jjm
2454  INTEGER, INTENT(out) :: iind(iim_f), jind(jjm_f)
2455  !
2456  ! LOCAL
2457  !
2458  INTEGER :: i, j
2459  REAL :: lolo
2460  LOGICAL :: over_dateline = .FALSE.
2461  !
2462  !
2463  IF ( ( ABS(limit_east) .GT. 180. ) .OR. &
2464       ( ABS(limit_west) .GT. 180. ) ) THEN
2465     WRITE(numout,*) 'Limites Ouest, Est: ',limit_west,limit_east
2466     CALL ipslerr_p (3,'domain_size', &
2467 &        'Longitudes problem.','In run.def file :', &
2468 &        'limit_east > 180. or limit_west > 180.')
2469  ENDIF
2470  !
2471  IF ( limit_west .GT. limit_east ) over_dateline = .TRUE.
2472  !
2473  IF ( ( limit_south .LT. -90. ) .OR. &
2474       ( limit_north .GT. 90. ) .OR. &
2475       ( limit_south .GE. limit_north ) ) THEN
2476     WRITE(numout,*) 'Limites Nord, Sud: ',limit_north,limit_south
2477     CALL ipslerr_p (3,'domain_size', &
2478 &        'Latitudes problem.','In run.def file :', &
2479 &        'limit_south < -90. or limit_north > 90. or limit_south >= limit_north')
2480  ENDIF
2481  !
2482  ! Here we assume that the grid of the forcing data is regular. Else we would have
2483  ! to do more work to find the index table.
2484  !
2485  iim = 0
2486  DO i=1,iim_f
2487     !
2488     lolo =  lon(i,1)
2489     IF ( lon(i,1) .GT. 180. ) lolo =  lon(i,1) - 360.
2490     IF ( lon(i,1) .LT. -180. ) lolo =  lon(i,1) + 360.
2491     !
2492     IF (lon(i,1) < limit_west) iim_g_begin = i+1
2493     IF (lon(i,1) < limit_east) iim_g_end = i
2494     !
2495     IF ( over_dateline ) THEN
2496        IF ( lolo .LE. limit_west .OR. lolo .GE. limit_east ) THEN
2497           iim = iim + 1
2498           iind(iim) = i
2499        ENDIF
2500     ELSE
2501        IF ( lolo .GE. limit_west .AND. lolo .LE. limit_east ) THEN
2502           iim = iim + 1
2503           iind(iim) = i
2504        ENDIF
2505     ENDIF
2506     !
2507  ENDDO
2508  !
2509  jjm = 0
2510  DO j=1,jjm_f
2511     IF (lat(1,j) > limit_north) jjm_g_begin = j+1
2512     IF (lat(1,j) > limit_south) jjm_g_end = j
2513     !
2514     IF ( lat(1,j) .GE. limit_south .AND. lat(1,j) .LE. limit_north) THEN
2515        jjm = jjm + 1
2516        jind(jjm) = j
2517     ENDIF
2518  ENDDO
2519
2520  IF (printlev_loc >= 1) WRITE(numout,*) 'Domain zoom size: iim, jjm = ', iim, jjm
2521
2522  END SUBROUTINE domain_size
2523
2524
2525!! ==============================================================================================================================\n
2526!! SUBROUTINE   : flinget_buffer
2527!!
2528!>\BRIEF       
2529!!
2530!!\n DESCRIPTION :  This subroutine is a wrap of flinget/IOIPSL. The arguments are the same.
2531!!                  flinget_buffer will call flinget and buffer the forcing data localy in this subroutine.
2532!!                  According to the variable NBUFF set in run.def, several time steps can be read at the same time
2533!!                  from the forcing file. If NBUFF=0, the full forcing file is read.
2534!!                  The output, data_full, from this subroutine is always only one time step of corresponding to itb.
2535!!                  itb must be equal to ite.
2536!!
2537!! RECENT CHANGE(S): None
2538!!
2539!! MAIN OUTPUT VARIABLE(S):
2540!!
2541!! REFERENCE(S) :
2542!!
2543!_ ================================================================================================================================
2544  SUBROUTINE flinget_buffer(force_id, varname, iim_full, jjm_full, llm_full, ttm, itb, ite, data_full)
2545   
2546    !! Input arguments
2547    INTEGER, INTENT(in)          :: force_id                      !! Id for forcing file
2548    CHARACTER(len=*), INTENT(in) :: varname                       !! Name of current variable to be read
2549    INTEGER, INTENT(in)          :: iim_full, jjm_full, llm_full  !! Horizontal and vertical domaine
2550    INTEGER, INTENT(in)          :: ttm                           !! Full lenght of forcing file
2551    INTEGER, INTENT(in)          :: itb, ite                      !! Time step to be read from forcing file. itb must be equal to ite
2552
2553    !! Output argument
2554    REAL, DIMENSION(iim_full, jjm_full), INTENT(out) :: data_full !! Data for time step itb.
2555
2556    !! Define specific type to buffer data together with name and index
2557    TYPE buffer_type
2558       CHARACTER(len=20) :: name                   !! Name of variable in forcing file
2559       INTEGER :: istart                           !! Start index of current buffered data
2560       INTEGER :: iend                             !! End index of current buffered data
2561       REAL, ALLOCATABLE, DIMENSION(:,:,:) :: data !! Data read from forcing file for intervall [istart,iend]
2562    END TYPE buffer_type
2563   
2564    !! Local variables
2565    INTEGER, PARAMETER :: maxvar=20                          !! Max number of variables to be buffered
2566    TYPE(buffer_type), DIMENSION(maxvar),SAVE :: data_buffer !! Containing all variables and the current buffered data
2567    INTEGER, SAVE   :: nbuff                                 !! Number of time steps to be buffered
2568    INTEGER, SAVE   :: lastindex=0                           !! Current number of variables stored in data_buffer
2569    INTEGER, SAVE   :: ttm0                                  !! Time lenght of forcing file, stored for test purpose
2570    LOGICAL, SAVE   :: first=.TRUE.                          !! First call to this subroutine
2571    INTEGER         :: index                                 !! Index in data_buffer for current variable
2572    INTEGER         :: i, ierr                               !! Loop and error variables
2573    INTEGER         :: nbuff_new                             !! Temporary variable for nbuff used in the end of the forcing file
2574   
2575    !! 1. Initialization
2576    IF (first) THEN
2577       data_buffer(:)%name='undef'
2578       ! Read NBUFF from run.def
2579       ! Note that getin_p is not used because this subroutine might be called only by master process
2580
2581       !Config Key  = NBUFF
2582       !Config Desc = Number of time steps of data to buffer between each reading of the forcing file
2583       !Config If   = OFF_LINE
2584       !Config Help = The full simulation time length will be read if NBUFF equal 0.
2585       !Config        NBUFF > 1 can be used for smaller regions or site simulations only.
2586       !Config Def  = 1
2587       !Config Units= -
2588
2589       nbuff=1
2590       CALL getin('NBUFF', nbuff)
2591
2592       IF (nbuff == 0 .OR. nbuff >ttm) THEN
2593          ! Set nbuff as the full forcing file lenght
2594          nbuff=ttm
2595       ELSE IF (nbuff < 0) THEN
2596          ! Negativ nbuff not possible
2597          CALL ipslerr_p(3,'flinget_buffer','NBUFF must be a positiv number','Set NBUFF=0 for full simulation lenght','')
2598       END IF
2599       IF (printlev_loc >= 1) WRITE(numout,*)'flinget_buffer: NBUFF=',nbuff,' number of time step will be buffered'
2600       IF (printlev_loc >= 1) WRITE(numout,*)'flinget_buffer: Choose a lower value for NBUFF if problem with memory'
2601       
2602       ! Save dimensions to check following timesteps
2603       ! ttm is the full lenght of forcing file
2604       ttm0=ttm
2605       
2606       first=.FALSE.
2607    END IF
2608
2609    !! 2. Coeherence tests on input arguments
2610    IF (ttm /= ttm0) THEN
2611       WRITE(numout,*)'Problem with ttm=',ttm,' ttm0=',ttm0
2612       CALL ipslerr_p(3,'flinget_buffer','Error with ttm and ttm0','','')
2613    END IF
2614    IF (itb /= ite) THEN
2615       WRITE(numout,*) 'There is a problem. Why is itb not equal ite ?'
2616       WRITE(numout,*) 'itb=',itb,' ite=',ite,' varname=',varname
2617       CALL ipslerr_p(3,'flinget_buffer','ite not equal itb','','')
2618    END IF
2619
2620
2621    !! 3. Find index for current variable
2622    index=0
2623    DO i=1, maxvar
2624       IF ( trim(varname) == data_buffer(i)%name ) THEN
2625          index=i
2626          CYCLE
2627       END IF
2628    END DO
2629   
2630    !! 4. Initialize and allocate if necesary the current variable
2631    IF ( index == 0 ) THEN
2632       ! The variable was not found
2633       ! This must be the first time for current variable
2634       index=lastindex+1
2635       lastindex=index
2636       IF (index > maxvar) CALL ipslerr_p(3,'flinget_buffer','to many variables','maxvar is too small','')
2637       
2638       ! Initialize the data_buffer for this index
2639       data_buffer(index)%name=trim(varname)
2640       ALLOCATE(data_buffer(index)%data(iim_full,jjm_full,nbuff),stat=ierr)
2641       IF (ierr /= 0) CALL ipslerr_p(3,'flinget_buffer','pb alloc data_buffer%data','for variable=',varname)
2642       data_buffer(index)%istart=0
2643       data_buffer(index)%iend=0
2644    END IF
2645   
2646   
2647    !! 5. Call flinget if current time step (itb) is outside the buffered intervall
2648    IF (( itb > data_buffer(index)%iend ) .OR. ( itb < data_buffer(index)%istart )) THEN
2649       ! itb is not in the time slice previously read or it is the first time to read
2650       ! Reading of forcing file will now be done
2651       ! First recalculate index to be read
2652       data_buffer(index)%istart = itb
2653       data_buffer(index)%iend   = itb + nbuff - 1
2654       
2655       ! Check and correct if data_buffer(index)%iend is exceeding file size
2656       IF (data_buffer(index)%iend > ttm) THEN
2657          ! iend is exceeding the limit of the file. Change iend to the last time step in the file.
2658          data_buffer(index)%iend = ttm
2659
2660          ! Calculate a new smaller nbuff
2661          nbuff_new = ttm - itb + 1
2662
2663          ! Resize data buffer
2664          DEALLOCATE(data_buffer(index)%data)
2665          ALLOCATE(data_buffer(index)%data(iim_full,jjm_full, nbuff_new), stat=ierr )
2666          IF (ierr /= 0) CALL ipslerr_p(3,'flinget_buffer','pb realloc data_buffer%data with new nbuff','','')
2667       END IF
2668
2669!       WRITE(numout,*) 'Now do flinget for ',varname,', itb=',itb,', istart=',&
2670!            data_buffer(index)%istart,', iend=',data_buffer(index)%iend
2671       CALL flinget (force_id,varname, iim_full, jjm_full, llm_full, ttm, data_buffer(index)%istart, &
2672            data_buffer(index)%iend, data_buffer(index)%data(:,:,:))
2673    END IF
2674   
2675    !! 6. Initialize the output variable with data from buffered variable
2676    ! Find index for the time step corrsponding to itb in the time slice previously read from forcing file
2677    i=itb-data_buffer(index)%istart+1
2678    ! Initialize output variable
2679    data_full(:,:) = data_buffer(index)%data(:,:,i)
2680   
2681   
2682  END SUBROUTINE flinget_buffer
2683
2684END MODULE readdim2
Note: See TracBrowser for help on using the repository browser.