source: branches/publications/ORCHIDEE-ICE_SurfaceMassBalance/src_driver/weather.f90 @ 8398

Last change on this file since 8398 was 4195, checked in by josefine.ghattas, 7 years ago

Fix errors seen with specific debug compile options. See ticket #204

  1. Jornet-Puig
File size: 122.1 KB
Line 
1! =================================================================================================================================
2! MODULE       : weather
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.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 simulates weather.
10!!
11!!\n DESCRIPTION: None
12!!
13!! RECENT CHANGE(S): None
14!!
15!! REFERENCE(S) :
16!!
17!! SVN          :
18!! $HeadURL: $
19!! $Date: $
20!! $Revision: $
21!! \n
22!_ ================================================================================================================================
23
24MODULE weather
25
26  USE netcdf
27!-
28  USE defprec
29  USE ioipsl_para
30  USE constantes
31  USE mod_orchidee_para
32
33  USE solar
34  USE grid, ONLY : year,month,day,sec
35!-
36  IMPLICIT NONE
37!-
38  PRIVATE
39  PUBLIC weathgen_main, weathgen_domain_size, weathgen_init, weathgen_read_file, weathgen_qsat_2d
40!
41! Only for root proc
42  INTEGER, SAVE                              :: iim_file, jjm_file, llm_file, ttm_file !(unitless)
43  INTEGER,DIMENSION(:,:),SAVE,ALLOCATABLE    :: ncorr !(unitless)
44  INTEGER,DIMENSION(:,:,:),SAVE,ALLOCATABLE  :: icorr,jcorr !(unitless)
45  INTEGER,SAVE                               :: i_cut, n_agg !(unitless)
46
47  REAL,DIMENSION(:,:),SAVE,ALLOCATABLE :: xinwet   !! climatological wet days + anomaly @tex $(days.month^{-1})$ @endtex
48  REAL,DIMENSION(:,:),SAVE,ALLOCATABLE :: xinprec  !! climatological precipition + anomaly @tex $(mm.day^{-1})$ @endtex
49  REAL,DIMENSION(:,:),SAVE,ALLOCATABLE :: xint     !! climatological temp + anomaly (C)
50  REAL,DIMENSION(:,:),SAVE,ALLOCATABLE :: xinq     !! climatological relative humidity + anomaly (0-1, unitless)
51  REAL,DIMENSION(:,:),SAVE,ALLOCATABLE :: xinwind  !! climatological wind speed + anomaly @tex $(m.s^{-1})$ @endtex
52  REAL,DIMENSION(:,:),SAVE,ALLOCATABLE :: xincld   !! climatological cloudiness + anomaly (0-1, unitless)
53  REAL,DIMENSION(:,:),SAVE,ALLOCATABLE :: xintrng  !! climatological temp range + anomaly (C)
54  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: xintopo  !! topography (m)
55  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: lat_land !! latitudes of land points (unitless)
56!-
57! daily values
58!-
59  REAL,SAVE :: julian_last
60  INTEGER,DIMENSION(:),SAVE,ALLOCATABLE :: iwet    !! flag for wet day / dry day (0-1, unitless)
61!-
62! today's values (m0 means "minus 0")
63!-
64  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: psurfm0  !! surface pressure today(Pa)
65  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: cloudm0  !! cloud fraction today (0-1, unitless)
66  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: tmaxm0   !! maximum daily temperature today (K)
67  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: tminm0   !! minimum daily temperature today (K)
68  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: qdm0     !! daily average specific humidity today (kg_h2o/kg_air)
69  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: udm0     !! daily average wind speed today  @tex $(m.s^{-1})$ @endtex
70  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: precipm0 !! daily precitation today @tex $(mm.day^{-1})$ @endtex
71!-
72! yesterday's values (m1 means "minus 1")
73!-
74  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: psurfm1  !! surface pressure yesterday (Pa)
75  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: cloudm1  !! cloud fraction yesterday (0-1, unitless)
76  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: tmaxm1   !! maximum daily temperature yesterday (K)
77  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: tminm1   !! minimum daily temperature yesterday (K)
78  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: qdm1     !! daily average specific humidity yesterday (kg_h2o/kg_air)
79  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: udm1     !! daily average wind speed  yesterday  @tex $(m.s^{-1})$ @endtex
80  REAL,DIMENSION(:),SAVE,ALLOCATABLE   :: precipm1 !! daily precitation  yesterday @tex $(mm.day^{-1})$ @endtex
81!-
82! other
83!-
84  INTEGER,SAVE                  :: ipprec        !! statistical (0) or prescribed (1) daily values
85
86  LOGICAL,SAVE                  :: precip_exact  !! respect monthly precipitation
87  INTEGER,DIMENSION(31,12),SAVE :: jour_precip
88
89
90  INTEGER,PARAMETER      :: seedsize_max = 300  !! max size of random seed
91  LOGICAL,SAVE           :: dump_weather
92  CHARACTER(LEN=20),SAVE :: dump_weather_file
93  LOGICAL,SAVE           :: gathered
94  INTEGER,SAVE           :: dump_id
95
96!
97  REAL,PARAMETER         :: zero_t=273.15   !! Absolute zero
98!
99  REAL,PARAMETER :: pir = pi/180.
100  REAL,PARAMETER :: rair = 287.
101!-
102  INTEGER,PARAMETER :: nmon = 12  !! Number of months
103
104!
105  CHARACTER(LEN=3),DIMENSION(12) :: cal = &             !! Months of the year (unitless)
106 &  (/ 'JAN','FEB','MAR','APR','MAY','JUN', &
107 &     'JUL','AUG','SEP','OCT','NOV','DEC' /)
108  INTEGER,DIMENSION(12),SAVE :: ndaypm = &              !! Number of days per month (noleap year) (unitless)
109 &  (/ 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31 /)
110  INTEGER,SAVE :: soldownid, rainfid, snowfid, lwradid, &
111 &                tairid, qairid,  psolid, uid, vid, &
112 &                time_id, timestp_id
113!-
114  INTEGER,SAVE :: n_rtp = nf90_real4      !! Parameters for NETCDF
115!-
116  INTEGER  :: ALLOC_ERR                   !! Flag for dynamic allocations
117!-
118  CHARACTER(LEN=20),SAVE :: calendar_str   !! Calendar type
119!-
120  INTEGER, DIMENSION(:), ALLOCATABLE, SAVE :: kindex_w  !! Land points index
121  INTEGER, SAVE                            :: nbindex_w  !! Land points index
122!-
123  INTEGER, PARAMETER :: termcol = 100     !! Plot of projection file => grid, number of column on terminal
124!80
125  CONTAINS
126!-
127!===
128!-
129
130!! ================================================================================================================================
131!! SUBROUTINE   : daily
132!!
133!>\BRIEF          This routine generates daily weather conditions from monthly-mean
134!! climatic parameters.
135!!
136!! DESCRIPTION  :  Specifically, this routine generates daily values of
137!!                 - daily total precipitation \n
138!!                 - daily maximum temperature \n
139!!                 - daily minimum temperature \n
140!!                 - daily average cloud cover \n
141!!                 - daily average relative humidity \n
142!!                 - daily average wind speed \n
143!!                 In order to generate daily weather conditions, the model uses
144!!                 a series of 'weather generator' approaches,
145!!                 which generate random combinations of weather conditions
146!!                 based upon the climatological conditions in general. \n
147!!                 This weather generator is based upon the so-called Richardson
148!!                 weather generator. \n
149!!
150!! RECENT CHANGE(S): None
151!!
152!! MAIN OUTPUT VARIABLE(S): ::psurf, ::cloud, ::tmax, ::tmin, ::qd, ::ud, ::precip
153!!
154!! REFERENCE(S) :
155!! -  Geng, S., F.W.T. Penning de Vries, and L. Supit, 1985:  A simple
156!! method for generating rainfall data, Agricultural and Forest
157!! Meteorology, 36, 363-376.
158!! -  Richardson, C. W. and Wright, D. A., 1984: WGEN: A model for
159!! generating daily weather variables: U. S. Department of
160!! Agriculture, Agricultural Research Service.
161!! - Richardson, C., 1981: Stochastic simulation of daily
162!! precipitation, temperature, and solar radiation. Water Resources
163!! Research 17, 182-190.
164!!
165!! FLOWCHART    : None
166!! \n
167!_ ================================================================================================================================
168
169SUBROUTINE daily &
170 &  (npoi, imonth, iday, cloud, tmax, tmin, precip, qd, ud, psurf)
171
172!-
173! in & out: global variables
174!-
175
176! INTEGER,INTENT(INOUT):: iwet(npoi) !! wet day / dry day flag!*
177!-
178
179  !! 0. Parameters and variables declaration
180
181  REAL,PARAMETER :: rair = 287.     !! Molecular weight of one mole of dry air @tex $(g.mol{-1})$ @endtex
182  REAL,PARAMETER :: grav = 9.81     !! Acceleration of the gravity @tex $(m.s^{-2})$ @endtex
183  REAL,PARAMETER :: pi = 3.1415927  !! pi
184
185  !! 0.1 Input variables
186
187  INTEGER,INTENT(IN) :: npoi         !! total number of land points
188  INTEGER,INTENT(IN) :: imonth, iday
189
190  !! 0.2 Output variables
191
192  REAL,INTENT(OUT) :: psurf(npoi)   !! surface pressure (Pa)
193  REAL,INTENT(OUT) :: cloud(npoi)   !! cloud fraction (0-1, unitless)
194  REAL,INTENT(OUT) :: tmax(npoi)    !! maximum daily temperature (K)
195  REAL,INTENT(OUT) :: tmin(npoi)    !! minimum daily temperature (K)
196  REAL,INTENT(OUT) :: qd(npoi)      !! daily average specific humidity (kg_h2o/kg_air)
197  REAL,INTENT(OUT) :: ud(npoi)      !! daily average wind speed  @tex $(m.s^{-1})$ @endtex
198  REAL,INTENT(OUT) :: precip(npoi)  !! daily precitation @tex $(mm.day^{-1})$ @endtex
199
200  !! 0.4 Local variables
201
202  REAL :: td(npoi)                                 !! daily average temperature (K)
203  REAL,allocatable,save,dimension(:,:) ::  xstore  !! weather generator 'memory' matrix
204  REAL :: ee(3), r(3), rr(npoi,3)
205  REAL :: alpha(npoi), rndnum, pwd, pww
206  REAL :: beta(npoi)
207  REAL :: pwet(npoi)
208  REAL :: rwork
209  REAL :: omcloud, omqd, omtmax
210  REAL :: cloudm, cloudw, cloudd
211  REAL :: cloude(npoi), clouds(npoi)
212  REAL :: tmaxd, tmaxw, tmaxm
213  REAL :: tminm
214  REAL :: tmins(npoi), tmaxs(npoi)
215  REAL :: tmine(npoi), tmaxe(npoi)
216  REAL :: qdm(npoi),qdd(npoi),qde(npoi),qdw(npoi),qdup(npoi),qdlow(npoi)
217  INTEGER :: i,j,k
218  REAL :: amn,b1,b2,b3,eud,rn,rn1,rn2,rn3,rn4,s1,s2,s12,x1,y, z(npoi)
219  REAL :: aa(npoi),ab(npoi),tr1(npoi), tr2(npoi)
220  REAL :: tdm,trngm,tdum
221  REAL :: qsattd(npoi)
222  INTEGER :: it1w, it2w
223  REAL :: dt
224  REAL :: rainpwd(npoi)
225  INTEGER :: not_ok(npoi)
226  INTEGER :: count_not_ok,count_not_ok_g
227  LOGICAL,SAVE :: lstep_init_daily = .TRUE.
228  INTEGER,save :: npoi0
229  REAL :: xx
230  REAL, DIMENSION(3,3) :: a,b              !! define autocorrelation matrices for Richardson generator
231                                           !!
232                                           !! note that this matrix should be based upon a statistical
233                                           !! analysis of regional weather patterns
234                                           !!
235                                           !! for global simulations, we use 'nominal' values
236
237  LOGICAL :: Warning_aa_ab(npoi), Warning_iwet(npoi) !! Warnings
238!---------------------------------------------------------------------
239!-
240! initial setup for daily climate calculations
241!-
242  a(1,:) = (/ 0.600,  0.500,  0.005 /)
243  a(2,:) = (/ 0.010,  0.250,  0.005 /)
244  a(3,:) = (/ 0.020,  0.125,  0.250 /)
245!-
246  b(1,:) = (/ 0.500,  0.250, -0.250 /)
247  b(2,:) = (/ 0.000,  0.500,  0.250 /)
248  b(3,:) = (/ 0.000,  0.000,  0.500 /)
249!-
250! GK240100
251  IF (lstep_init_daily) THEN
252    lstep_init_daily = .FALSE.
253    ALLOC_ERR=-1
254    ALLOCATE(xstore(npoi,3), STAT=ALLOC_ERR)
255    IF (ALLOC_ERR/=0) THEN
256      WRITE(numout,*) "ERROR IN ALLOCATION of xstore : ",ALLOC_ERR
257      STOP
258    ENDIF
259    xstore(:,:) = zero
260    npoi0 = npoi
261  ELSE IF (npoi /= npoi0) THEN
262    WRITE(numout,*) 'Domain size old, new: ',npoi0,npoi
263    STOP 'WG Daily: Problem: Domain has changed since last call'
264  ENDIF
265!-
266! define working variables
267!-
268  rwork = (cte_grav/rair/0.0065)
269!-
270! 'omega' parameters used to calculate differences in expected
271! climatic parameters on wet and dry days
272!
273! following logic of weather generator used in the EPIC crop model
274!
275! omcloud -- cloud cover
276! omqd    -- humidity
277! omtmax  -- maximum temperature
278!-
279  omcloud = 0.90    ! originally 0.90
280  omqd    = 0.50    ! originally 0.50
281  omtmax  = 0.75    ! originally 0.75
282!-
283! calculate weighting factors used in interpolating climatological
284! monthly-mean input values to daily-mean values
285!-
286! this is a simple linear interpolation technique that takes into
287! account the length of each month
288!-
289  IF (ipprec == 0) THEN
290    IF (REAL(iday) < REAL(ndaypm(imonth)+1)/2.0) then
291      it1w = imonth-1
292      it2w = imonth
293      dt   = (REAL(iday)-0.5)/ndaypm(imonth)+0.5
294    ELSE
295      it1w = imonth
296      it2w = imonth+1
297      dt   = (REAL(iday)-0.5)/ndaypm(imonth)-0.5
298    ENDIF
299    if (it1w <  1)  it1w = 12
300    if (it2w > 12)  it2w = 1
301  ELSE
302     dt = -1.
303     it1w = -1
304     it2w = -1
305  ENDIF
306!-
307  IF (ipprec == 0) THEN
308!---
309!-- use weather generator to create daily statistics
310!---
311! (1) determine if today will rain or not
312!---
313!-- calculate monthly-average probability of rainy day
314!---
315    DO i=1,npoi
316      pwet(i) = xinwet(i,imonth)/ndaypm(imonth)
317    ENDDO
318!---
319    IF (.NOT.precip_exact) THEN
320!-----
321!---- (1.1) following Geng et al.
322!-----
323      IF (is_root_prc) THEN
324         CALL random_number (rndnum)
325      ENDIF
326      CALL bcast(rndnum)
327!-----
328      DO i=1,npoi
329        IF (xinprec(i,imonth) > 1.e-6) THEN
330!---------
331!-------- implement simple first-order Markov-chain precipitation
332!-------- generator logic based on Geng et al. (1986),
333!-------- Richardson and Wright (1984), and Richardson (1981)
334!---------
335!-------- basically, this allows for the probability of today being
336!-------- a wet day (a day with measureable precipitation)
337!-------- to be a function of what yesterday was (wet or dry)
338!---------
339!-------- the logic here is that it is more likely that a wet day
340!-------- will follow another wet day -- allowing
341!-------- for 'storm events' to persist
342!---------
343!-------- estimate the probability of a wet day after a dry day
344!---------
345          pwd = 0.75*pwet(i)
346!---------
347!-------- estimate the probability of a wet day after a wet day
348!---------
349          pww = 0.25+pwd
350!---------
351!-------- decide if today is a wet day or a dry day
352!-------- using a random number
353!---------
354!-------- call random_number(rndnum) ! done before
355!---------
356          IF (iwet(i) == 0) then
357            IF (rndnum <= pwd) iwet(i) = 1
358          ELSE
359            IF (rndnum > pww) iwet(i) = 0
360          ENDIF
361        ELSE
362          iwet(i) = 0
363        ENDIF
364      ENDDO
365    ELSE
366!-----
367!---- (1.2) preserving the monthly number of precip days
368!----       and monthly precip
369!-----
370      DO i=1,npoi
371        IF (ABS(xinwet(i,imonth)) < 32.) THEN
372          IF (xinprec(i,imonth) > 1.e-6) THEN
373            IF (   jour_precip(iday,imonth) &
374 &              <= NINT(MAX(1.,xinwet(i,imonth))) ) THEN
375              iwet(i) = 1
376            ELSE
377              iwet(i) = 0
378            ENDIF
379          ELSE
380           iwet(i) = 0
381          ENDIF
382        ENDIF
383      ENDDO
384    ENDIF
385!---
386!-- (2) determine today's precipitation amount
387!---
388    IF (.not.precip_exact) THEN
389       Warning_aa_ab(:)=.FALSE.
390       Warning_iwet(:)=.FALSE.
391!-----
392!---- (2.1) following Geng et al.
393!-----
394      aa(:) = zero
395      ab(:) = zero
396      tr2(:)= zero
397      tr1(:)= zero
398      beta(:) = un
399      DO i=1,npoi
400!-------
401!------ initialize daily precipitation to zero
402!-------
403        precip(i) = zero
404!-------
405        IF (xinprec(i,imonth) > 1.e-6) THEN
406!---------
407!-------- if it is going to rain today
408!---------
409          IF (iwet(i) == 1) THEN
410!-----------
411!---------- calculate average rainfall per wet day
412!-----------
413            rainpwd(i) = xinprec(i,imonth) &
414 &                      *ndaypm(imonth)/MAX(0.1,xinwet(i,imonth))
415!-----------
416!---------- randomly select a daily rainfall amount
417!---------- from a probability density function of rainfall
418!----------
419!---------- method i --
420!-----------
421!---------- use the following technique from Geng et al. and Richardson
422!---------- to distribute rainfall probabilities
423!-----------
424!---------- pick a random rainfall amount
425!---------- from a two-parameter gamma function distribution function
426!-----------
427!---------- estimate two parameters for gamma function
428!---------- (following Geng et al.)
429!-----------
430            beta(i) = MAX(1.0,-2.16+1.83*rainpwd(i))
431            alpha(i) = rainpwd(i)/beta(i)
432!-----------
433!---------- determine daily precipitation amount
434!---------- from gamma distribution function
435!---------- (following WGEN code of Richardson and Wright (1984))
436!-----------
437            IF (ABS(1.-alpha(i)) < 1.e-6) THEN
438              alpha(i) = 1.e-6*(alpha(i)/ABS(alpha(i)))
439            ENDIF
440            aa(i) = 1.0/alpha(i)
441            ab(i) = 1.0/(1.0-alpha(i))
442!-----------
443            IF ( (ABS(aa(i)) < 1.e-6) .OR. (ABS(ab(i)) < 1.e-6) ) THEN
444               Warning_aa_ab(:)=.TRUE.
445            ENDIF
446            tr1(i) = exp(-18.42/aa(i))
447            tr2(i) = exp(-18.42/ab(i))
448          ENDIF
449        ELSE
450          IF (iwet(i) == 1) THEN
451            Warning_iwet(i)=.TRUE.
452          ENDIF
453        ENDIF
454      ENDDO
455
456      DO i=1,npoi
457         IF ( Warning_aa_ab(i) ) THEN
458            WRITE(numout,*) ' ATTENTION, aa ou ab:'
459            WRITE(numout,*) ' aa, ab = ',aa(i),ab(i)
460            WRITE(numout,*) '   alpha, rainpwd, beta =', &
461 &                       alpha(i),rainpwd(i),beta(i)
462         ENDIF
463         IF ( Warning_iwet(i) ) THEN
464            WRITE(numout,*) ' ATTENTION, iwet = 1 alors que xinprec = 0)'
465            WRITE(numout,*) '   xinprec, iwet = ',xinprec(i,imonth),iwet(i)
466          ENDIF
467      ENDDO
468!-----
469      where ( iwet(:) == 1 )
470        not_ok(:) = 1
471      elsewhere
472        not_ok(:) = 0
473      endwhere
474!-----
475      count_not_ok_g=0
476      count_not_ok=SUM(not_ok(:))
477      CALL reduce_sum(count_not_ok,count_not_ok_g)
478      CALL bcast(count_not_ok_g)
479!-
480      z(:) = zero
481      DO WHILE (count_not_ok_g > 0)
482        IF (is_root_prc) THEN
483        CALL random_number (rn1)
484        CALL random_number (rn2)
485        ENDIF
486        CALL bcast(rn1)
487        CALL bcast(rn2)
488
489        DO i=1,npoi
490          IF ((iwet(i) == 1).AND.(not_ok(i) == 1)) then
491            IF ( (rn1-tr1(i)) <= zero ) THEN
492              s1 = zero
493            ELSE
494              s1 = rn1**aa(i)
495            ENDIF
496!-----------
497            IF ((rn2-tr2(i)) <= zero) THEN
498              s2 = zero
499            ELSE
500              s2 = rn2**ab(i)
501            ENDIF
502!-----------
503            s12 = s1+s2
504            IF ((s12-1.0) <= zero) THEN
505              z(i) = s1/s12
506              not_ok(i) = 0
507            ENDIF
508          ENDIF
509        ENDDO
510
511        count_not_ok_g=0
512        count_not_ok=SUM(not_ok(:))
513        CALL reduce_sum(count_not_ok,count_not_ok_g)
514        CALL bcast(count_not_ok_g)
515      ENDDO
516!-----
517      IF (is_root_prc) THEN
518         CALL random_number (rn3)
519      ENDIF
520      CALL bcast(rn3)
521!      WRITE(*,*) mpi_rank,"rn3=",rn3
522!-----
523      DO i=1,npoi
524        IF (iwet(i) == 1) then
525          precip(i) = -z(i)*log(rn3)*beta(i)
526        ENDIF
527      ENDDO
528!-----
529!---- method ii --
530!-----
531!---- here we use a one-parameter Weibull distribution function
532!---- following the analysis of Selker and Haith (1990)
533!-----
534!---- Selker, J.S. and D.A. Haith, 1990: Development and testing
535!---- of single- parameter precipitation distributions,
536!---- Water Resources Research, 11, 2733-2740.
537!-----
538!---- this technique seems to have a significant advantage over other
539!---- means of generating rainfall distribution functions
540!-----
541!---- by calibrating the Weibull function to U.S. precipitation records,
542!---- Selker and Haith were able to establish the following relationship
543!-----
544!---- the cumulative probability of rainfall intensity x is given as:
545!-----
546!---- f(x) = 1.0-exp(-(1.191 x / rainpwd)**0.75)
547!-----
548!---- where x       : rainfall intensity
549!----       rainpwd : rainfall per wet day
550!-----
551!---- using transformation method, take uniform deviate and convert
552!---- it to a random number weighted by the following Weibull function
553!-----
554!----    call random_number(rndnum)
555!-----
556!----    precip(i) = rainpwd / 1.191*(-log(1.0-rndnum))**1.333333
557!-----
558!---- bound daily precipitation to "REAListic" range
559!-----
560      DO i=1,npoi
561        IF (iwet(i) == 1) THEN
562!---------
563!-------- lower end is determined by definition of a 'wet day'
564!-------- (at least 0.25 mm of total precipitation)
565!---------
566!-------- upper end is to prevent ibis from blowing up
567!---------
568          precip(i) = MAX(precip(i),  0.25) ! min =   0.25 mm/day
569          precip(i) = MIN(precip(i),150.00) ! max = 150.00 mm/day
570        ENDIF
571      ENDDO
572    ELSE
573!-----
574!---- (2.2) preserving the monthly number of precip days
575!----       and monthly precip
576!-----
577      DO i=1,npoi
578!-------
579!------ Correction Nathalie. C'est abs(xinwet) < 32 qu'il faut tester
580!------ et non pas abs(xinprec(i,imonth)) < 32.
581!-------
582!------ IF ( (iwet(i) == 1).and.(abs(xinprec(i,imonth)) < 32.) ) THEN
583        IF ( (iwet(i) == 1).and.(abs(xinwet(i,imonth)) < 32.) ) THEN
584          precip(i) = xinprec(i,imonth)*REAL(ndaypm(imonth)) &
585 &                   /REAL(NINT(MAX(1.,xinwet(i,imonth))))
586        ELSE
587          precip(i) = zero
588        ENDIF
589      ENDDO
590    ENDIF
591!---
592!-- (3) estimate expected minimum and maximum temperatures
593!---
594    DO i=1,npoi
595!-----
596!---- first determine the expected maximum and minimum temperatures
597!---- (from climatological means) for this day of the year
598!-----
599!---- mean daily mean temperature (K)
600      tdm = xint(i,it1w)+dt*(xint(i,it2w)-xint(i,it1w))+zero_t
601!---- mean daily temperature range (K)
602      trngm = xintrng(i,it1w)+dt*(xintrng(i,it2w)-xintrng(i,it1w))
603!---- mean minimum and maximum temperatures
604      tmaxm = tdm+0.56*trngm
605      tminm = tdm-0.44*trngm
606!-----
607!---- modify maximum temperatures for wet and dry days
608!-----
609      IF (pwet(i) /= zero) THEN
610        tmaxd = tmaxm+pwet(i)*omtmax*trngm
611        tmaxw = tmaxd-        omtmax*trngm
612      ELSE
613        tmaxd = tmaxm
614        tmaxw = tmaxm
615      ENDIF
616!-----
617!---- set the 'expected' maximum and minimum temperatures for today
618!-----
619!---- note that the expected minimum temperatures are the same for
620!---- both wet and dry days
621!-----
622      if (iwet(i) == 0)  tmaxe(i) = tmaxd
623      if (iwet(i) == 1)  tmaxe(i) = tmaxw
624!-----
625      tmine(i) = tminm
626!-----
627!---- estimate variability in minimum and maximum temperatures
628!-----
629!---- tmaxs : standard deviation in maximum temperature (K)
630!---- tmins : standard deviation in minimum temperature (K)
631!-----
632!---- Regression is based on analysis of 2-m air temperature data
633!---- from the NCEP/NCAR reanalysis (1958-1997) for 294 land points
634!---- over central North America
635!---- (24N-52N, 130W-60W, 0.5-degree resolution):
636!---- Daily max and min temperatures were calculated for each
637!---- land point from daily mean temperature and temperature range.
638!---- Anomalies were calculated
639!---- by subtracting similar max and min temperatures calculated from
640!---- monthly mean temperature and range (interpolated to daily).
641!---- The 40 years of anomalies were then binned by month
642!---- and the standard deviation calculated for each month.
643!---- The 294 x 12 standard deviations were then regressed
644!---- against the 3528 long-term monthly mean temperatures.
645!-----
646!---- note: the values are bound to be greater than 1.0 K
647!----       (at the very least they must be bound
648!----        so they don't go below zero)
649!-----
650      tmaxs(i) = MAX(1.0,-0.0713*(tdm-zero_t)+4.89)
651      tmins(i) = MAX(1.0,-0.1280*(tdm-zero_t)+5.73)
652    ENDDO
653!---
654!-- (4) estimate expected cloud cover
655!---
656!---
657!-- the formulation of dry and wet cloud cover has been
658!-- derived from the weather generator used in the epic crop model
659!---
660    DO i=1,npoi
661!-----
662!---- cloudm : mean cloud cover for today
663!---- cloudd : dry day cloud cover
664!---- cloudw : dry day cloud cover
665!---- cloude : expected cloud cover today
666!-----
667!---- mean cloud cover (%)
668!-----
669      cloudm = xincld(i,it1w)+dt*(xincld(i,it2w)-xincld(i,it1w))
670!-----
671!---- convert from percent to fraction
672!-----
673      cloudm = cloudm/100.0
674!-----
675!---- adjust cloud cover depending on dry day / rainy day
676!---- following logic of the EPIC weather generator code
677!-----
678      IF (pwet(i) /= zero) THEN
679        cloudd = (cloudm-pwet(i)*omcloud)/(un-pwet(i)*omcloud)
680        cloudd = MIN(un,MAX(zero,cloudd))
681        cloudw = (cloudm-(un-pwet(i))*cloudd)/pwet(i)
682      ELSE
683        cloudd = cloudm
684        cloudw = cloudm
685      ENDIF
686      IF (iwet(i) == 0)  cloude(i) = cloudd
687      IF (iwet(i) == 1)  cloude(i) = cloudw
688!-----
689!---- estimate variability in cloud cover for wet and dry days
690!---- following numbers proposed by Richardson
691!-----
692!---- clouds : standard deviation of cloud fraction
693!-----
694      IF (iwet(i) == 0)  clouds(i) = 0.24*cloude(i)
695      IF (iwet(i) == 1)  clouds(i) = 0.48*cloude(i)
696    ENDDO
697!---
698! (5) determine today's temperatures and cloud cover using
699!     first-order serial autoregressive technique
700!---
701!-- use the Richardson (1981) weather generator approach to simulate the
702!-- daily values of minimum / maximum temperature and cloud cover
703!---
704!-- following the implementation of the Richardson WGEN weather
705!-- generator used in the EPIC crop model
706!---
707!-- this approach uses a multivariate generator, which assumes that the
708!-- perturbation of minimum / maximum temperature and cloud cover are
709!-- normally distributed and that the serial correlation of each
710!-- variable may be described by a first-order autoregressive model
711!---
712!-- generate standard deviates for weather generator
713!---
714    DO j=1,3
715      ee(j) = 9999.
716      DO WHILE (ee(j) > 2.5)
717        IF (is_root_prc) THEN
718           CALL random_number (rn1)
719           CALL random_number (rn2)
720        ENDIF
721        CALL bcast(rn1)
722        CALL bcast(rn2)
723        ee(j) = SQRT(-2.0*LOG(rn1))*COS(6.283185*rn2)
724      ENDDO
725    ENDDO
726!---
727!-- zero out vectors
728!---
729    r(1:3)  = zero
730    rr(1:npoi,1:3) = zero
731!---
732!-- update working vectors
733!---
734    do j=1,3
735      do k=1,3
736        r(j) = r(j)+b(j,k)*ee(j)
737      enddo
738    enddo
739!---
740    do j=1,3
741      do k=1,3
742        do i=1,npoi
743          rr(i,j) = rr(i,j)+a(j,k)*xstore(i,k)
744        enddo
745      enddo
746    enddo
747!---
748!-- solve for x() perturbation vector and save current vector
749!-- into the xim1() storage vector (saved for each point)
750!---
751    do j=1,3
752      do i=1,npoi
753        xstore(i,j) = r(j)+rr(i,j)
754      enddo
755    enddo
756!---
757!-- determine today's minimum and maximum temperature
758!--
759    do i=1,npoi
760      tmax(i) = tmaxe(i)+tmaxs(i)*xstore(i,1)
761      tmin(i) = tmine(i)+tmins(i)*xstore(i,2)
762!-----
763!---- if tmin > tmax, then switch the two around
764!-----
765      if (tmin(i) > tmax(i)) then
766        tdum    = tmax(i)
767        tmax(i) = tmin(i)
768        tmin(i) = tdum
769      ENDIF
770!---- daily average temperature
771      td(i) = 0.44*tmax(i)+0.56*tmin(i)
772!---- determine today's cloud cover
773      cloud(i) = cloude(i)+clouds(i)*xstore(i,3)
774!---- constrain cloud cover to be between 0 and 100%
775      cloud(i) = MAX(zero,MIN(un,cloud(i)))
776    enddo
777!---
778!-- (6) estimate today's surface atmospheric pressure
779!---
780    do i=1,npoi
781!-----
782!---- simply a function of the daily average temperature
783!---- and topographic height -- nothing fancy here
784!-----
785      psurf(i) = 101325.0*(td(i)/(td(i)+0.0065*xintopo(i)))**rwork
786    enddo
787!---
788!-- (7) estimate today's relative humidity
789!---
790    IF (is_root_prc) THEN
791       CALL random_number (rn)
792    ENDIF
793    CALL bcast(rn)
794!---
795    CALL weathgen_qsat (npoi,td,psurf,qsattd)
796!---
797    do i=1,npoi
798!-----
799!---- the formulation of dry and wet relative humidities has been
800!---- derived from the weather generator used in the epic crop model
801!-----
802!---- qdm : mean relative humidity
803!---- qdd : dry day relative humidity
804!---- qdw : rainy day relative humidity
805!---- qde : expected relative humidity (based on wet/dry decision)
806!-----
807!---- mean relative humidity (%)
808      qdm(i) = xinq(i,it1w)+dt*(xinq(i,it2w)-xinq(i,it1w))
809!---- convert from percent to fraction
810      qdm(i) = qdm(i)/100.0
811!-----
812!---- adjust humidity depending on dry day / rainy day
813!---- following logic of the EPIC weather generator code
814!-----
815      if (pwet(i) /= zero) then
816        qdd(i) = (qdm(i)-pwet(i)*omqd)/(un-pwet(i)*omqd)
817        if (qdd(i) < 0.2) then
818          qdd(i) = 0.2
819          if (qdd(i) > qdm(i)) qdm(i) = qdd(i)
820        ENDIF
821        qdd(i) = MIN(un,qdd(i))
822        qdw(i) = (qdm(i)-(un-pwet(i))*qdd(i))/pwet(i)
823      ELSE
824        qdd(i) = qdm(i)
825        qdw(i) = qdm(i)
826      ENDIF
827!-----
828      if (iwet(i) == 0)  qde(i) = qdd(i)
829      if (iwet(i) == 1)  qde(i) = qdw(i)
830!-----
831!---- estimate lower and upper bounds of humidity distribution function
832!---- following logic of the EPIC weather generator code
833!-----
834      xx = exp(qde(i))
835      qdup(i)  = qde(i)+(un-qde(i))*xx/euler
836      qdlow(i) = qde(i)*(un-1./xx)
837!-----
838!---- randomlly select humidity from triangular distribution function
839!---- following logic of the EPIC weather generator code
840!-----
841!---- call random_number(rn) ! GK done before
842!-----
843      y  = 2.0/(qdup(i)-qdlow(i))
844!-----
845      b3 = qde(i)-qdlow(i)
846      b2 = qdup(i)-qde(i)
847      b1 = rn/y
848!-----
849      x1 = y*b3/2.0
850!-----
851      if (rn > x1) then
852        qd(i) = qdup(i)-sqrt (b2*b2-2.0*b2*(b1-0.5*b3))
853      ELSE
854        qd(i) = qdlow(i)+sqrt (2.0*b1*b3)
855      ENDIF
856!-----
857!---- adjust daily humidity to conserve monthly mean values
858!-----
859!---- note that this adjustment sometimes gives rise to humidity
860!---- values greater than 1.0 -- which is corrected below
861!-----
862      amn = (qdup(i)+qde(i)+qdlow(i))/3.0
863      qd(i) = qd(i)*qde(i)/amn
864!-----
865!---- constrain daily average relative humidity
866!-----
867      qd(i) = MAX(0.30,MIN(qd(i),0.99))
868!-----
869!---- convert from relative humidity to specific humidity at
870!---- daily mean temperature
871!-----
872      qd(i) = qd(i)*qsattd(i)
873    enddo
874!---
875!-- (8) estimate today's daily average wind speed
876!---
877    IF (is_root_prc) THEN
878        CALL random_number (rn4)
879    ENDIF
880    CALL bcast(rn4)
881
882    DO i=1,npoi
883!-----
884!---- first estimate the expected daily average wind speed (from monthly
885!---- means)
886!-----
887      eud = xinwind(i,it1w)+dt*(xinwind(i,it2w)-xinwind(i,it1w))
888!-----
889!---- following logic of the EPIC weather generator
890!---- select random wind speed following this equation
891!-----
892!---- call random_number(rn4)
893!-----
894      ud(i) = 1.13989*eud*(-log(rn4))**0.30
895!---- constrain daily wind speeds to be between 2.5 and 10.0 m/sec
896      ud(i) = MAX(2.5,MIN(ud(i),10.0))
897    ENDDO
898  ELSE
899!---
900!-- use REAL daily climate data
901!---
902    DO i=1,npoi
903!-----
904!---- use basic daily climate data, converting units
905!-----
906!---- daily total precipitation
907      precip(i) = xinprec(i,imonth)
908!---- daily average temperatures
909      td(i) = xint(i,imonth)+zero_t
910      trngm = MIN(44.0,xintrng(i,imonth))
911!-----
912      tmax(i) = td(i)+0.56*trngm
913      tmin(i) = td(i)-0.44*trngm
914!---- daily average cloud cover
915      cloud(i) = xincld(i,imonth)*0.01
916!---- daily average specific humidity
917      qd(i) = xinq(i,imonth)
918!---- daily average wind speed
919      ud(i) = xinwind(i,imonth)
920!-----
921!---- compute surface atmospheric pressure
922!-----
923      psurf(i) = 101325.0*(td(i)/(td(i)+0.0065*xintopo(i)))**rwork
924    ENDDO
925  ENDIF
926!-------------------
927END SUBROUTINE daily
928!-
929!===
930!-
931
932!! ================================================================================================================================
933!! SUBROUTINE   : diurnal
934!!
935!>\BRIEF          This routine interpolates values from the!*
936!! subroutine daily into instantaneous values for simulating a diurnal cycle.
937!!
938!! DESCRIPTION  : 
939!!
940!! RECENT CHANGE(S): None
941!!
942!! MAIN OUTPUT VARIABLE(S):  ::fira, ::solad, ::ua, ::ta, ::qa, ::raina, ::snowa, ::rh.
943!!
944!! REFERENCE(S) :
945!!
946!! FLOWCHART    : None
947!! \n
948!_ ================================================================================================================================
949
950SUBROUTINE diurnal &
951& (npoi, nband, time, jday, plens, startp, endp, latitude, &
952&  cloud, tmax, tmin, precip, qd, ud, psurf, &
953&  fira, solad, solai, ua, ta, qa, raina, snowa, rh)
954!---------------------------------------------------------------------
955  IMPLICIT NONE
956!-
957
958  !! 0. Parameter and variables declaration
959
960  !! 0.1 Input variables
961
962  INTEGER,INTENT(IN) :: npoi    !! number of grid points (unitless)
963  INTEGER,INTENT(IN) :: nband   !! number of visible bands (unitless)
964  REAL,INTENT(IN) :: time
965  INTEGER, INTENT(IN) :: jday
966  REAL,INTENT(IN) :: plens,startp,endp
967  REAL,INTENT(IN) :: latitude(npoi)   !! latitude in degrees
968  REAL,INTENT(IN) :: cloud(npoi)      !! cloud fraction (0-1, unitless)
969  REAL,INTENT(IN) :: tmax(npoi)       !! maximum daily temperature (K)
970  REAL,INTENT(IN) :: tmin(npoi)       !! maximum daily temperature (K)
971  REAL,INTENT(IN) :: precip(npoi)     !! daily precitation @tex $(mm.day^{-1})$ @endtex
972  REAL,INTENT(IN) :: qd(npoi)         !! daily average specific humidity (kg_h2o/kg_air)
973  REAL,INTENT(IN) :: ud(npoi)         !! daily average wind speed @tex $(m.s^{-1})$ @endtex
974  REAL,INTENT(IN) :: psurf(npoi)      !! surface pressure (Pa)
975
976  !! 0.2 Output variables
977
978  REAL,INTENT(OUT) :: fira(npoi)          !! incoming ir flux  @tex $(W.m^{-2})$ @endtex
979  REAL,INTENT(OUT) :: solad(npoi,nband)   !! direct downward solar flux @tex $(W.m^{-2})$ @endtex
980  REAL,INTENT(OUT) :: solai(npoi,nband)   !! diffuse downward solar flux @tex $(W.m^{-2})$ @endtex
981  REAL,INTENT(OUT) :: ua(npoi)            !! wind speed @tex $(m.s^{-1})$ @endtex
982  REAL,INTENT(OUT) :: ta(npoi)            !! air temperature (K)
983  REAL,INTENT(OUT) :: qa(npoi)            !! specific humidity (kg_h2o/kg_air)
984  REAL,INTENT(OUT) :: raina(npoi)         !! rainfall rate @tex $(mm.day^{-1})$ @endtex
985  REAL,INTENT(OUT) :: snowa(npoi)         !! snowfall rate @tex $(mm.day^{-1})$ @endtex
986  REAL,INTENT(OUT) :: rh(npoi)            !! relative humidity (0-1, unitless)
987
988  !! 0.4 Local variables
989
990  REAL,SAVE      :: step
991  REAL :: xl,so,xllp,xee,xse
992  REAL :: xlam,dlamm,anm,ranm,ranv,anv,tls,rlam
993  REAL :: sd,cd,deltar,delta,Dis_ST,ddt
994!-
995  REAL :: coszen(npoi)                      !! cosine of solar zenith angle
996  REAL :: rtime
997  REAL :: sw,frac,gamma,qmin,qmax,qsa,emb,ea,ec,dtair,dtcloud,rn
998  REAL :: trans(npoi), fdiffuse(npoi), qsatta(npoi), qsattmin(npoi)
999  INTEGER :: i,ib
1000  INTEGER,SAVE :: npoi0
1001  LOGICAL,SAVE :: lstep_init_diurnal = .TRUE.
1002
1003!---------------------------------------------------------------------
1004! GK240100
1005  IF (lstep_init_diurnal) THEN
1006    lstep_init_diurnal = .FALSE.
1007    npoi0 = npoi
1008  ELSE IF (npoi /= npoi0) THEN
1009    WRITE(numout,*) 'Domain size old, new: ',npoi0,npoi
1010    STOP 'WG Diurnal: Problem: Domain has changed since last call'
1011  ENDIF
1012
1013! calculate time in hours
1014  rtime = time/3600.0
1015
1016  CALL downward_solar_flux(npoi,latitude,calendar_str,REAL(jday),rtime,cloud,nband,solad,solai)
1017!-
1018! temperature calculations
1019!-
1020!---
1021!-- assign hourly temperatures using tmax and tmin
1022!-- following Environmental Biophysics, by Campbell and Norman, p.23
1023!---
1024!-- this function fits a fourier series to the diurnal temperature cycle
1025!-- note that the maximum temperature occurs at 2:00 pm local solar time
1026!---
1027!-- note that the daily mean value of gamma is 0.44,
1028!-- so td = 0.44*tmax+0.56*tmin,  instead of
1029!--    td = 0.50*tmax+0.50*tmin
1030!---
1031  gamma = 0.44-0.46*SIN(    pi/12.0*rtime+0.9) &
1032              +0.11*SIN(2.0*pi/12.0*rtime+0.9)
1033  DO i=1,npoi
1034    ta(i) = tmax(i)*gamma+tmin(i)*(1.0-gamma)
1035  ENDDO
1036!-
1037! humidity calculations
1038!-
1039  CALL weathgen_qsat (npoi,tmin,psurf,qsattmin)
1040  CALL weathgen_qsat (npoi,ta,psurf,qsatta)
1041!-
1042  DO i=1,npoi
1043!---
1044!-- adjust specific humidity against daily minimum temperatures
1045!---
1046!-- To do this, qa is written as an approximate sine function
1047!-- (same as ta) to preserve the daily mean specific humidity,
1048!-- while also preventing rh from exceeding 99% at night
1049!---
1050!-- Note that the daily mean RH is *not* preserved, and therefore the
1051!-- output RH will be slightly different from what was read in.
1052!---
1053!-- first adjust so that maximum RH cannot exceed 99% at night
1054!---
1055    qmin = MIN(qd(i),0.99*qsattmin(i))
1056    qmax = (qd(i)-0.56*qmin)/0.44
1057!---
1058!-- if needed, adjust again to 99% at other times of the day (in which
1059!-- case the daily mean *specific* humidity is also not preserved)
1060!---
1061    qsa  = 0.99*qsatta(i)
1062!---
1063!-- calculate the hourly specific humidity, using the above adjustments
1064!---
1065    qa(i) = MIN(qsa,qmax*gamma+qmin*(1.0-gamma))
1066!---
1067!-- calculate the hourly relative humidity
1068!--
1069    rh(i) = 100.*qa(i)/qsatta(i)
1070  ENDDO
1071!-
1072! wind speed calculations
1073!-
1074  IF (is_root_prc) THEN
1075     CALL random_number (rn)
1076  ENDIF
1077  CALL bcast(rn)
1078!-
1079  DO i=1,npoi
1080!---
1081!-- following logic of the EPIC weather generator
1082!-- select random wind speed following this equation
1083!---
1084!-- call random_number(rn) ! done before
1085!---
1086    ua(i) = 1.13989*ud(i)*(-log(rn))**0.30
1087!---
1088!-- fix wind speeds to always be above 2.5 m/sec and below 10.0 m/sec
1089!---
1090    ua(i) = MAX(2.5,MIN(10.0,ua(i)))
1091  ENDDO
1092!-
1093! ir flux calculations
1094!-
1095  DO i=1,npoi
1096!---
1097!-- clear-sky emissivity as a function of water vapor pressure
1098!-- and atmospheric temperature
1099!---
1100!-- calculate the ir emissivity of the clear sky
1101!-- using equation from idso (1981) water resources res., 17, 295-304
1102!---
1103    emb = 0.01*(psurf(i)*qa(i)/(0.622+qa(i)))
1104    ea  = 0.70+5.95e-5*emb*EXP(1500.0/ta(i))
1105!---
1106!-- assign the ir emissivity of clouds
1107!-- (assume they are ~black in the ir)
1108!---
1109    ec = 0.950
1110!---
1111!-- assign the temperature difference of emissions (air+cloud) from
1112!-- the surface air temperature
1113!---
1114    dtair   = zero
1115    dtcloud = zero
1116!---
1117!-- total downward ir is equal to the sum of:
1118!---
1119!-- (1) clear sky contribution to downward ir radiation flux
1120!-- (2) cloud contribution to downward ir radiation flux
1121!---
1122    fira(i) = (1.-cloud(i))*ea*c_stefan*(ta(i)-dtair)**4 &
1123 &           +cloud(i)*ec*c_stefan*(ta(i)-dtcloud)**4
1124  ENDDO
1125!-
1126! snow and rain calculations
1127!-
1128  DO i=1,npoi
1129!---
1130!-- reset snow and rain to zero
1131!---
1132    snowa(i) = zero
1133    raina(i) = zero
1134!---
1135!-- if precipitation event then calculate
1136!---
1137    IF (time >= startp .and. time < endp) then
1138!-----
1139!---- for rain / snow partitioning, make it all rain if
1140!---- ta > 2.5 C and all snow if ta <= 2.5 C
1141!-----
1142!---- reference:
1143!-----
1144!---- Auer, A. H., 1974: The rain versus snow threshold temperatures,
1145!---- Weatherwise, 27, 67.
1146!-----
1147      IF (ta(i)-273.15 > 2.5) then
1148        raina(i) = precip(i)/plens
1149      ELSE
1150        snowa(i) = precip(i)/plens
1151      ENDIF
1152    ENDIF
1153  ENDDO
1154!---------------------
1155END SUBROUTINE diurnal
1156!-
1157!===
1158!-
1159
1160!! ================================================================================================================================
1161!! SUBROUTINE   : weathgen_main
1162!!
1163!>\BRIEF        This subroutine manages the calls to the different subroutines of the weather module.
1164!!
1165!! DESCRIPTION  : None
1166!!
1167!! RECENT CHANGE(S): None
1168!!
1169!! MAIN OUTPUT VARIABLE(S): ::tair, ::pb, ::qair, ::swdown, ::rainf, ::snowf, ::u, ::v, ::lwdown
1170!!
1171!! REFERENCE(S) :
1172!!
1173!! FLOWCHART    : None
1174!! \n
1175!_ ================================================================================================================================
1176
1177SUBROUTINE weathgen_main &
1178& (itau, istp, filename, force_id, iim, jjm, nband, &
1179&  rest_id, lrstread, lrstwrite, &
1180&  limit_west, limit_east, limit_north, limit_south, &
1181&  zonal_res, merid_res, lon, lat, date0, dt_force, &
1182&  kindex, nbindex, &
1183&  swdown, rainf, snowf, tair, u, v, qair, pb, lwdown)
1184!---------------------------------------------------------------------
1185  IMPLICIT NONE
1186!-
1187
1188  !! 0. Variables and parameters declaration
1189
1190  !! 0.1 Input variables
1191
1192  INTEGER,INTENT(IN)                  :: itau,istp
1193  CHARACTER(LEN=*),INTENT(IN)         :: filename
1194  INTEGER,INTENT(IN)                  :: force_id
1195  INTEGER,INTENT(IN)                  :: iim,jjm
1196  INTEGER,INTENT(IN)                  :: nband
1197  INTEGER,INTENT(IN)                  :: rest_id
1198  LOGICAL,INTENT(IN)                  :: lrstread, lrstwrite
1199  REAL,INTENT(IN)                     :: limit_west,limit_east
1200  REAL,INTENT(IN)                     :: limit_north,limit_south
1201  REAL,INTENT(IN)                     :: zonal_res,merid_res
1202  REAL,INTENT(IN)                     :: date0,dt_force
1203  REAL,DIMENSION(iim,jjm),INTENT(IN)  :: lon,lat  !! longitude, latitude
1204
1205  !! 0.2 Output variables
1206
1207  REAL,DIMENSION(iim,jjm),INTENT(OUT) :: &
1208 &  tair,pb,qair,swdown,rainf,snowf, u,v,lwdown
1209
1210  !! 0.3 Mofified variables
1211
1212  INTEGER,INTENT(INOUT)                    :: nbindex
1213  INTEGER,DIMENSION(iim*jjm),INTENT(INOUT) :: kindex
1214
1215  !! 0.4 Local variables
1216
1217  REAL, ALLOCATABLE, DIMENSION(:,:) :: &
1218 &  tair_g,pb_g,qair_g,swdown_g,rainf_g,snowf_g, u_g,v_g,lwdown_g
1219  REAL,DIMENSION(nbindex) :: &
1220 &  tairl,pbl,qairl,swdownl,rainfl,snowfl, ul,vl,lwdownl
1221  INTEGER :: i,j,ij
1222!---------------------------------------------------------------------
1223  IF (lrstread) THEN
1224    CALL weathgen_begin ( &
1225     & dt_force,itau, date0, &
1226     & rest_id,iim,jjm, &
1227     & lon,lat,tair,pb,qair,kindex,nbindex)
1228        RETURN
1229  ELSE
1230    CALL weathgen_get &
1231 &   (itau, date0, dt_force, nbindex, nband, lat_land, &
1232 &    swdownl, rainfl, snowfl, tairl, ul, vl, qairl, pbl, lwdownl)
1233
1234    tair(:,:)=val_exp
1235    qair(:,:)=val_exp
1236    pb(:,:)=val_exp
1237    DO ij=1,nbindex
1238       j = (((kindex(ij)-1)/iim) + 1)
1239       i = (kindex(ij) - (j-1)*iim)
1240       !
1241       swdown(i,j)=swdownl(ij)
1242       rainf(i,j)=rainfl(ij)
1243       snowf(i,j)=snowfl(ij)
1244       tair(i,j)=tairl(ij)
1245       u(i,j)=ul(ij)
1246       v(i,j)=vl(ij)
1247       qair(i,j)=qairl(ij)
1248       pb(i,j)=pbl(ij)
1249       lwdown(i,j)=lwdownl(ij)
1250    ENDDO
1251!---
1252    IF (dump_weather) THEN
1253      ALLOCATE(tair_g(iim_g,jjm_g))
1254      ALLOCATE(pb_g(iim_g,jjm_g))
1255      ALLOCATE(qair_g(iim_g,jjm_g))
1256      ALLOCATE(swdown_g(iim_g,jjm_g))
1257      ALLOCATE(rainf_g(iim_g,jjm_g))
1258      ALLOCATE(snowf_g(iim_g,jjm_g))
1259      ALLOCATE(u_g(iim_g,jjm_g))
1260      ALLOCATE(v_g(iim_g,jjm_g))
1261      ALLOCATE(lwdown_g(iim_g,jjm_g))
1262
1263      CALL gather2D_mpi(tair, tair_g)
1264      CALL gather2D_mpi(pb, pb_g)
1265      CALL gather2D_mpi(qair, qair_g)
1266      CALL gather2D_mpi(swdown, swdown_g)
1267      CALL gather2D_mpi(rainf, rainf_g)
1268      CALL gather2D_mpi(snowf, snowf_g)
1269      CALL gather2D_mpi(u, u_g)
1270      CALL gather2D_mpi(v, v_g)
1271      CALL gather2D_mpi(lwdown, lwdown_g)
1272      IF (is_root_prc) THEN
1273         CALL weathgen_dump &
1274 &           (itau, dt_force, iim_g, jjm_g, nbp_glo, index_g, lrstwrite, &
1275 &            swdown_g, rainf_g, snowf_g, tair_g, u_g, v_g, qair_g, pb_g, lwdown_g)
1276      ENDIF
1277    ENDIF
1278!---
1279    IF (lrstwrite) THEN
1280      CALL weathgen_restwrite (rest_id,istp,iim,jjm,nbindex,kindex)
1281    ENDIF
1282  ENDIF
1283!---------------------------
1284END SUBROUTINE weathgen_main
1285!-
1286!===
1287!-
1288
1289!! ================================================================================================================================
1290!! SUBROUTINE   : weathgen_init
1291!!
1292!>\BRIEF         This subroutine initializes weather variables.
1293!!
1294!! DESCRIPTION  : None
1295!!
1296!! RECENT CHANGE(S): None
1297!!
1298!! MAIN OUTPUT VARIABLE(S):  ::kindex, ::nbindex
1299!!
1300!! REFERENCE(S) :
1301!!
1302!! FLOWCHART    : None
1303!! \n
1304!_ ================================================================================================================================
1305
1306SUBROUTINE weathgen_init &
1307     & (filename,dt_force,force_id,iim,jjm, &
1308     &  zonal_res,merid_res,lon,lat,kindex,nbindex)
1309!!$,iind,jind)
1310  !---------------------------------------------------------------------
1311  IMPLICIT NONE
1312  !-
1313
1314  !! 0. Variables and parameters declaration
1315
1316  REAL,PARAMETER  :: fcrit = .5       !! Minimum land fraction on original grid
1317
1318  !! 0.1 Input variables
1319
1320  CHARACTER(LEN=*),INTENT(IN)         :: filename
1321  REAL,INTENT(IN)                     :: dt_force
1322  INTEGER,INTENT(IN)                  :: iim, jjm
1323  REAL,INTENT(IN)                     :: zonal_res,merid_res
1324  REAL,DIMENSION(iim,jjm),INTENT(IN)  :: lon,lat
1325
1326  !! 0.2 Output variables 
1327
1328  INTEGER,INTENT(OUT)                 :: nbindex
1329  INTEGER,DIMENSION(iim*jjm),INTENT(OUT)  :: kindex
1330!!$  INTEGER,DIMENSION(iim),INTENT(OUT) :: iind
1331!!$  INTEGER,DIMENSION(jjm),INTENT(OUT) :: jind
1332
1333  !! 0.3 Modified variables
1334
1335  INTEGER,INTENT(INOUT)               :: force_id
1336
1337  !! 0.4 Local variables
1338
1339  REAL,DIMENSION(:),ALLOCATABLE         :: lon_file, lon_temp
1340  REAL,DIMENSION(:,:),ALLOCATABLE       :: nav_lon, nav_lat
1341  REAL,DIMENSION(:),ALLOCATABLE         :: lat_file, lat_temp
1342  REAL,DIMENSION(:,:),ALLOCATABLE       :: lsm_file
1343  REAL     :: xextent_file, yextent_file, xres_file, yres_file
1344  INTEGER  :: i, j, plotstep
1345  REAL,DIMENSION(iim,jjm)               :: mask
1346  CHARACTER(LEN=1),DIMENSION(0:1)       :: maskchar
1347  CHARACTER(LEN=30)                     :: var_name
1348  REAL     :: x_cut
1349  REAL,DIMENSION(iim) :: tmp_lon
1350  REAL,DIMENSION(jjm) :: tmp_lat
1351
1352!_ ================================================================================================================================
1353
1354  !-
1355  ! 0. messages, initialisations
1356  !-
1357  WRITE(numout,*) &
1358       &  'weathgen_init: Minimum land fraction on original grid =',fcrit
1359  CALL ioget_calendar(calendar_str)
1360  !-
1361  ! 1. on lit les longitudes et latitudes de la grille de depart
1362  !    ainsi que le masque terre-ocean
1363  !-
1364  CALL flinclo(force_id)
1365  CALL flininfo (filename,iim_file,jjm_file,llm_file,ttm_file,force_id)
1366  !-
1367  ALLOC_ERR=-1
1368  ALLOCATE(nav_lon(iim_file,jjm_file), STAT=ALLOC_ERR)
1369  IF (ALLOC_ERR/=0) THEN
1370     WRITE(numout,*) "ERROR IN ALLOCATION of nav_lon : ",ALLOC_ERR
1371     STOP
1372  ENDIF
1373
1374  ALLOC_ERR=-1
1375  ALLOCATE(nav_lat(iim_file,jjm_file), STAT=ALLOC_ERR)
1376  IF (ALLOC_ERR/=0) THEN
1377     WRITE(numout,*) "ERROR IN ALLOCATION of nav_lat : ",ALLOC_ERR
1378     STOP
1379  ENDIF
1380  !-
1381  var_name='nav_lon'
1382  CALL flinget (force_id,var_name,iim_file,jjm_file,0,0,1,1,nav_lon)
1383  var_name='nav_lat'
1384  CALL flinget (force_id,var_name,iim_file,jjm_file,0,0,1,1,nav_lat)
1385  !-
1386
1387  ALLOC_ERR=-1
1388  ALLOCATE(lon_file(iim_file), STAT=ALLOC_ERR)
1389  IF (ALLOC_ERR/=0) THEN
1390     WRITE(numout,*) "ERROR IN ALLOCATION of lon_file : ",ALLOC_ERR
1391     STOP
1392  ENDIF
1393
1394  ALLOC_ERR=-1
1395  ALLOCATE(lat_file(jjm_file), STAT=ALLOC_ERR)
1396  IF (ALLOC_ERR/=0) THEN
1397     WRITE(numout,*) "ERROR IN ALLOCATION of lat_file : ",ALLOC_ERR
1398     STOP
1399  ENDIF
1400  !-
1401  DO i=1,iim_file
1402     lon_file(i) = nav_lon(i,1)
1403  ENDDO
1404  DO j=1,jjm_file
1405     lat_file(j) = nav_lat(1,j)
1406  ENDDO
1407!-
1408
1409  ALLOC_ERR=-1
1410  ALLOCATE(lsm_file(iim_file,jjm_file), STAT=ALLOC_ERR)
1411  IF (ALLOC_ERR/=0) THEN
1412    WRITE(numout,*) "ERROR IN ALLOCATION of lsm_file : ",ALLOC_ERR
1413    STOP
1414  ENDIF
1415!-
1416  var_name='lsmera'
1417  CALL flinget (force_id,var_name,iim_file,jjm_file,0,0,1,1,lsm_file)
1418!-
1419! 2. La resolution du modele ne doit pas etre superieure
1420!    a celle de la grille de depart
1421!-
1422  xextent_file = lon_file(iim_file)-lon_file(1)
1423  yextent_file = lat_file(1)-lat_file(jjm_file)
1424  xres_file = xextent_file/REAL(iim_file-1)
1425  yres_file = yextent_file/REAL(jjm_file-1)
1426!-
1427  IF (xres_file > zonal_res) THEN
1428    WRITE(numout,*) 'Zonal resolution of model grid too fine.'
1429    WRITE(numout,*) 'Resolution of original data (deg): ', xres_file
1430    STOP
1431  ENDIF
1432!-
1433  IF (yres_file > merid_res) THEN
1434    WRITE(numout,*) 'Meridional resolution of model grid too fine.'
1435    WRITE(numout,*) 'Resolution of original data (deg): ', yres_file
1436    STOP
1437  ENDIF
1438!-
1439! 3. On verifie la coherence des coordonnees de depart et d'arrivee.
1440!    Sinon, il faut deplacer une partie du monde (rien que ca).
1441!-
1442  i_cut = 0
1443!-
1444
1445  ALLOC_ERR=-1
1446  ALLOCATE(lon_temp(iim_file), STAT=ALLOC_ERR)
1447  IF (ALLOC_ERR/=0) THEN
1448    WRITE(numout,*) "ERROR IN ALLOCATION of lon_temp : ",ALLOC_ERR
1449    STOP
1450  ENDIF
1451
1452  ALLOC_ERR=-1
1453  ALLOCATE(lat_temp(jjm_file), STAT=ALLOC_ERR)
1454  IF (ALLOC_ERR/=0) THEN
1455    WRITE(numout,*) "ERROR IN ALLOCATION of lat_temp : ",ALLOC_ERR
1456    STOP
1457  ENDIF
1458!-
1459  IF (lon(iim,1) > lon_file(iim_file)) THEN
1460!-- A l'Est de la region d'interet, il n'y a pas de donnees
1461!-- le bout a l'Ouest de la region d'interet est deplace de 360 deg
1462!-- vers l'Est
1463    x_cut = lon(1,1)
1464    DO i=1,iim_file
1465      IF (lon_file(i) < x_cut) i_cut = i
1466    ENDDO
1467    IF ((i_cut < 1).OR.(i_cut >= iim_file)) THEN
1468        STOP 'Cannot find longitude for domain shift'
1469    ENDIF
1470!---
1471    lon_temp(1:iim_file-i_cut-1) = lon_file(i_cut:iim_file)
1472    lon_temp(iim_file-i_cut:iim_file) = lon_file(1:i_cut+1)+360.
1473    lon_file(:) = lon_temp(:)
1474  ELSEIF (lon(1,1) < lon_file(1)) THEN
1475!-- A l'Ouest de la region d'interet, il n'y a pas de donnees
1476!-- le bout a l'Est de la region d'interet est deplace de 360 deg
1477!-- vers l'Ouest
1478    x_cut = lon(iim,1)
1479    DO i=1,iim_file
1480      IF (lon_file(i) < x_cut) i_cut = i
1481    ENDDO
1482    IF ( ( i_cut < 1 ) .OR. ( i_cut >= iim_file ) ) THEN
1483        STOP 'Cannot find longitude for domain shift'
1484    ENDIF
1485!---
1486    lon_temp(1:iim_file-i_cut-1) = lon_file(i_cut:iim_file) -360.
1487    lon_temp(iim_file-i_cut:iim_file) = lon_file(1:i_cut+1)
1488    lon_file(:) = lon_temp(:)
1489  ENDIF
1490!-
1491  DEALLOCATE (lon_temp)
1492  DEALLOCATE (lat_temp)
1493!-
1494  IF (    (lon(1,1) < lon_file(1)) &
1495 &    .OR.(     (lon(iim,1) > lon_file(iim_file)) &
1496 &         .AND.(lon(iim,1) > lon_file(1)+360.) ) ) THEN
1497    WRITE(numout,*) lon(:,1)
1498    WRITE(numout,*)
1499    WRITE(numout,*) lon_file(:)
1500    STOP 'weathgen_init: cannot find coherent x-coordinates'
1501  ENDIF
1502!-
1503  IF (i_cut /= 0) THEN
1504    CALL shift_field (iim_file,jjm_file,i_cut,lsm_file)
1505  ENDIF
1506!-
1507! 4. Verification
1508!-
1509  WRITE(numout,*)
1510  WRITE(numout,*) 'Input File: (Shifted) Global Land-Sea Mask'
1511  WRITE(numout,*)
1512  maskchar(0) = '-'
1513  maskchar(1) = 'X'
1514  plotstep = INT(REAL(iim_file-1)/termcol)+1
1515  DO j=1,jjm_file,plotstep
1516    DO i=1,iim_file,plotstep
1517      WRITE(numout,'(a1,$)') maskchar(NINT(lsm_file(i,j)))
1518    ENDDO
1519    WRITE(numout,*)
1520  ENDDO
1521  WRITE(numout,*)
1522!-
1523! 5. Prepare interpolation from fine grid land points to model grid
1524!-
1525! 5.1 how many grid points of the original grid fall into one grid
1526!     box of the model grid?
1527!-
1528  n_agg = NINT((zonal_res/xres_file*merid_res/yres_file )+1.)
1529!-
1530! au diable l'avarice !
1531!-
1532  n_agg = n_agg*2
1533!-
1534! 5.2 Allocate arrays where we store information about which
1535!     (and how many) points on the original grid fall
1536!     into which box on the model grid
1537!-
1538
1539  ALLOC_ERR=-1
1540  ALLOCATE(ncorr(iim,jjm), STAT=ALLOC_ERR)
1541  IF (ALLOC_ERR/=0) THEN
1542    WRITE(numout,*) "ERROR IN ALLOCATION of ncorr : ",ALLOC_ERR
1543    STOP
1544  ENDIF
1545
1546  ALLOC_ERR=-1
1547  ALLOCATE(icorr(iim,jjm,n_agg), STAT=ALLOC_ERR)
1548  IF (ALLOC_ERR/=0) THEN
1549    WRITE(numout,*) "ERROR IN ALLOCATION of icorr : ",ALLOC_ERR
1550    STOP
1551  ENDIF
1552
1553  ALLOC_ERR=-1
1554  ALLOCATE(jcorr(iim,jjm,n_agg), STAT=ALLOC_ERR)
1555  IF (ALLOC_ERR/=0) THEN
1556    WRITE(numout,*) "ERROR IN ALLOCATION of jcorr : ",ALLOC_ERR
1557    STOP
1558  ENDIF
1559!-
1560! 6. Land-Ocean Mask on model grid
1561!-
1562  tmp_lon = lon(:,1)
1563  tmp_lat = lat(1,:)
1564
1565  CALL mask_c_o &
1566 &  (iim_file, jjm_file, lon_file, lat_file, lsm_file, fcrit, &
1567 &   iim, jjm, zonal_res, merid_res, n_agg, tmp_lon, tmp_lat, &
1568! &   iim, jjm, zonal_res, merid_res, n_agg, lon(:,1), lat(1,:), &
1569 &   mask, ncorr, icorr, jcorr)
1570!-
1571  WRITE(numout,*) 'Land-Sea Mask on Model Grid'
1572  WRITE(numout,*)
1573  plotstep = INT(REAL(iim-1)/termcol)+1
1574  DO j=1,jjm,plotstep
1575    DO i=1,iim,plotstep
1576      WRITE(numout,'(a1,$)') maskchar(NINT(mask(i,j)))
1577    ENDDO
1578    WRITE(numout,*)
1579  ENDDO
1580  WRITE(numout,*)
1581!-
1582! 7. kindex table.
1583!-
1584  nbindex = 0
1585  DO j=1,jjm
1586    DO i=1,iim
1587      IF (NINT(mask(i,j)) == 1) THEN
1588        nbindex = nbindex+1
1589        kindex(nbindex) = (j-1)*iim+i
1590      ENDIF
1591    ENDDO
1592  ENDDO
1593  nbindex_w = nbindex
1594  ALLOC_ERR=-1
1595  ALLOCATE(kindex_w(nbindex_w), STAT=ALLOC_ERR)
1596  IF (ALLOC_ERR/=0) THEN
1597    WRITE(numout,*) "ERROR IN ALLOCATION of kindex_w : ",ALLOC_ERR
1598    STOP
1599  ENDIF
1600  kindex_w(:)=kindex(1:nbindex)
1601!-
1602  IF ( nbindex == 0 ) THEN
1603    WRITE(numout,*) 'Sorry, you are in the middle of the ocean. Check your coordinates.'
1604    STOP
1605  ELSE
1606    WRITE(numout,*) 'Number of continental points: ',nbindex
1607  ENDIF
1608
1609!-
1610! 10. clean up
1611!-
1612  DEALLOCATE (lon_file)
1613  DEALLOCATE (lat_file)
1614  DEALLOCATE (lsm_file)
1615
1616END SUBROUTINE weathgen_init
1617
1618!! ================================================================================================================================
1619!! SUBROUTINE   : weathgen_read_file
1620!!
1621!>\BRIEF         This subroutine allocates variables and reads files. 
1622!!
1623!! DESCRIPTION  : 
1624!!
1625!! RECENT CHANGE(S): None
1626!!
1627!! MAIN OUTPUT VARIABLE(S):
1628!!
1629!! REFERENCE(S) :
1630!!
1631!! FLOWCHART    : None
1632!! \n
1633!_ ================================================================================================================================
1634
1635SUBROUTINE weathgen_read_file &
1636     & (force_id,iim,jjm)
1637  !---------------------------------------------------------------------
1638  IMPLICIT NONE
1639  !-
1640
1641  !! 0. Variables and parameters declaration
1642
1643  REAL,PARAMETER  :: fcrit = .5
1644
1645  !! 0.1 Input variables
1646
1647  INTEGER,INTENT(IN)                  :: force_id
1648  INTEGER,INTENT(IN)                  :: iim, jjm
1649
1650  !! 0.4 Local variables
1651
1652  CHARACTER(LEN=30)               :: var_name
1653
1654  INTEGER,DIMENSION(iim*jjm)  :: kindex
1655  INTEGER                     :: nbindex
1656
1657  REAL,DIMENSION(iim*jjm)     :: xchamp
1658  REAL,DIMENSION(iim*jjm,nmon)  :: xchampm
1659
1660!_ ================================================================================================================================
1661
1662  kindex(:)=0
1663
1664#ifdef CPP_PARA
1665  nbindex=nbp_loc
1666  CALL scatter(index_g,kindex)
1667  kindex(1:nbindex)=kindex(1:nbindex)-(jj_begin-1)*iim_g
1668#else
1669  ! Copy saved land points index
1670  nbindex = nbindex_w
1671  kindex(1:nbindex_w) = kindex_w(:)
1672#endif
1673
1674!-
1675
1676  ALLOC_ERR=-1
1677  ALLOCATE(lat_land(nbindex), STAT=ALLOC_ERR)
1678  IF (ALLOC_ERR/=0) THEN
1679    WRITE(numout,*) "ERROR IN ALLOCATION of lat_land : ",ALLOC_ERR
1680    STOP
1681  ENDIF
1682
1683!-
1684! 8 topography
1685!-
1686
1687  ALLOC_ERR=-1
1688  ALLOCATE(xintopo(nbindex), STAT=ALLOC_ERR)
1689  IF (ALLOC_ERR/=0) THEN
1690    WRITE(numout,*) "ERROR IN ALLOCATION of xintopo : ",ALLOC_ERR
1691    STOP
1692  ENDIF
1693!-
1694  var_name='altitude'
1695  CALL weather_read (force_id,var_name,iim_file,jjm_file,1,i_cut, &
1696                     iim,jjm,n_agg,ncorr,icorr,jcorr,xchamp)
1697  xintopo(:)=xchamp(kindex(1:nbindex))
1698!-
1699! 9. Allocate and read the monthly fields
1700!-
1701
1702  ALLOC_ERR=-1
1703  ALLOCATE(xinwet(nbindex,nmon), STAT=ALLOC_ERR)
1704  IF (ALLOC_ERR/=0) THEN
1705    WRITE(numout,*) "ERROR IN ALLOCATION of xinwet : ",ALLOC_ERR
1706    STOP
1707  ENDIF
1708  var_name='prs'
1709  CALL weather_read (force_id,var_name,iim_file,jjm_file,nmon,i_cut, &
1710                     iim,jjm,n_agg,ncorr,icorr,jcorr,xchampm)
1711  xinwet(:,:)=xchampm(kindex(1:nbindex),:)
1712  !-
1713
1714  ALLOC_ERR=-1
1715  ALLOCATE(xinprec(nbindex,nmon), STAT=ALLOC_ERR)
1716  IF (ALLOC_ERR/=0) THEN
1717    WRITE(numout,*) "ERROR IN ALLOCATION of xinprec : ",ALLOC_ERR
1718    STOP
1719  ENDIF
1720  var_name='prm'
1721  CALL weather_read (force_id,var_name,iim_file,jjm_file,nmon,i_cut, &
1722                     iim,jjm,n_agg,ncorr,icorr,jcorr,xchampm)
1723  xinprec(:,:)=xchampm(kindex(1:nbindex),:)
1724!-
1725 
1726  ALLOC_ERR=-1
1727  ALLOCATE(xint(nbindex,nmon), STAT=ALLOC_ERR)
1728  IF (ALLOC_ERR/=0) THEN
1729    WRITE(numout,*) "ERROR IN ALLOCATION of xint : ",ALLOC_ERR
1730    STOP
1731  ENDIF
1732  var_name='t2m'
1733  CALL weather_read (force_id,var_name,iim_file,jjm_file,nmon,i_cut, &
1734                     iim,jjm,n_agg,ncorr,icorr,jcorr,xchampm)
1735  xint(:,:)=xchampm(kindex(1:nbindex),:)
1736!-
1737
1738  ALLOC_ERR=-1
1739  ALLOCATE(xinq(nbindex,nmon), STAT=ALLOC_ERR)
1740  IF (ALLOC_ERR/=0) THEN
1741    WRITE(numout,*) "ERROR IN ALLOCATION of xinq : ",ALLOC_ERR
1742    STOP
1743  ENDIF
1744  var_name='r2m'
1745  CALL weather_read (force_id,var_name,iim_file,jjm_file,nmon,i_cut, &
1746                     iim,jjm,n_agg,ncorr,icorr,jcorr,xchampm)
1747  xinq(:,:)=xchampm(kindex(1:nbindex),:)
1748!-
1749
1750  ALLOC_ERR=-1
1751  ALLOCATE(xinwind(nbindex,nmon), STAT=ALLOC_ERR)
1752  IF (ALLOC_ERR/=0) THEN
1753    WRITE(numout,*) "ERROR IN ALLOCATION of xinwind : ",ALLOC_ERR
1754    STOP
1755  ENDIF
1756  var_name='uv10m'
1757  CALL weather_read (force_id,var_name,iim_file,jjm_file,nmon,i_cut, &
1758                     iim,jjm,n_agg,ncorr,icorr,jcorr,xchampm)
1759  xinwind(:,:)=xchampm(kindex(1:nbindex),:)
1760!-
1761
1762  ALLOC_ERR=-1
1763  ALLOCATE(xincld(nbindex,nmon), STAT=ALLOC_ERR)
1764  IF (ALLOC_ERR/=0) THEN
1765    WRITE(numout,*) "ERROR IN ALLOCATION of xincld : ",ALLOC_ERR
1766    STOP
1767  ENDIF
1768  var_name='tc'
1769  CALL weather_read (force_id,var_name,iim_file,jjm_file,nmon,i_cut, &
1770                       iim,jjm,n_agg,ncorr,icorr,jcorr,xchampm)
1771  xincld(:,:)=xchampm(kindex(1:nbindex),:)
1772!-
1773
1774  ALLOC_ERR=-1
1775  ALLOCATE(xintrng(nbindex,nmon), STAT=ALLOC_ERR)
1776  IF (ALLOC_ERR/=0) THEN
1777    WRITE(numout,*) "ERROR IN ALLOCATION of xintrng : ",ALLOC_ERR
1778    STOP
1779  ENDIF
1780  var_name='t2a'
1781  CALL weather_read (force_id,var_name,iim_file,jjm_file,nmon,i_cut, &
1782                       iim,jjm,n_agg,ncorr,icorr,jcorr,xchampm)
1783  xintrng(:,:)=xchampm(kindex(1:nbindex),:)
1784!-
1785! 10. clean up
1786!-
1787  IF (is_root_prc) THEN
1788     DEALLOCATE (ncorr)
1789     DEALLOCATE (icorr)
1790     DEALLOCATE (jcorr)
1791  ENDIF
1792
1793!-
1794! 12. Allocate space for daily mean values
1795!-
1796
1797  ALLOC_ERR=-1
1798  ALLOCATE(iwet(nbindex), STAT=ALLOC_ERR)
1799  IF (ALLOC_ERR/=0) THEN
1800    WRITE(numout,*) "ERROR IN ALLOCATION of iwet : ",ALLOC_ERR
1801    STOP
1802  ENDIF
1803!-
1804
1805  ALLOC_ERR=-1
1806  ALLOCATE(psurfm0(nbindex), STAT=ALLOC_ERR)
1807  IF (ALLOC_ERR/=0) THEN
1808    WRITE(numout,*) "ERROR IN ALLOCATION of psurfm0 : ",ALLOC_ERR
1809    STOP
1810  ENDIF
1811
1812  ALLOC_ERR=-1
1813  ALLOCATE(cloudm0(nbindex), STAT=ALLOC_ERR)
1814  IF (ALLOC_ERR/=0) THEN
1815    WRITE(numout,*) "ERROR IN ALLOCATION of cloudm0 : ",ALLOC_ERR
1816    STOP
1817  ENDIF
1818
1819  ALLOC_ERR=-1
1820  ALLOCATE(tmaxm0(nbindex), STAT=ALLOC_ERR)
1821  IF (ALLOC_ERR/=0) THEN
1822    WRITE(numout,*) "ERROR IN ALLOCATION of tmaxm0 : ",ALLOC_ERR
1823    STOP
1824  ENDIF
1825
1826  ALLOC_ERR=-1
1827  ALLOCATE(tminm0(nbindex), STAT=ALLOC_ERR)
1828  IF (ALLOC_ERR/=0) THEN
1829    WRITE(numout,*) "ERROR IN ALLOCATION of tminm0 : ",ALLOC_ERR
1830    STOP
1831  ENDIF
1832
1833  ALLOC_ERR=-1
1834  ALLOCATE(qdm0(nbindex), STAT=ALLOC_ERR)
1835  IF (ALLOC_ERR/=0) THEN
1836    WRITE(numout,*) "ERROR IN ALLOCATION of qdm0 : ",ALLOC_ERR
1837    STOP
1838  ENDIF
1839
1840  ALLOC_ERR=-1
1841  ALLOCATE(udm0(nbindex), STAT=ALLOC_ERR)
1842  IF (ALLOC_ERR/=0) THEN
1843    WRITE(numout,*) "ERROR IN ALLOCATION of udm0 : ",ALLOC_ERR
1844    STOP
1845  ENDIF
1846
1847  ALLOC_ERR=-1
1848  ALLOCATE(precipm0(nbindex), STAT=ALLOC_ERR)
1849  IF (ALLOC_ERR/=0) THEN
1850    WRITE(numout,*) "ERROR IN ALLOCATION of precipm0 : ",ALLOC_ERR
1851    STOP
1852  ENDIF
1853!-
1854
1855  ALLOC_ERR=-1
1856  ALLOCATE(psurfm1(nbindex), STAT=ALLOC_ERR)
1857  IF (ALLOC_ERR/=0) THEN
1858    WRITE(numout,*) "ERROR IN ALLOCATION of psurfm1 : ",ALLOC_ERR
1859    STOP
1860  ENDIF
1861
1862  ALLOC_ERR=-1
1863  ALLOCATE(cloudm1(nbindex), STAT=ALLOC_ERR)
1864  IF (ALLOC_ERR/=0) THEN
1865    WRITE(numout,*) "ERROR IN ALLOCATION of cloudm1 : ",ALLOC_ERR
1866    STOP
1867  ENDIF
1868
1869  ALLOC_ERR=-1
1870  ALLOCATE(tmaxm1(nbindex), STAT=ALLOC_ERR)
1871  IF (ALLOC_ERR/=0) THEN
1872    WRITE(numout,*) "ERROR IN ALLOCATION of tmaxm1 : ",ALLOC_ERR
1873    STOP
1874  ENDIF
1875
1876  ALLOC_ERR=-1
1877  ALLOCATE(tminm1(nbindex), STAT=ALLOC_ERR)
1878  IF (ALLOC_ERR/=0) THEN
1879    WRITE(numout,*) "ERROR IN ALLOCATION of tminm1 : ",ALLOC_ERR
1880    STOP
1881  ENDIF
1882
1883  ALLOC_ERR=-1
1884  ALLOCATE(qdm1(nbindex), STAT=ALLOC_ERR)
1885  IF (ALLOC_ERR/=0) THEN
1886    WRITE(numout,*) "ERROR IN ALLOCATION of qdm1 : ",ALLOC_ERR
1887    STOP
1888  ENDIF
1889
1890  ALLOC_ERR=-1
1891  ALLOCATE(udm1(nbindex), STAT=ALLOC_ERR)
1892  IF (ALLOC_ERR/=0) THEN
1893    WRITE(numout,*) "ERROR IN ALLOCATION of udm1 : ",ALLOC_ERR
1894    STOP
1895  ENDIF
1896
1897  ALLOC_ERR=-1
1898  ALLOCATE(precipm1(nbindex), STAT=ALLOC_ERR)
1899  IF (ALLOC_ERR/=0) THEN
1900    WRITE(numout,*) "ERROR IN ALLOCATION of precipm1 : ",ALLOC_ERR
1901    STOP
1902  ENDIF
1903END SUBROUTINE weathgen_read_file
1904!
1905!=
1906!
1907
1908!! ================================================================================================================================
1909!! SUBROUTINE   : weathgen_begin
1910!!
1911!>\BRIEF         This subroutines initializes variables or reads restart values.
1912!!
1913!! DESCRIPTION  : None
1914!!
1915!! RECENT CHANGE(S): None
1916!!
1917!! MAIN OUTPUT VARIABLE(S): ::nbindex, ::tair, ::pb, ::qair, ::kindex
1918!!
1919!! REFERENCE(S) :
1920!!
1921!! FLOWCHART    : None
1922!! \n
1923!_ ================================================================================================================================
1924
1925SUBROUTINE weathgen_begin ( &
1926     & dt_force,itau, date0, &
1927     & rest_id,iim,jjm, &
1928     & lon,lat,tair,pb,qair,kindex,nbindex)
1929  !---------------------------------------------------------------------
1930  IMPLICIT NONE
1931
1932  !-
1933
1934  !! 0. Variables and parameters declaration
1935
1936  !! 0.1 Input variables
1937
1938  REAL,INTENT(IN)                     :: dt_force, date0
1939  INTEGER,INTENT(IN)                  :: itau
1940  INTEGER,INTENT(IN)                  :: rest_id
1941  INTEGER,INTENT(IN)                  :: iim, jjm
1942  REAL,DIMENSION(iim,jjm),INTENT(IN)  :: lon,lat
1943
1944  !! 0.2 Output variables
1945
1946  INTEGER,INTENT(OUT)                     :: nbindex
1947  INTEGER,DIMENSION(iim*jjm),INTENT(OUT)  :: kindex
1948  REAL,DIMENSION(iim,jjm),INTENT(OUT)     :: tair,pb,qair
1949
1950  !! 0.4 Local variables
1951
1952  INTEGER  :: i, j, ij
1953  REAL     :: val_exp
1954  REAL,DIMENSION(iim*jjm)               :: xchamp
1955  REAL,DIMENSION(iim_g*jjm_g)           :: xchamp_g
1956  CHARACTER(LEN=30)                     :: var_name
1957  REAL,DIMENSION(1)                     :: jullasttab
1958  REAL,DIMENSION(seedsize_max)          :: seed_in_file
1959  INTEGER,DIMENSION(:), ALLOCATABLE     :: seed_in_proc
1960  INTEGER  :: seedsize, iret
1961  INTEGER  :: nlonid, nlatid, nlonid1, nlatid1, tdimid1, varid
1962  INTEGER  :: ndim, dims(4)
1963  CHARACTER(LEN=30) :: assoc
1964  CHARACTER(LEN=70) :: str70
1965  CHARACTER(LEN=80) :: stamp
1966  INTEGER  :: yy_b, mm_b, dd_b, hh, mm
1967  REAL     :: ss
1968  CHARACTER(LEN=10) :: today, att
1969  INTEGER  :: nlandid1, nlandid, nlevid, nlevid1
1970  REAL     :: lev_max, lev_min
1971  REAL     :: height_lev1
1972  INTEGER  :: imois
1973  REAL     :: xx, td
1974
1975!_ ================================================================================================================================
1976
1977  kindex(:)=0
1978
1979#ifdef CPP_PARA
1980  nbindex=nbp_loc
1981  CALL scatter(index_g,kindex)
1982  kindex(1:nbindex)=kindex(1:nbindex)-(jj_begin-1)*iim_g
1983#else
1984  ! Copy saved land points index
1985  nbindex = nbindex_w
1986  kindex(1:nbindex_w) = kindex_w(:)
1987#endif
1988!-
1989! 13. Prescribed or statistical values?
1990!-
1991  !Config Key   = IPPREC
1992  !Config Desc  = Use prescribed values
1993  !Config If    = ALLOW_WEATHERGEN
1994  !Config Def   = 0
1995  !Config Help  = If this is set to 1, the weather generator
1996  !Config         uses the monthly mean values for daily means.
1997  !Config         If it is set to 0, the weather generator
1998  !Config         uses statistical relationships to derive daily
1999  !Config         values from monthly means.
2000  !Config Units = [-]
2001  ipprec = 0
2002  CALL getin_p ('IPPREC',ipprec)
2003  WRITE(numout,*) 'IPPREC: ',ipprec
2004!-
2005! 14. Do we want exact monthly precipitations even with ipprec=0 ?
2006!-
2007  !Config Key   = WEATHGEN_PRECIP_EXACT
2008  !Config Desc  = Exact monthly precipitation
2009  !Config If    = ALLOW_WEATHERGEN
2010  !Config Def   = n
2011  !Config Help  = If this is set to y, the weather generator
2012  !Config         will generate pseudo-random precipitations
2013  !Config         whose monthly mean is exactly the prescribed one.
2014  !Config         In this case, the daily precipitation (for rainy
2015  !Config         days) is constant (that is, some days have 0 precip,
2016  !Config         the other days have precip=Precip_month/n_precip,
2017  !Config         where n_precip is the prescribed number of rainy days
2018  !Config         per month).
2019  !Config Units = [FLAG]
2020  precip_exact = .FALSE.
2021  CALL getin_p ('WEATHGEN_PRECIP_EXACT',precip_exact)
2022  WRITE(numout,*) 'PRECIP_EXACT: ',precip_exact
2023
2024!-
2025! 15. Read restart file
2026!-
2027  CALL ioget_expval (val_exp)
2028!-
2029  var_name= 'julian'
2030  IF (is_root_prc) THEN
2031     CALL restget (rest_id,var_name,1,1,1,itau,.TRUE.,jullasttab)
2032     IF (jullasttab(1) == val_exp) THEN
2033        jullasttab(1) = itau2date(itau-1, date0, dt_force)
2034     ENDIF
2035  ENDIF
2036  CALL bcast(jullasttab)
2037  julian_last = jullasttab(1)
2038!-
2039  var_name= 'seed'
2040  IF (is_root_prc) &
2041       CALL restget (rest_id,var_name,seedsize_max, &
2042 &              1,1,itau,.TRUE.,seed_in_file)
2043  CALL bcast(seed_in_file)
2044  IF (ALL(seed_in_file(:) == val_exp)) THEN
2045!---
2046!-- there is no need to reinitialize the random number generator as
2047!-- this does not seem to be a restart
2048!---
2049    CONTINUE
2050  ELSE
2051!---
2052!-- reinitialize the random number generator
2053!---
2054     IF (is_root_prc) &
2055          CALL RANDOM_SEED( SIZE = seedsize )
2056     CALL bcast(seedsize)
2057     IF (seedsize > seedsize_max) THEN
2058        STOP 'weathgen_begin: increase seedsize_max'
2059     ENDIF
2060 
2061     IF (precip_exact) THEN
2062!---
2063!-- preparer un tableau utilise pour determiner s'il pleut ou pas
2064!-- (en fct. du nombre de jours de pluie par mois).
2065!---
2066        IF (is_root_prc) THEN
2067           DO imois=1,12
2068              CALL permute (ndaypm(imois),jour_precip(:,imois))
2069           ENDDO
2070        ENDIF
2071       CALL bcast(jour_precip)
2072    ENDIF
2073
2074    ALLOC_ERR=-1
2075    ALLOCATE(seed_in_proc(seedsize), STAT=ALLOC_ERR)
2076    IF (ALLOC_ERR/=0) THEN
2077      WRITE(numout,*) "ERROR IN ALLOCATION of seed_in_proc : ",ALLOC_ERR
2078      STOP
2079    ENDIF
2080    seed_in_proc(1:seedsize) = NINT( seed_in_file(1:seedsize) )
2081    CALL RANDOM_SEED (PUT = seed_in_proc)
2082    DEALLOCATE( seed_in_proc )
2083 ENDIF
2084!-
2085  var_name= 'iwet'
2086  IF (is_root_prc) THEN
2087    CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2088    IF (ALL(xchamp_g(:) == val_exp)) THEN
2089      xchamp_g(:) = zero
2090    ENDIF
2091  ENDIF
2092  CALL scatter2D_mpi(xchamp_g,xchamp)
2093  iwet(:) = NINT(xchamp(kindex(1:nbindex)))
2094!-
2095  var_name= 'psurfm0'
2096  IF (is_root_prc) THEN
2097     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2098     IF (ALL(xchamp_g(:) == val_exp)) THEN
2099        xchamp_g(:) = 100000.
2100     ENDIF
2101  ENDIF
2102  CALL scatter2D_mpi(xchamp_g,xchamp)
2103  psurfm0(:) = xchamp(kindex(1:nbindex))
2104!-
2105  var_name= 'cloudm0'
2106  IF (is_root_prc) THEN
2107     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2108     IF (ALL(xchamp_g(:) == val_exp)) THEN
2109        xchamp_g(:) = .5
2110     ENDIF
2111  ENDIF
2112  CALL scatter2D_mpi(xchamp_g,xchamp)
2113  cloudm0(:) = xchamp(kindex(1:nbindex))
2114!-
2115  var_name= 'tmaxm0'
2116  IF (is_root_prc) THEN
2117     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2118     IF (ALL(xchamp_g(:) == val_exp)) THEN
2119        xchamp_g(:) = 285.
2120     ENDIF
2121  ENDIF
2122  CALL scatter2D_mpi(xchamp_g,xchamp)
2123  tmaxm0(:) = xchamp(kindex(1:nbindex))
2124!-
2125  var_name= 'tminm0'
2126  IF (is_root_prc) THEN
2127     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2128     IF (ALL(xchamp_g(:) == val_exp)) THEN
2129        xchamp_g(:) = 275.
2130     ENDIF
2131  ENDIF
2132  CALL scatter2D_mpi(xchamp_g,xchamp)
2133  tminm0(:) = xchamp(kindex(1:nbindex))
2134!-
2135  var_name= 'qdm0'
2136  IF (is_root_prc) THEN
2137     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2138     IF (ALL(xchamp_g(:) == val_exp)) THEN
2139        xchamp_g(:) = 1.E-03
2140     ENDIF
2141  ENDIF
2142  CALL scatter2D_mpi(xchamp_g,xchamp)
2143  qdm0(:) = xchamp(kindex(1:nbindex))
2144!-
2145  var_name= 'udm0'
2146  IF (is_root_prc) THEN
2147     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2148     IF (ALL(xchamp_g(:) == val_exp)) THEN
2149        xchamp_g(:) = 2.
2150     ENDIF
2151  ENDIF
2152  CALL scatter2D_mpi(xchamp_g,xchamp)
2153  udm0(:) = xchamp(kindex(1:nbindex))
2154!-
2155  var_name= 'precipm0'
2156  IF (is_root_prc) THEN
2157     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2158     IF (ALL(xchamp_g(:) == val_exp)) THEN
2159        xchamp_g(:) = 1.
2160     ENDIF
2161  ENDIF
2162  CALL scatter2D_mpi(xchamp_g,xchamp)
2163  precipm0(:) = xchamp(kindex(1:nbindex))
2164!-
2165  var_name= 'psurfm1'
2166  IF (is_root_prc) THEN
2167     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2168     IF (ALL(xchamp_g(:) == val_exp)) THEN
2169        xchamp_g(:) = 100000.
2170     ENDIF
2171  ENDIF
2172  CALL scatter2D_mpi(xchamp_g,xchamp)
2173  psurfm1(:) = xchamp(kindex(1:nbindex))
2174!-
2175  var_name= 'cloudm1'
2176  IF (is_root_prc) THEN
2177     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2178     IF (ALL(xchamp_g(:) == val_exp)) THEN
2179        xchamp_g(:) = .5
2180     ENDIF
2181  ENDIF
2182  CALL scatter2D_mpi(xchamp_g,xchamp)
2183  cloudm1(:) = xchamp(kindex(1:nbindex))
2184!-
2185  var_name= 'tmaxm1'
2186  IF (is_root_prc) THEN
2187     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2188     IF (ALL(xchamp_g(:) == val_exp)) THEN
2189        xchamp_g(:) = 285.
2190     ENDIF
2191  ENDIF
2192  CALL scatter2D_mpi(xchamp_g,xchamp)
2193  tmaxm1(:) = xchamp(kindex(1:nbindex))
2194!-
2195  var_name= 'tminm1'
2196  IF (is_root_prc) THEN
2197     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2198     IF (ALL(xchamp_g(:) == val_exp)) THEN
2199        xchamp_g(:) = 275.
2200     ENDIF
2201  ENDIF
2202  CALL scatter2D_mpi(xchamp_g,xchamp)
2203  tminm1(:) = xchamp(kindex(1:nbindex))
2204!-
2205  var_name= 'qdm1'
2206  IF (is_root_prc) THEN
2207     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2208     IF (ALL(xchamp_g(:) == val_exp)) THEN
2209        xchamp_g(:) = 1.E-03
2210     ENDIF
2211  ENDIF
2212  CALL scatter2D_mpi(xchamp_g,xchamp)
2213  qdm1(:) = xchamp(kindex(1:nbindex))
2214!-
2215  var_name= 'udm1'
2216  IF (is_root_prc) THEN
2217     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2218     IF (ALL(xchamp_g(:) == val_exp)) THEN
2219        xchamp_g(:) = 2.
2220     ENDIF
2221  ENDIF
2222  CALL scatter2D_mpi(xchamp_g,xchamp)
2223  udm1(:) = xchamp(kindex(1:nbindex))
2224!-
2225  var_name= 'precipm1'
2226  IF (is_root_prc) THEN
2227     CALL restget (rest_id, var_name, iim_g, jjm_g, 1, itau, .TRUE., xchamp_g)
2228     IF (ALL(xchamp_g(:) == val_exp)) THEN
2229        xchamp_g(:) = 1.
2230     ENDIF
2231  ENDIF
2232  CALL scatter2D_mpi(xchamp_g,xchamp)
2233  precipm1(:) = xchamp(kindex(1:nbindex))
2234
2235!-
2236! 16. We still need instantaneous tair, qair, and the surface pressure
2237!     We take daily mean values read from the restart file
2238!-
2239!!$  tair(:,:)=280.
2240!!$  qair(:,:)=1.E-03
2241!!$  pb(:,:)=101325
2242  tair(:,:)=val_exp
2243  qair(:,:)=val_exp
2244  pb(:,:)=val_exp
2245  xx = cte_grav/rair/0.0065
2246  DO ij=1,nbindex
2247     j = ((kindex(ij)-1)/iim) + 1
2248     i = kindex(ij) - (j-1)*iim
2249     
2250     lat_land(ij) = lat(i,j)
2251     
2252     td =  (tmaxm0(ij)+tminm0(ij))/2.
2253     tair(i,j) = td
2254     qair(i,j) = qdm1(ij)
2255     pb(i,j) = 101325.*(td/(td+0.0065*xintopo(ij)))**xx
2256  ENDDO
2257!-
2258! 17. We can write a forcing file for Orchidee
2259!     from this weather Generator run.
2260!-
2261  !Config Key   = DUMP_WEATHER
2262  !Config Desc  = Write weather from generator into a forcing file
2263  !Config If    = ALLOW_WEATHERGEN 
2264  !Config Def   = n
2265  !Config Help  = This flag makes the weather generator dump its
2266  !Config         generated weather into a forcing file which can
2267  !Config         then be used to get the same forcing on different
2268  !Config         machines. This only works correctly if there is
2269  !Config         a restart file (otherwise the forcing at the first
2270  !Config         time step is slightly wrong).
2271  !Config Units = [FLAG]
2272  dump_weather = .FALSE.
2273  CALL getin_p ('DUMP_WEATHER',dump_weather)
2274!-
2275  IF (dump_weather .AND. is_root_prc) THEN
2276!---
2277!-- Initialize the file
2278!---
2279     !Config Key   = DUMP_WEATHER_FILE
2280     !Config Desc  = Name of the file that contains the weather from generator
2281     !Config If    = DUMP_WEATHER
2282     !Config Def   = weather_dump.nc
2283     !Config Help  =
2284     !Config Units = [FILE]
2285    dump_weather_file = 'weather_dump.nc'
2286    CALL getin ('DUMP_WEATHER_FILE',dump_weather_file)
2287!---
2288    !Config Key   = DUMP_WEATHER_GATHERED
2289    !Config Desc  = Dump weather data on gathered grid
2290    !Config If    = DUMP_WEATHER
2291    !Config Def   = y
2292    !Config Help  = If 'y', the weather data are gathered for all land points.
2293    !Config Units = [FLAG]
2294    gathered = .TRUE.
2295    CALL getin ('DUMP_WEATHER_GATHERED',gathered)
2296!---
2297    iret = NF90_CREATE (TRIM(dump_weather_file),NF90_CLOBBER,dump_id)
2298!---
2299!-- Dimensions
2300!---
2301    iret = NF90_DEF_DIM (dump_id,'x',iim_g,nlonid1)
2302    iret = NF90_DEF_DIM (dump_id,'y',jjm_g,nlatid1)
2303    iret = NF90_DEF_DIM (dump_id,'z',  1,nlevid1)
2304!---
2305    IF (gathered) THEN
2306      iret = NF90_DEF_DIM (dump_id,'land',nbp_glo,nlandid1)
2307    ENDIF
2308    iret = NF90_DEF_DIM (dump_id,'tstep',NF90_UNLIMITED,tdimid1)
2309!---
2310!-- Coordinate variables
2311!---
2312    dims(1:2) = (/ nlonid1, nlatid1 /)
2313!---
2314    iret = NF90_DEF_VAR (dump_id,'nav_lon',n_rtp,dims(1:2),nlonid)
2315    iret = NF90_PUT_ATT (dump_id,nlonid,'units',"degrees_east")
2316    iret = NF90_PUT_ATT (dump_id,nlonid,'valid_min',MINVAL(lon_g))
2317    iret = NF90_PUT_ATT (dump_id,nlonid,'valid_max',MAXVAL(lon_g))
2318    iret = NF90_PUT_ATT (dump_id,nlonid,'long_name',"Longitude")
2319!---
2320    iret = NF90_DEF_VAR (dump_id,'nav_lat',n_rtp,dims(1:2),nlatid)
2321    iret = NF90_PUT_ATT (dump_id,nlatid,'units',"degrees_north")
2322    iret = NF90_PUT_ATT (dump_id,nlatid,'valid_min',MINVAL(lat_g))
2323    iret = NF90_PUT_ATT (dump_id,nlatid,'valid_max',MAXVAL(lat_g))
2324    iret = NF90_PUT_ATT (dump_id,nlatid,'long_name',"Latitude")
2325!---
2326    height_lev1 = 10.
2327    !Config Key   = HEIGHT_LEV1_DUMP
2328    !Config Desc  =
2329    !Config If    = DUMP_WEATHER
2330    !Config Def   = 10.
2331    !Config Help  =
2332    !Config Units = [m]
2333    CALL getin ('HEIGHT_LEV1_DUMP',height_lev1)
2334    lev_min = height_lev1
2335    lev_max = height_lev1
2336!---
2337    iret = NF90_DEF_VAR (dump_id,'level',n_rtp,(/ nlevid1 /),nlevid)
2338    iret = NF90_PUT_ATT (dump_id,nlevid,'units',"m")
2339    iret = NF90_PUT_ATT (dump_id,nlevid,'valid_min',lev_min)
2340    iret = NF90_PUT_ATT (dump_id,nlevid,'valid_max',lev_max)
2341    iret = NF90_PUT_ATT (dump_id,nlevid,'long_name',"Vertical levels")
2342!---
2343    IF (gathered) THEN
2344      iret = NF90_DEF_VAR (dump_id,'land',NF90_INT,(/ nlandid1 /),nlandid)
2345      iret = NF90_PUT_ATT (dump_id,nlandid,'compress',"y x")
2346    ENDIF
2347!---
2348!-- Store the time axes.
2349!---
2350    iret = NF90_DEF_VAR (dump_id,'time',n_rtp,tdimid1,time_id)
2351
2352    yy_b=0
2353    mm_b=1
2354    dd_b=1
2355    hh=00
2356    mm=00
2357    ss=0.
2358
2359    WRITE (str70,7000) yy_b, mm_b, dd_b, hh, mm, INT(ss)
2360    iret = NF90_PUT_ATT (dump_id,time_id,'units',TRIM(str70))
2361    iret = NF90_PUT_ATT (dump_id,time_id,'calendar',TRIM(calendar_str))
2362    iret = NF90_PUT_ATT (dump_id,time_id,'title','Time')
2363    iret = NF90_PUT_ATT (dump_id,time_id,'long_name','Time axis')
2364    WRITE(str70,7001) yy_b, cal(mm_b), dd_b, hh, mm, INT(ss)
2365    iret = NF90_PUT_ATT (dump_id,time_id,'time_origin',TRIM(str70))
2366!---
2367!-- Time steps
2368!---
2369    iret = NF90_DEF_VAR (dump_id,'timestp',NF90_INT,tdimid1,timestp_id)
2370    WRITE(str70,7002) yy_b, mm_b, dd_b, hh, mm, INT(ss)
2371    iret = NF90_PUT_ATT (dump_id,timestp_id,'units',TRIM(str70))
2372    iret = NF90_PUT_ATT (dump_id,timestp_id,'title','Time steps')
2373    iret = NF90_PUT_ATT (dump_id,timestp_id,'tstep_sec',dt_force)
2374    iret = NF90_PUT_ATT &
2375 &           (dump_id,timestp_id,'long_name','Time step axis')
2376    WRITE(str70,7001) yy_b, cal(mm_b), dd_b, hh, mm, INT(ss)
2377    iret = NF90_PUT_ATT (dump_id,timestp_id,'time_origin',TRIM(str70))
2378!---
23797000 FORMAT('seconds since ',I4.4,'-',I2.2,'-',I2.2,' ',I2.2,':',I2.2,':',I2.2)
23807001 FORMAT(' ',I4.4,'-',A3,'-',I2.2,' ',I2.2,':',I2.2,':',I2.2)
23817002 FORMAT('timesteps since ', I4.4,'-',I2.2,'-',I2.2,' ',I2.2,':',I2.2,':',I2.2)
2382!---
2383!-- The variables in the file are declared and their attributes
2384!-- written.
2385!---
2386    IF (gathered) THEN
2387      ndim = 2
2388      dims(1:2) = (/ nlandid1, tdimid1 /)
2389      assoc = 'time (nav_lat nav_lon)'
2390    ELSE
2391      ndim = 3
2392      dims(1:3) = (/ nlonid1, nlatid1, tdimid1 /)
2393      assoc = 'time nav_lat nav_lon'
2394    ENDIF
2395!---
2396    iret = NF90_DEF_VAR (dump_id,'SWdown',n_rtp,dims(1:ndim),varid)
2397    iret = NF90_PUT_ATT (dump_id,varid,'axis','TYX')
2398    iret = NF90_PUT_ATT (dump_id,varid,'units','W/m^2')
2399    iret = NF90_PUT_ATT (dump_id,varid,'long_name', &
2400 &                       'Surface incident shortwave radiation')
2401    iret = NF90_PUT_ATT (dump_id,varid,'associate',TRIM(assoc))
2402    iret = NF90_PUT_ATT (dump_id,varid,'missing_value',undef_sechiba)
2403    soldownid = varid
2404!---
2405    iret = NF90_DEF_VAR (dump_id,'Rainf',n_rtp,dims(1:ndim),varid)
2406    iret = NF90_PUT_ATT (dump_id,varid,'axis','TYX')
2407    iret = NF90_PUT_ATT (dump_id,varid,'units','kg/m^2s')
2408    iret = NF90_PUT_ATT (dump_id,varid,'long_name', &
2409 &                       'Rainfall rate')
2410    iret = NF90_PUT_ATT (dump_id,varid,'associate',TRIM(assoc))
2411    iret = NF90_PUT_ATT (dump_id,varid,'missing_value',undef_sechiba)
2412    rainfid = varid
2413!---
2414    iret = NF90_DEF_VAR (dump_id,'Snowf',n_rtp,dims(1:ndim),varid)
2415    iret = NF90_PUT_ATT (dump_id,varid,'axis','TYX')
2416    iret = NF90_PUT_ATT (dump_id,varid,'units','kg/m^2s')
2417    iret = NF90_PUT_ATT (dump_id,varid,'long_name', &
2418 &                       'Snowfall rate')
2419    iret = NF90_PUT_ATT (dump_id,varid,'associate',TRIM(assoc))
2420    iret = NF90_PUT_ATT (dump_id,varid,'missing_value',undef_sechiba)
2421    snowfid = varid
2422!---
2423    iret = NF90_DEF_VAR (dump_id,'LWdown',n_rtp,dims(1:ndim),varid)
2424    iret = NF90_PUT_ATT (dump_id,varid,'axis','TYX')
2425    iret = NF90_PUT_ATT (dump_id,varid,'units','W/m^2')
2426    iret = NF90_PUT_ATT (dump_id,varid,'long_name', &
2427 &                       'Surface incident longwave radiation')
2428    iret = NF90_PUT_ATT (dump_id,varid,'associate',TRIM(assoc))
2429    iret = NF90_PUT_ATT (dump_id,varid,'missing_value',undef_sechiba)
2430    lwradid = varid
2431!---
2432    iret = NF90_DEF_VAR (dump_id,'PSurf',n_rtp,dims(1:ndim),varid)
2433    iret = NF90_PUT_ATT (dump_id,varid,'axis','TYX')
2434    iret = NF90_PUT_ATT (dump_id,varid,'units','Pa')
2435    iret = NF90_PUT_ATT (dump_id,varid,'long_name', &
2436 &                       'Surface pressure')
2437    iret = NF90_PUT_ATT (dump_id,varid,'associate',TRIM(assoc))
2438    iret = NF90_PUT_ATT (dump_id,varid,'missing_value',undef_sechiba)
2439    psolid = varid
2440!---
2441!-- 3D Variables to be written
2442!---
2443    IF (gathered) THEN
2444      ndim = 3
2445      dims(1:3) = (/ nlandid1, nlevid1, tdimid1 /)
2446      assoc = 'time level (nav_lat nav_lon)'
2447    ELSE
2448      ndim = 4
2449      dims(1:4) = (/ nlonid1, nlatid1, nlevid1, tdimid1 /)
2450      assoc = 'time level nav_lat nav_lon'
2451    ENDIF
2452!---
2453    iret = NF90_DEF_VAR (dump_id,'Tair',n_rtp,dims(1:ndim),varid)
2454    iret = NF90_PUT_ATT (dump_id,varid,'axis','TZYX')
2455    iret = NF90_PUT_ATT (dump_id,varid,'units','K')
2456    iret = NF90_PUT_ATT (dump_id,varid,'long_name', &
2457 &                       'Near surface air temperature')
2458    iret = NF90_PUT_ATT (dump_id,varid,'associate',TRIM(assoc))
2459    iret = NF90_PUT_ATT (dump_id,varid,'missing_value',undef_sechiba)
2460    tairid = varid
2461!---
2462    iret = NF90_DEF_VAR (dump_id,'Qair',n_rtp,dims(1:ndim),varid)
2463    iret = NF90_PUT_ATT (dump_id,varid,'axis','TZYX')
2464    iret = NF90_PUT_ATT (dump_id,varid,'units','kg/kg')
2465    iret = NF90_PUT_ATT (dump_id,varid,'long_name', &
2466 &                       'Near surface specific humidity')
2467    iret = NF90_PUT_ATT (dump_id,varid,'associate',TRIM(assoc))
2468    iret = NF90_PUT_ATT (dump_id,varid,'missing_value',undef_sechiba)
2469    qairid = varid
2470!---
2471    iret = NF90_DEF_VAR (dump_id,'Wind_N',n_rtp,dims(1:ndim),varid)
2472    iret = NF90_PUT_ATT (dump_id,varid,'axis','TZYX')
2473    iret = NF90_PUT_ATT (dump_id,varid,'units','m/s')
2474    iret = NF90_PUT_ATT (dump_id,varid,'long_name', &
2475 &                       'Near surface northward wind component')
2476    iret = NF90_PUT_ATT (dump_id,varid,'associate',TRIM(assoc))
2477    iret = NF90_PUT_ATT (dump_id,varid,'missing_value',undef_sechiba)
2478    uid = varid
2479!---
2480    iret = NF90_DEF_VAR (dump_id,'Wind_E',n_rtp,dims(1:ndim),varid)
2481    iret = NF90_PUT_ATT (dump_id,varid,'axis','TZYX')
2482    iret = NF90_PUT_ATT (dump_id,varid,'units','m/s')
2483    iret = NF90_PUT_ATT (dump_id,varid,'long_name', &
2484 &                       'Near surface eastward wind component')
2485    iret = NF90_PUT_ATT (dump_id,varid,'associate',TRIM(assoc))
2486    iret = NF90_PUT_ATT (dump_id,varid,'missing_value',undef_sechiba)
2487    vid = varid
2488!---
2489!-- Global attributes
2490!---
2491    CALL DATE_AND_TIME (today, att)
2492    stamp = "WG, date: "//TRIM(today)//" at "//TRIM(att)
2493    iret = NF90_PUT_ATT (dump_id,NF90_GLOBAL,'Conventions',"GDT 1.2")
2494    iret = NF90_PUT_ATT (dump_id,NF90_GLOBAL,'file_name', &
2495 &                       TRIM(dump_weather_file))
2496    iret = NF90_PUT_ATT (dump_id,NF90_GLOBAL,'production',TRIM(stamp))
2497!---
2498!-- Finish the definition phase
2499!---
2500    iret = NF90_ENDDEF (dump_id)
2501!---
2502!--    Write coordinates
2503!---
2504    iret = NF90_PUT_VAR (dump_id,nlonid,lon_g)
2505    IF (iret /= NF90_NOERR) THEN
2506       WRITE(numout,*) iret
2507       CALL ipslerr_p (3,'weathgen_begin', &
2508 &          'Could not put variable nav_lon in the file : ', &
2509 &          TRIM(dump_weather_file),'(Solution ?)')
2510    ENDIF
2511    iret = NF90_PUT_VAR (dump_id,nlatid,lat_g)
2512    IF (iret /= NF90_NOERR) THEN
2513       WRITE(numout,*) iret
2514       CALL ipslerr_p (3,'weathgen_begin', &
2515 &          'Could not put variable nav_lat in the file : ', &
2516 &          TRIM(dump_weather_file),'(Solution ?)')
2517    ENDIF
2518    iret = NF90_PUT_VAR (dump_id,nlevid,height_lev1)
2519    IF (iret /= NF90_NOERR) THEN
2520       WRITE(numout,*) iret
2521       CALL ipslerr_p (3,'weathgen_begin', &
2522 &          'Could not put variable level in the file : ', &
2523 &          TRIM(dump_weather_file),'(Solution ?)')
2524    ENDIF
2525!---
2526    IF (gathered) THEN
2527       iret = NF90_PUT_VAR (dump_id,nlandid,index_g(1:nbp_glo))
2528       IF (iret /= NF90_NOERR) THEN
2529          WRITE(numout,*) iret
2530          CALL ipslerr_p (3,'weathgen_begin', &
2531 &          'Could not put variable land in the file : ', &
2532 &          TRIM(dump_weather_file),'(Solution ?)')
2533       ENDIF
2534    ENDIF
2535!---
2536 ENDIF ! dump_weather
2537!-----------------------------
2538END SUBROUTINE weathgen_begin
2539!-
2540!===
2541!-
2542!! ================================================================================================================================
2543!! SUBROUTINE   : weathgen_get
2544!!
2545!>\BRIEF        This subroutine initializes forcing values.
2546!!
2547!! DESCRIPTION  : None
2548!!
2549!! RECENT CHANGE(S): None
2550!!
2551!! MAIN OUTPUT VARIABLE(S): ::swdown, ::raina, ::snowa, ::tair, ::u, ::v, ::qair, ::psurf, ::lwdown
2552!!
2553!! REFERENCE(S) :
2554!!
2555!! FLOWCHART    : None
2556!! \n
2557!_ ================================================================================================================================
2558
2559SUBROUTINE weathgen_get &
2560& (itau, date0, dt_force, nbindex, nband, lat, &
2561&  swdown, raina, snowa, tair, u, v, qair, psurf, lwdown)
2562!---------------------------------------------------------------------
2563  IMPLICIT NONE
2564
2565  !! 0. Variables and parameters declaration
2566
2567  !! 0.1 Input variables
2568
2569  INTEGER,INTENT(IN)               :: itau      !! number of time step
2570  REAL,INTENT(IN)                  :: date0     !! date when itau was 0
2571  REAL,INTENT(IN)                  :: dt_force  !! time step (s)
2572  INTEGER,INTENT(IN)               :: nbindex   !! number of land points
2573  INTEGER,INTENT(IN)               :: nband     !! number of visible bands
2574  REAL,DIMENSION(nbindex),INTENT(IN)  :: lat    !! latitude (deg)
2575
2576  !! 0.2 Output variables 
2577
2578  REAL,DIMENSION(nbindex,nband),INTENT(OUT) :: swdown        !! Downward solar radiation @tex $(W.m^{-2})$ @endtex
2579  REAL,DIMENSION(nbindex),INTENT(OUT)       :: raina, snowa  !! precipitations @tex $(mm.day^{-1})$ @endtex
2580  REAL,DIMENSION(nbindex),INTENT(OUT)       :: tair          !! air temperature (K)
2581  REAL,DIMENSION(nbindex),INTENT(OUT)       :: u,v           !! wind speed @tex $(m.s^{-1})$ @endtex
2582  REAL,DIMENSION(nbindex),INTENT(OUT)       :: qair          !! air humidity @tex $(kg_h2o.kg_air^{-1})$ @endtex
2583  REAL,DIMENSION(nbindex),INTENT(OUT)       :: psurf         !! Surface pressure (Pa)
2584  REAL,DIMENSION(nbindex),INTENT(OUT)       :: lwdown        !! Downward long wave radiation @tex $(W.m^{-2})$ @endtex
2585
2586  !! 0.4 Local variables
2587
2588  REAL,DIMENSION(nbindex)        :: cloud, tmax, tmin, precipd, qd, ud
2589  REAL,DIMENSION(nbindex)        :: rh
2590  REAL,DIMENSION(nbindex,nband)  :: solai, solad
2591  REAL                        :: julian, jur
2592  REAL                        :: x
2593  INTEGER                     :: yy, mm, dd
2594  REAL                        :: ss, plens, time
2595
2596!_ ================================================================================================================================
2597
2598!-
2599! 1. get a reduced julian day
2600!-
2601  julian = itau2date(itau-1, date0, dt_force)
2602!S. Zaehle, test: solar noon at 12 o'clock!
2603!  julian = itau2date(itau, date0, dt_force)
2604  CALL ju2ymds (julian, yy, mm, dd, ss)
2605  CALL ymds2ju (yy,1,1,0.0, jur)
2606  julian = julian-jur
2607  CALL ju2ymds (julian, yy, mm, dd, ss)
2608!-
2609! 2. daily values
2610!-
2611  IF (INT(julian_last) /= INT(julian)) THEN
2612!-- today's values become yesterday's values
2613    cloudm1(:) = cloudm0(:)
2614    tmaxm1(:) = tmaxm0(:)
2615    tminm1(:) = tminm0(:)
2616    precipm1(:) = precipm0(:)
2617    qdm1(:) = qdm0(:)
2618    udm1(:) = udm0(:)
2619    psurfm1(:) = psurfm0(:)
2620!-- we have to get new daily values
2621!!$    WRITE(*,*) mpi_rank, "weathgen_get : date ",yy, mm, dd, ss
2622!!$    WRITE(*,*) mpi_rank, "weathgen_get : grid date ",year, month, day, sec
2623    CALL daily (nbindex, mm, dd, cloudm0, tmaxm0, tminm0, &
2624 &              precipm0, qdm0, udm0, psurfm0)
2625  ENDIF
2626!-
2627! 3. interpolate daily values
2628!    (otherwise we get ugly temperature jumps at midnight)
2629!-
2630  x = (julian-INT(julian))
2631!-
2632  cloud(:) = (1.-x)*cloudm1(:)+x*cloudm0(:)
2633  tmax(:) = (1.-x)*tmaxm1(:)+x*tmaxm0(:)
2634  tmin(:) = (1.-x)*tminm1(:)+x*tminm0(:)
2635  precipd(:) = (1.-x)*precipm1(:)+x*precipm0(:)
2636  qd(:) = (1.-x)*qdm1(:)+x*qdm0(:)
2637  ud(:) = (1.-x)*udm1(:)+x*udm0(:)
2638  psurf(:) = (1.-x)*psurfm1(:)+x*psurfm0(:)
2639!-
2640! 4. read instantaneous values
2641!-
2642  plens = one_day/dt_force
2643  time = (julian-REAL(INT(julian)))*one_day
2644!-
2645  CALL diurnal (nbindex, nband, time, NINT(julian), plens, 0., one_day, &
2646 &              lat, cloud, tmax, tmin, precipd, qd, ud, psurf, &
2647 &              lwdown, solad, solai, u, tair, qair, raina, snowa, rh)
2648!-
2649  raina(:) = raina(:)/dt_force
2650  snowa(:) = snowa(:)/dt_force
2651!-
2652  swdown(:,:) = solad(:,:)+solai(:,:)
2653!-
2654  v(:) = zero
2655!-
2656! 5. Store date
2657!-
2658  julian_last = julian
2659!--------------------------
2660END SUBROUTINE weathgen_get
2661!-
2662!===
2663!-
2664!! ================================================================================================================================
2665!! SUBROUTINE   : weathgen_restwrite
2666!!
2667!>\BRIEF         This subroutine writes data in the restart file.
2668!!
2669!! DESCRIPTION  : None
2670!!
2671!! RECENT CHANGE(S): None
2672!!
2673!! MAIN OUTPUT VARIABLE(S): None
2674!!
2675!! REFERENCE(S) :
2676!!
2677!! FLOWCHART    : None
2678!! \n
2679!_ ================================================================================================================================
2680
2681SUBROUTINE weathgen_restwrite (rest_id,itau,iim,jjm,nbindex,kindex)
2682!---------------------------------------------------------------------
2683  IMPLICIT NONE
2684!-
2685
2686  !! 0. Variables and parameters declaration
2687
2688  !! 0.1 Input variables
2689
2690  INTEGER,INTENT(IN)  :: rest_id,itau,iim,jjm,nbindex
2691  INTEGER,DIMENSION(iim*jjm),INTENT(IN) :: kindex
2692
2693  !! 0.4 Local variables
2694
2695  CHARACTER(LEN=30)                 :: var_name
2696  INTEGER                           :: i,j,ij
2697  REAL,DIMENSION(1)                 :: jullasttab
2698  REAL,DIMENSION(seedsize_max)      :: seed_in_file
2699  INTEGER,DIMENSION(:),ALLOCATABLE  :: seed_in_proc
2700  INTEGER                           :: seedsize
2701  REAL                              :: rndnum
2702  REAL,DIMENSION(iim*jjm)           :: xchamp
2703  REAL,DIMENSION(iim_g*jjm_g)       :: xchamp_g
2704
2705!_ ================================================================================================================================
2706
2707  var_name= 'julian'
2708  jullasttab(:) = julian_last
2709  IF (is_root_prc) CALL restput (rest_id, var_name, 1, 1, 1, itau, jullasttab)
2710!-
2711  IF (is_root_prc) THEN
2712     CALL RANDOM_SEED( SIZE = seedsize )
2713     IF (seedsize > seedsize_max) THEN
2714        STOP 'weathgen_restwrite: increase seedsize_max'
2715     ENDIF
2716  ENDIF
2717  CALL bcast(seedsize)
2718
2719  IF (is_root_prc) THEN
2720     ALLOC_ERR=-1
2721     ALLOCATE(seed_in_proc(seedsize), STAT=ALLOC_ERR)
2722     IF (ALLOC_ERR/=0) THEN
2723        WRITE(numout,*) "ERROR IN ALLOCATION of seed_in_proc : ",ALLOC_ERR
2724        STOP
2725     ENDIF
2726!-
2727     CALL RANDOM_SEED (GET = seed_in_proc)
2728!-
2729     seed_in_file(1:seedsize) = REAL(seed_in_proc(1:seedsize))
2730!-
2731! fill in the seed up to seedsize_max
2732! (useful in the case we restart on
2733!  a machine with a longer seed vector:
2734!  we do not want a degenerated seed)
2735!-
2736     DO i=seedsize+1,seedsize_max
2737        CALL RANDOM_NUMBER( rndnum )
2738        seed_in_file(i) = 100000.*rndnum
2739     ENDDO
2740  ENDIF
2741  CALL bcast (seed_in_file)
2742!-
2743  IF (is_root_prc) THEN
2744     DEALLOCATE( seed_in_proc )
2745!-
2746     var_name= 'seed'
2747     CALL restput (rest_id,var_name,seedsize_max,1,1,itau,seed_in_file)
2748  ENDIF
2749!-
2750
2751  xchamp(:) = val_exp
2752 
2753!!$  DO j=1,jjm
2754!!$    DO i=1,iim
2755!!$      ij = (j-1)*iim+i
2756!!$      xchamp(i,j) = REAL(iwet(ij))
2757!!$    ENDDO
2758!!$  ENDDO
2759  DO ij=1,nbindex
2760     xchamp(kindex(ij)) = REAL(iwet(ij))
2761  ENDDO
2762  var_name= 'iwet'
2763  CALL gather2D_mpi(xchamp,xchamp_g)
2764  IF (is_root_prc) THEN
2765     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2766  ENDIF
2767!-
2768  DO ij=1,nbindex
2769    xchamp(kindex(ij)) = psurfm0(ij)
2770  ENDDO
2771  var_name= 'psurfm0'
2772  CALL gather2D_mpi(xchamp,xchamp_g)
2773  IF (is_root_prc) THEN
2774     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2775  ENDIF
2776!-
2777  DO ij=1,nbindex
2778    xchamp(kindex(ij)) = cloudm0(ij)
2779  ENDDO
2780  var_name= 'cloudm0'
2781  CALL gather2D_mpi(xchamp,xchamp_g)
2782  IF (is_root_prc) THEN
2783     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2784  ENDIF
2785!-
2786  DO ij=1,nbindex
2787    xchamp(kindex(ij)) = tmaxm0(ij)
2788  ENDDO
2789  var_name= 'tmaxm0'
2790  CALL gather2D_mpi(xchamp,xchamp_g)
2791  IF (is_root_prc) THEN
2792     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2793  ENDIF
2794!-
2795  DO ij=1,nbindex
2796    xchamp(kindex(ij)) = tminm0(ij)
2797  ENDDO
2798  var_name= 'tminm0'
2799  CALL gather2D_mpi(xchamp,xchamp_g)
2800  IF (is_root_prc) THEN
2801     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2802  ENDIF
2803!-
2804  DO ij=1,nbindex
2805    xchamp(kindex(ij)) = qdm0(ij)
2806  ENDDO
2807  var_name= 'qdm0'
2808  CALL gather2D_mpi(xchamp,xchamp_g)
2809  IF (is_root_prc) THEN
2810     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2811  ENDIF
2812!-
2813  DO ij=1,nbindex
2814    xchamp(kindex(ij)) = udm0(ij)
2815  ENDDO
2816  var_name= 'udm0'
2817  CALL gather2D_mpi(xchamp,xchamp_g)
2818  IF (is_root_prc) THEN
2819     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2820  ENDIF
2821!-
2822  DO ij=1,nbindex
2823    xchamp(kindex(ij)) = precipm0(ij)
2824  ENDDO
2825  var_name= 'precipm0'
2826  CALL gather2D_mpi(xchamp,xchamp_g)
2827  IF (is_root_prc) THEN
2828     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2829  ENDIF
2830!-
2831  DO ij=1,nbindex
2832    xchamp(kindex(ij)) = psurfm1(ij)
2833  ENDDO
2834  var_name= 'psurfm1'
2835  CALL gather2D_mpi(xchamp,xchamp_g)
2836  IF (is_root_prc) THEN
2837     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2838  ENDIF
2839!-
2840  DO ij=1,nbindex
2841    xchamp(kindex(ij)) = cloudm1(ij)
2842  ENDDO
2843  var_name= 'cloudm1'
2844  CALL gather2D_mpi(xchamp,xchamp_g)
2845  IF (is_root_prc) THEN
2846     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2847  ENDIF
2848!-
2849  DO ij=1,nbindex
2850    xchamp(kindex(ij)) = tmaxm1(ij)
2851  ENDDO
2852  var_name= 'tmaxm1'
2853  CALL gather2D_mpi(xchamp,xchamp_g)
2854  IF (is_root_prc) THEN
2855     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2856  ENDIF
2857!-
2858  DO ij=1,nbindex
2859    xchamp(kindex(ij)) = tminm1(ij)
2860  ENDDO
2861  var_name= 'tminm1'
2862  CALL gather2D_mpi(xchamp,xchamp_g)
2863  IF (is_root_prc) THEN
2864     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2865  ENDIF
2866!-
2867  DO ij=1,nbindex
2868    xchamp(kindex(ij)) = qdm1(ij)
2869  ENDDO
2870  var_name= 'qdm1'
2871  CALL gather2D_mpi(xchamp,xchamp_g)
2872  IF (is_root_prc) THEN
2873     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2874  ENDIF
2875!-
2876  DO ij=1,nbindex
2877    xchamp(kindex(ij)) = udm1(ij)
2878  ENDDO
2879  var_name= 'udm1'
2880  CALL gather2D_mpi(xchamp,xchamp_g)
2881  IF (is_root_prc) THEN
2882     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2883  ENDIF
2884!-
2885  DO ij=1,nbindex
2886    xchamp(kindex(ij)) = precipm1(ij)
2887  ENDDO
2888  var_name= 'precipm1'
2889  CALL gather2D_mpi(xchamp,xchamp_g)
2890  IF (is_root_prc) THEN
2891     CALL restput (rest_id, var_name, iim_g, jjm_g, 1, itau, xchamp_g)
2892  ENDIF
2893!--------------------------------
2894END SUBROUTINE weathgen_restwrite
2895!-
2896!===
2897!-
2898!! ================================================================================================================================
2899!! SUBROUTINE   : weathgen_data
2900!!
2901!>\BRIEF         This subroutine reads data from an netcdf file.
2902!!
2903!! DESCRIPTION  : None
2904!!
2905!! RECENT CHANGE(S): None
2906!!
2907!! MAIN OUTPUT VARIABLE(S): ::champout
2908!!
2909!! REFERENCE(S) :
2910!!
2911!! FLOWCHART    : None
2912!! \n
2913!_ ================================================================================================================================
2914
2915SUBROUTINE weather_read &
2916& (force_id,nomvar,iim_file,jjm_file,n3,i_cut, &
2917&  iim,jjm,n_agg,ncorr,icorr,jcorr,champout)
2918!---------------------------------------------------------------------
2919  IMPLICIT NONE
2920!-
2921
2922  !! 0. Variables and parameters declaration
2923 
2924  !! 0.1 Input variables
2925
2926  INTEGER,INTENT(IN)                          :: force_id
2927  CHARACTER(LEN=*),INTENT(IN)                 :: nomvar
2928  INTEGER,INTENT(IN)                          :: iim_file,jjm_file
2929  INTEGER,INTENT(IN)                          :: n3
2930  INTEGER,INTENT(IN)                          :: i_cut
2931  INTEGER,INTENT(IN)                          :: iim,jjm
2932  INTEGER,INTENT(IN)                          :: n_agg
2933  INTEGER,DIMENSION(:,:),INTENT(IN)           :: ncorr
2934  INTEGER,DIMENSION(:,:,:),INTENT(IN)         :: icorr,jcorr
2935
2936  !! 0.2 Output variables
2937
2938  REAL,DIMENSION(iim*jjm,n3),INTENT(OUT)      :: champout
2939
2940  !! 0.4 Local variables
2941
2942  REAL,DIMENSION(iim_file,jjm_file,n3)        :: champ_file
2943  REAL,ALLOCATABLE,DIMENSION(:,:)             :: champout_g
2944  INTEGER                                     :: i,j,ij,l,m
2945
2946!_ ================================================================================================================================
2947
2948  WRITE(numout,*) 'Lecture ',TRIM(nomvar)
2949!-
2950  IF (is_root_prc) THEN
2951     ALLOCATE(champout_g(iim_g*jjm_g,n3))
2952     IF ( n3 == 1 ) THEN
2953        CALL flinget (force_id,nomvar(1:LEN_TRIM(nomvar)), &
2954             &                iim_file, jjm_file, 0, 0,  1, 1, champ_file)
2955     ELSE
2956        DO l=1,n3
2957           CALL flinget &
2958                &      (force_id,nomvar(1:LEN_TRIM(nomvar)), &
2959                &       iim_file, jjm_file, 0, n3,  l, l, champ_file(:,:,l))
2960        ENDDO
2961     ENDIF
2962     ! shift if necessary
2963     IF (i_cut /= 0) THEN
2964        DO l=1,n3
2965           CALL shift_field (iim_file,jjm_file,i_cut,champ_file(:,:,l))
2966        ENDDO
2967     ENDIF
2968     ! interpolate onto the model grid
2969     DO l=1,n3
2970        DO j=1,jjm_g
2971           DO i=1,iim_g
2972              ij = i+(j-1)*iim_g
2973              champout_g(ij,l) = zero
2974              DO m=1,ncorr(i,j)
2975                 champout_g(ij,l) = champout_g(ij,l) &
2976        &                        +champ_file(icorr(i,j,m),jcorr(i,j,m),l)
2977              ENDDO
2978              champout_g(ij,l) = champout_g(ij,l)/REAL(ncorr(i,j))
2979           ENDDO
2980        ENDDO
2981     ENDDO
2982!$     DO l=1,n3
2983!$        DO j=1,jjm_g
2984!$           WRITE(numout,*) j,(/ ( champout_g((j-1)*iim_g+i,l), i=1,iim_g ) /)
2985!$        ENDDO
2986!$     ENDDO
2987  ELSE
2988     ALLOCATE(champout_g(1,1))
2989  ENDIF
2990!!$  CALL scatter2D(champout_g,champout)
2991#ifndef CPP_PARA
2992  champout(:,:)=champout_g(:,:)
2993#else
2994  CALL orch_scatter2D_mpi_rgen(champout_g,champout,SIZE(champout_g,1),SIZE(champout_g, 2))
2995#endif
2996
2997!$  DO l=1,n3
2998!$     DO j=1,jjm
2999!$        WRITE(numout,*) j,(/ ( champout((j-1)*iim_g+i,l), i=1,iim_g ) /)
3000!$     ENDDO
3001!$  ENDDO
3002  !----------------------------
3003END SUBROUTINE weather_read
3004!-
3005!===
3006!-
3007!! ================================================================================================================================
3008!! SUBROUTINE   : weathgen_dump
3009!!
3010!>\BRIEF        This subroutine "dumps" data before writing an netcdf file.
3011!!
3012!! DESCRIPTION  : None
3013!!
3014!! RECENT CHANGE(S): None
3015!!
3016!! MAIN OUTPUT VARIABLE(S):
3017!!
3018!! REFERENCE(S) :
3019!!
3020!! FLOWCHART    : None
3021!! \n
3022!_ ================================================================================================================================
3023
3024SUBROUTINE weathgen_dump &
3025& (itau, dt_force, iim, jjm, nbindex, kindex, lrstwrite, &
3026&  swdown, rainf, snowf, tair, u, v, qair, pb, lwdown )
3027!---------------------------------------------------------------------
3028  IMPLICIT NONE
3029!-
3030
3031  !! 0. Variables and parameters declaration
3032
3033  !! 0.1 Input variables
3034
3035  INTEGER,INTENT(IN)                     :: itau
3036  REAL,INTENT(IN)                        :: dt_force
3037  INTEGER,INTENT(IN)                     :: iim,jjm
3038  INTEGER,INTENT(IN)                     :: nbindex
3039  LOGICAL,INTENT(IN)                     :: lrstwrite
3040  INTEGER,DIMENSION(iim*jjm),INTENT(IN)  :: kindex
3041  REAL,DIMENSION(iim*jjm),INTENT(IN)     :: &
3042 &  swdown, rainf, snowf, tair, u, v, qair, pb, lwdown
3043
3044  !! 0.4 Local variables
3045
3046  INTEGER                 :: iret,ndim
3047  INTEGER,DIMENSION(4)    :: corner,edges
3048  REAL,DIMENSION(iim*jjm) :: var_gather
3049
3050!_ ================================================================================================================================
3051
3052!-
3053! time dimension
3054!-
3055  iret = NF90_PUT_VAR (dump_id,timestp_id,(/ REAL(itau) /), &
3056 &                     start=(/ itau /),count=(/ 1 /))
3057  iret = NF90_PUT_VAR (dump_id,time_id,(/ REAL(itau)*dt_force /), &
3058 &                     start=(/ itau /),count=(/ 1 /))
3059!-
3060! 2D variables: pas de dimension verticale
3061!-
3062  IF (gathered) THEN
3063    ndim = 2
3064    corner(1:2) = (/ 1, itau /)
3065    edges(1:2) = (/ nbindex, 1 /)
3066  ELSE
3067    ndim = 3
3068    corner(1:3) = (/ 1, 1, itau /)
3069    edges(1:3) = (/ iim, jjm, 1 /)
3070  ENDIF
3071!-
3072  CALL gather_weather (iim*jjm,nbindex,kindex,swdown, var_gather)
3073  iret = NF90_PUT_VAR (dump_id,soldownid, var_gather, &
3074 &         start=corner(1:ndim), count=edges(1:ndim))
3075  CALL gather_weather (iim*jjm,nbindex,kindex,rainf,  var_gather)
3076  iret = NF90_PUT_VAR (dump_id,rainfid,   var_gather, &
3077 &         start=corner(1:ndim), count=edges(1:ndim))
3078  CALL gather_weather (iim*jjm,nbindex,kindex,snowf,  var_gather)
3079  iret = NF90_PUT_VAR (dump_id,snowfid,   var_gather, &
3080 &         start=corner(1:ndim), count=edges(1:ndim))
3081  CALL gather_weather (iim*jjm,nbindex,kindex,pb,     var_gather)
3082  iret = NF90_PUT_VAR (dump_id,psolid,    var_gather, &
3083 &         start=corner(1:ndim), count=edges(1:ndim))
3084  CALL gather_weather (iim*jjm,nbindex,kindex,lwdown, var_gather)
3085  iret = NF90_PUT_VAR (dump_id,lwradid,   var_gather, &
3086 &         start=corner(1:ndim), count=edges(1:ndim))
3087!-
3088! 3D variables
3089!-
3090  IF (gathered) THEN
3091    ndim = 3
3092    corner(1:3) = (/ 1, 1, itau /)
3093    edges(1:3) = (/ nbindex, 1, 1 /)
3094  ELSE
3095    ndim = 4
3096    corner(1:4) = (/ 1, 1, 1, itau /)
3097    edges(1:4) = (/ iim, jjm, 1, 1 /)
3098  ENDIF
3099!-
3100  CALL gather_weather (iim*jjm,nbindex,kindex,u,    var_gather)
3101  iret = NF90_PUT_VAR (dump_id,uid,    var_gather, &
3102 &         start=corner(1:ndim), count=edges(1:ndim))
3103  CALL gather_weather (iim*jjm,nbindex,kindex,v,    var_gather)
3104  iret = NF90_PUT_VAR (dump_id,vid,    var_gather, &
3105 &         start=corner(1:ndim), count=edges(1:ndim))
3106  CALL gather_weather (iim*jjm,nbindex,kindex,tair, var_gather)
3107  iret = NF90_PUT_VAR (dump_id,tairid, var_gather, &
3108 &         start=corner(1:ndim), count=edges(1:ndim))
3109  CALL gather_weather (iim*jjm,nbindex,kindex,qair, var_gather)
3110  iret = NF90_PUT_VAR (dump_id,qairid, var_gather, &
3111 &         start=corner(1:ndim), count=edges(1:ndim))
3112!-
3113  IF (lrstwrite) THEN
3114    iret = NF90_CLOSE (dump_id)
3115  ENDIF
3116!---------------------------
3117END SUBROUTINE weathgen_dump
3118!-
3119!===
3120!-
3121
3122!! ================================================================================================================================
3123!! SUBROUTINE   : gather_weather
3124!!
3125!>\BRIEF        This subroutine determines which points are not in the computational domain and
3126!! creates a mask for these points.
3127!!
3128!! DESCRIPTION  : None
3129!!
3130!! RECENT CHANGE(S): None
3131!!
3132!! MAIN OUTPUT VARIABLE(S): ::var_out
3133!!
3134!! REFERENCE(S) :
3135!!
3136!! FLOWCHART    : None
3137!! \n
3138!_ ================================================================================================================================
3139
3140SUBROUTINE gather_weather (iimjjm, nbindex, kindex, var_in, var_out)
3141!---------------------------------------------------------------------
3142  IMPLICIT NONE
3143!-
3144
3145  !! 0. Variables and parameters declaration
3146
3147  !! 0.1 Input variables
3148
3149  INTEGER,INTENT(IN)                     :: iimjjm,nbindex
3150  INTEGER,DIMENSION(iimjjm),INTENT(IN)   :: kindex
3151  REAL,DIMENSION(iimjjm),INTENT(IN)      :: var_in
3152
3153  !! 0.2 Output variables 
3154
3155  REAL,DIMENSION(iimjjm),INTENT(OUT)     :: var_out
3156
3157  !! 0.4 Local variables
3158
3159  INTEGER                                :: i
3160  LOGICAL,SAVE                           :: lstep_init_gather = .TRUE.
3161  INTEGER,SAVE                           :: nb_outside
3162  INTEGER,ALLOCATABLE,SAVE,DIMENSION(:)  :: outside
3163
3164!_ ================================================================================================================================
3165
3166  IF (lstep_init_gather) THEN
3167!---
3168!-- determine which points are not in the computational domain and
3169!-- create a mask for these points
3170!---
3171    lstep_init_gather = .FALSE.
3172 
3173    ALLOC_ERR=-1
3174    ALLOCATE(outside(iimjjm), STAT=ALLOC_ERR)
3175    IF (ALLOC_ERR/=0) THEN
3176      WRITE(numout,*) "ERROR IN ALLOCATION of outside : ",ALLOC_ERR
3177      STOP
3178    ENDIF
3179    outside(:) = zero
3180    nb_outside = 0
3181    DO i=1,iimjjm
3182      IF ( ALL( kindex(:) /= i ) ) THEN
3183        nb_outside = nb_outside+1
3184        outside(nb_outside) = i
3185      ENDIF
3186    ENDDO
3187  ENDIF
3188!-
3189  IF ( gathered ) THEN
3190    DO i=1,nbindex
3191      var_out(i) = var_in(kindex(i))
3192    ENDDO
3193  ELSE
3194    var_out(:) = var_in(:)
3195    DO i=1,nb_outside
3196      var_out(outside(i)) = undef_sechiba
3197    ENDDO
3198  ENDIF
3199!--------------------
3200END SUBROUTINE gather_weather
3201!-
3202!===
3203!-
3204
3205!! ================================================================================================================================
3206!! SUBROUTINE   : shift_shield
3207!!
3208!>\BRIEF       
3209!!
3210!! DESCRIPTION  : None
3211!!
3212!! RECENT CHANGE(S): None
3213!!
3214!! MAIN OUTPUT VARIABLE(S): ::champ
3215!!
3216!! REFERENCE(S) :
3217!!
3218!! FLOWCHART    : None
3219!! \n
3220!_ ================================================================================================================================
3221
3222SUBROUTINE shift_field (im,jm,i_cut,champ)
3223!---------------------------------------------------------------------
3224
3225  !! 0. Variables and parameters declaration
3226
3227  !! 0.1 Input variables
3228
3229  INTEGER,INTENT(IN)                  :: im,jm,i_cut
3230
3231  !! 0.3 Modified variables
3232
3233  REAL,DIMENSION(im,jm),INTENT(INOUT) :: champ
3234
3235  !! 0.4 Local variables
3236
3237  REAL,DIMENSION(im,jm)               :: champ_temp
3238
3239!_ ================================================================================================================================
3240
3241  IF ( (i_cut >= 1).AND.(i_cut <= im) ) THEN
3242    champ_temp(1:im-i_cut-1,:) = champ(i_cut:im,:)
3243    champ_temp(im-i_cut:im,:)  = champ(1:i_cut+1,:)
3244    champ(:,:) = champ_temp(:,:)
3245  ENDIF
3246!-------------------------
3247END SUBROUTINE shift_field
3248!-
3249!===
3250!-
3251!! ================================================================================================================================
3252!! SUBROUTINE   : weathgen_domain_size
3253!!
3254!>\BRIEF        This subroutine determines the size of the domain.
3255!!
3256!! DESCRIPTION  : None
3257!!
3258!! RECENT CHANGE(S): None
3259!!
3260!! MAIN OUTPUT VARIABLE(S): ::iim, ::jjm, ::limit_west, ::limit_east, ::limit_north, ::limit_south
3261!!
3262!! REFERENCE(S) :
3263!!
3264!! FLOWCHART    : None
3265!! \n
3266!_ ================================================================================================================================
3267
3268SUBROUTINE weathgen_domain_size &
3269& (limit_west,limit_east,limit_north,limit_south, &
3270&  zonal_res,merid_res,iim,jjm)
3271!---------------------------------------------------------------------
3272  IMPLICIT NONE
3273!-
3274  !! 0. Variables and parameters declaration
3275
3276  !! 0.1 Input variables
3277
3278  REAL,INTENT(IN)     :: zonal_res,merid_res
3279
3280  !! 0.2 Output variables
3281
3282  INTEGER,INTENT(OUT) :: iim,jjm
3283
3284  !! 0.3 Modified variables
3285
3286  REAL,INTENT(INOUT)  :: limit_west,limit_east,limit_north,limit_south
3287
3288!_ ================================================================================================================================
3289
3290  IF (limit_west > limit_east)  limit_east = limit_east+360.
3291!-
3292  IF (    (limit_west >= limit_east) &
3293 &    .OR.(limit_east > 360.) &
3294 &    .OR.(limit_west < -180.) &
3295 &    .OR.(limit_east-limit_west > 360.) ) THEN
3296    WRITE(numout,*) 'PROBLEME longitudes.'
3297    WRITE(numout,*) 'Limites Ouest, Est: ',limit_west,limit_east
3298    STOP
3299  ENDIF
3300!-
3301  IF (    (limit_south < -90.) &
3302 &    .OR.(limit_north > 90.) &
3303 &    .OR.(limit_south >= limit_north ) ) THEN
3304    WRITE(numout,*) 'PROBLEME latitudes.'
3305    WRITE(numout,*) 'Limites Nord, Sud: ',limit_north,limit_south
3306    STOP
3307  ENDIF
3308!-
3309  IF (    (zonal_res <= 0. ) &
3310 &    .OR.(zonal_res > limit_east-limit_west) ) THEN
3311    WRITE(numout,*) 'PROBLEME resolution zonale.'
3312    WRITE(numout,*) 'Limites Ouest, Est, Resolution: ', &
3313 &             limit_west,limit_east,zonal_res
3314    STOP
3315  ENDIF
3316!-
3317  IF (    (merid_res <= 0.) &
3318 &    .OR.(merid_res > limit_north-limit_south) ) THEN
3319    WRITE(numout,*) 'PROBLEME resolution meridionale.'
3320    WRITE(numout,*) 'Limites Nord, Sud, Resolution: ', &
3321 &             limit_north,limit_south,merid_res
3322    STOP
3323  ENDIF
3324!-
3325  iim = NINT(MAX((limit_east-limit_west)/zonal_res,1.))
3326  jjm = NINT(MAX((limit_north-limit_south)/merid_res,1.))
3327!-
3328  WRITE(numout,*) 'Domain size: iim, jjm = ', iim, jjm
3329!----------------------------------
3330END SUBROUTINE weathgen_domain_size
3331!-
3332!===
3333!-
3334
3335!! ================================================================================================================================
3336!! FUNCTION     : tsat1
3337!!
3338!>\BRIEF         This function computes the saturated temperature for vapor.
3339!!
3340!! DESCRIPTION :  functions tsatl,tsati are used below so that Lowe's
3341!!                polyomial for liquid is used if t gt 273.16, or for ice if
3342!!                t lt 273.16. also impose range of validity for Lowe's polys.\n
3343!!
3344!! RECENT CHANGE(S): None
3345!!
3346!! RETURN VALUE : tsat
3347!!
3348!! REFERENCE(S) :
3349!! - Lowe PR, 1977, An Approximating Polynomial for the Computation of Saturation
3350!! Vapor Pressure, Journal of Applied Meteorology.16,101-103.
3351!!
3352!! FLOWCHART    : None
3353!! \n
3354!_ ================================================================================================================================
3355
3356FUNCTION tsatl (t) RESULT (tsat)
3357
3358  !! 0. Variables and parameters declaration
3359 
3360  !! 0.1 Input variables
3361
3362  REAL,INTENT(IN) :: t
3363
3364  !! 0.2 Result
3365  REAL            :: tsat
3366
3367!_ ================================================================================================================================
3368
3369  tsat = MIN(100.,MAX(t-zero_t,zero))
3370!-----------------
3371END FUNCTION tsatl
3372!-
3373!===
3374!-
3375!! ================================================================================================================================
3376!! FUNCTION     : tsati
3377!!
3378!>\BRIEF         This function computes the saturated temperature for ice.
3379!!
3380!! DESCRIPTION :  functions tsatl,tsati are used below so that Lowe's
3381!!                polyomial for liquid is used if t gt 273.16, or for ice if
3382!!                t lt 273.16. also impose range of validity for Lowe's polys.\n
3383!!
3384!! RECENT CHANGE(S): None
3385!!
3386!! RETURN VALUE : tsat
3387!!
3388!! REFERENCE(S) :
3389!! - Lowe PR, 1977, An Approximating Polynomial for the Computation of Saturation
3390!! Vapor Pressure, Journal of Applied Meteorology.16,101-103.
3391!!
3392!! FLOWCHART    : None
3393!! \n
3394!_ ================================================================================================================================
3395
3396FUNCTION tsati (t) RESULT (tsat)
3397
3398  !! 0. Variables and parameters declaration
3399 
3400  !! 0.1 Input variables
3401
3402  REAL,INTENT(IN) :: t
3403
3404  !! 0.2 Result
3405  REAL            :: tsat
3406
3407!_ ================================================================================================================================
3408
3409  tsat = MAX(-60.,MIN(t-zero_t,zero))
3410
3411!-----------------
3412END FUNCTION tsati
3413!-
3414!===
3415!-
3416
3417!! ================================================================================================================================
3418!! FUNCTION     : esat
3419!!
3420!>\BRIEF         This function computes specific humidity with the polynomials of Lowe.
3421!!
3422!! DESCRIPTION : The function esat is svp in n/m**2, with t in deg k.
3423!!               (100 * lowe's poly since 1 mb = 100 n/m**2.). \n
3424!!               Polynomials for svp(t), d(svp)/dt over water and ice
3425!!
3426!! RECENT CHANGE(S): None
3427!!
3428!! RETURN VALUE : esatout
3429!!
3430!! REFERENCE(S) :
3431!! - Lowe PR, 1977, An Approximating Polynomial for the Computation of Saturation
3432!! Vapor Pressure, Journal of Applied Meteorology.16,101-103.
3433!!
3434!! FLOWCHART    : None
3435!! \n
3436!_ ================================================================================================================================
3437
3438FUNCTION esat (t) RESULT (esatout)
3439
3440  !! 0. Variables and parameters declaration
3441
3442  REAL,PARAMETER :: &                                                    !! polynomials for svp(t), d(svp)/dt over water and ice are from
3443 & asat0 = 6.1078000,    asat1 = 4.4365185e-1, asat2 = 1.4289458e-2, &   !! lowe(1977),jam,16,101-103.
3444 & asat3 = 2.6506485e-4, asat4 = 3.0312404e-6, asat5 = 2.0340809e-8, &
3445 & asat6 = 6.1368209e-11, &
3446 & bsat0 = 6.1091780,    bsat1 = 5.0346990e-1, bsat2 = 1.8860134e-2, &
3447 & bsat3 = 4.1762237e-4, bsat4 = 5.8247203e-6, bsat5 = 4.8388032e-8, &
3448 & bsat6 = 1.8388269e-10
3449
3450  !! 0.1 Input variables
3451
3452  REAL,INTENT(IN) :: t
3453
3454  !! 0.2 Result
3455
3456  REAL             :: esatout
3457
3458  !! 0.4 Local variables
3459
3460  REAL             :: x
3461
3462!_ ================================================================================================================================
3463
3464  IF (t >= zero_t) THEN
3465    x = asat0
3466  ELSE
3467    x = bsat0
3468  ENDIF
3469!-
3470  esatout = 100.* &
3471    ( x &
3472     +tsatl(t)*(asat1+tsatl(t)*(asat2+tsatl(t)*(asat3 &
3473     +tsatl(t)*(asat4+tsatl(t)*(asat5+tsatl(t)* asat6))))) &
3474     +tsati(t)*(bsat1+tsati(t)*(bsat2+tsati(t)*(bsat3 &
3475     +tsati(t)*(bsat4+tsati(t)*(bsat5+tsati(t)* bsat6)))))  )
3476!----------------
3477END FUNCTION esat
3478!-
3479!===
3480!-
3481! ================================================================================================================================
3482!! FUNCTION     : qsat
3483!!
3484!>\BRIEF         This function computes the saturation specific humidity.
3485!!
3486!! DESCRIPTION :  statement function qsat is saturation specific humidity,
3487!! with svp e and ambient pressure p in n/m**2. impose an upper
3488!! limit of 1 to avoid spurious values for very high svp
3489!! and/or small p
3490!!
3491!! RECENT CHANGE(S): None
3492!!
3493!! RETURN VALUE : qsatout
3494!!
3495!! REFERENCE(S) :
3496!! - Lowe PR, 1977, An Approximating Polynomial for the Computation of Saturation
3497!! Vapor Pressure, Journal of Applied Meteorology.16,101-103.
3498!!
3499!! FLOWCHART    : None
3500!! \n
3501!_ ================================================================================================================================
3502
3503FUNCTION qsat (e,p) RESULT (qsatout)
3504
3505  !! 0. Variables and parameters declaration
3506
3507  !! 0.1 Input variables
3508
3509  REAL, INTENT(IN) :: e,p
3510
3511  !! 0.2 Result
3512  REAL             :: qsatout
3513
3514!_ ================================================================================================================================
3515
3516  qsatout = 0.622*e/MAX(p-(1.0-0.622)*e,0.622*e)
3517!----------------
3518END FUNCTION qsat
3519!-
3520!===
3521!-
3522
3523!! ================================================================================================================================
3524!! SUBROUTINE   : weathgen_qsat
3525!!
3526!>\BRIEF        This subroutine calculates the saturation vapor pressure with the polynomials of Lowe.
3527!!
3528!! DESCRIPTION  : Vectorized version of functions esat and qsat.
3529!!                statement function esat is svp in n/m**2, with t in deg K.\n
3530!!               (100 * lowe's poly since 1 mb = 100 n/m**2.)\n
3531!!               Polynomials for svp(t), d(svp)/dt over water
3532!!               and ice are from Lowe(1977),jam,16,101-103 \n
3533!!
3534!! RECENT CHANGE(S): None
3535!!
3536!! MAIN OUTPUT VARIABLE(S): ::qsat
3537!!
3538!! REFERENCE(S) :
3539!! - Lowe PR, 1977, An Approximating Polynomial for the Computation of Saturation
3540!! Vapor Pressure, Journal of Applied Meteorology.16,101-103.
3541!!
3542!! FLOWCHART    : None
3543!! \n
3544!_ ================================================================================================================================
3545
3546SUBROUTINE weathgen_qsat (npoi,t,p,qsat)
3547
3548
3549  !! 0. Variables and parameters declaration
3550
3551 !-
3552 ! polynomials for svp(t), d(svp)/dt over water and ice
3553 ! are from lowe(1977),ja
3554  REAL,PARAMETER :: &
3555 & asat0 = 6.1078000,    asat1 = 4.4365185e-1, asat2 = 1.4289458e-2, &   !! polynomials for svp(t), d(svp)/dt over water and ice
3556 & asat3 = 2.6506485e-4, asat4 = 3.0312404e-6, asat5 = 2.0340809e-8, &
3557 & asat6 = 6.1368209e-11, &
3558 & bsat0 = 6.1091780,    bsat1 = 5.0346990e-1, bsat2 = 1.8860134e-2, &
3559 & bsat3 = 4.1762237e-4, bsat4 = 5.8247203e-6, bsat5 = 4.8388032e-8, &
3560 & bsat6 = 1.8388269e-10
3561
3562  !! 0.1 Input variables
3563
3564  INTEGER,INTENT(IN)              :: npoi
3565  REAL,DIMENSION(npoi),INTENT(IN) :: t,p
3566
3567  !! 0.2 Output variables
3568
3569  REAL,DIMENSION(npoi),INTENT(OUT):: qsat
3570
3571  !! 0.4 Local variables
3572
3573  REAL,DIMENSION(npoi) :: x, tl, ti, e
3574
3575!_ ================================================================================================================================
3576
3577  WHERE (t(:) > zero_t)
3578    x(:) = asat0
3579  ELSEWHERE
3580    x(:) = bsat0
3581  ENDWHERE
3582!-
3583  tl(:) = MIN(100.,MAX(t(:)-zero_t,zero))
3584  ti(:) = MAX(-60.,MIN(t(:)-zero_t,zero))
3585!-
3586  e(:) =  100.* &
3587    ( x(:) &
3588     +tl(:)*(asat1+tl(:)*(asat2+tl(:)*(asat3 &
3589     +tl(:)*(asat4+tl(:)*(asat5+tl(:)* asat6))))) &
3590     +ti(:)*(bsat1+ti(:)*(bsat2+ti(:)*(bsat3 &
3591     +ti(:)*(bsat4+ti(:)*(bsat5+ti(:)* bsat6)))))  )
3592!-
3593  qsat(:) = 0.622*e(:)/MAX(p(:)-(1.0-0.622)*e(:),0.622*e(:))
3594!---------------------------
3595END SUBROUTINE weathgen_qsat
3596!-
3597!===
3598!-
3599
3600!! ================================================================================================================================
3601!! SUBROUTINE   : weathgen_qsat_2d
3602!!
3603!>\BRIEF        This subroutine calculates the saturation vapor pressure with the polynomials of Lowe.
3604!!
3605!! DESCRIPTION  : Vectorized version of functions esat and qsat.
3606!!                statement function esat is svp in n/m**2, with t in deg K.\n
3607!!               (100 * lowe's poly since 1 mb = 100 n/m**2.)\n
3608!!               Polynomials for svp(t), d(svp)/dt over water
3609!!               and ice are from Lowe(1977),jam,16,101-103 \n
3610!!
3611!! RECENT CHANGE(S): None
3612!!
3613!! MAIN OUTPUT VARIABLE(S): ::qsat
3614!!
3615!! REFERENCE(S) :
3616!! - Lowe PR, 1977, An Approximating Polynomial for the Computation of Saturation
3617!! Vapor Pressure, Journal of Applied Meteorology.16,101-103.
3618!!
3619!! FLOWCHART    : None
3620!! \n
3621!_ ================================================================================================================================
3622
3623SUBROUTINE weathgen_qsat_2d (iim,jjm,t,p,qsat)
3624
3625  !! 0. Parameters and variable declaration
3626
3627  !! 0.1 Input variables
3628
3629  INTEGER, INTENT(IN) :: iim
3630  INTEGER, INTENT(IN) :: jjm
3631  REAL,DIMENSION(iim,jjm),INTENT(IN)  :: t,p
3632
3633   !! 0.2 Output variables
3634   REAL,DIMENSION(iim,jjm),INTENT(OUT) :: qsat
3635
3636   !! 0.4 Local variables
3637
3638   REAL,DIMENSION(iim,jjm) :: x, tl, ti, e
3639
3640  REAL,PARAMETER :: &
3641 & asat0 = 6.1078000,    asat1 = 4.4365185e-1, asat2 = 1.4289458e-2, &
3642 & asat3 = 2.6506485e-4, asat4 = 3.0312404e-6, asat5 = 2.0340809e-8, &
3643 & asat6 = 6.1368209e-11, &
3644 & bsat0 = 6.1091780,    bsat1 = 5.0346990e-1, bsat2 = 1.8860134e-2, &
3645 & bsat3 = 4.1762237e-4, bsat4 = 5.8247203e-6, bsat5 = 4.8388032e-8, &
3646 & bsat6 = 1.8388269e-10
3647
3648!_ ================================================================================================================================
3649
3650  WHERE (t(:,:) > zero_t)
3651    x(:,:) = asat0
3652  ELSEWHERE
3653    x(:,:) = bsat0
3654  ENDWHERE
3655!-
3656  tl(:,:) = MIN(100.,MAX(t(:,:)-zero_t,0.))
3657  ti(:,:) = MAX(-60.,MIN(t(:,:)-zero_t,0.))
3658!-
3659  e(:,:) =  100.* &
3660    ( x(:,:) &
3661     +tl(:,:)*(asat1+tl(:,:)*(asat2+tl(:,:)*(asat3 &
3662     +tl(:,:)*(asat4+tl(:,:)*(asat5+tl(:,:)* asat6))))) &
3663     +ti(:,:)*(bsat1+ti(:,:)*(bsat2+ti(:,:)*(bsat3 &
3664     +ti(:,:)*(bsat4+ti(:,:)*(bsat5+ti(:,:)* bsat6)))))  )
3665!-
3666  qsat(:,:) = 0.622*e(:,:)/MAX(p(:,:)-(1.0-0.622)*e(:,:),0.622*e(:,:))
3667!---------------------------
3668END SUBROUTINE weathgen_qsat_2d
3669
3670
3671!! ================================================================================================================================
3672!! SUBROUTINE   : mask_c_o
3673!!
3674!>\BRIEF        This subroutine computes a field which indicated if the point is terrestrial or oceanic.
3675!!
3676!! DESCRIPTION  : From a mask field, we make an indicator mask Earth/ocean. Earth : 1 ; ocean : 0.
3677!!
3678!! RECENT CHANGE(S): z.x.li,01/04/1994 : creation of the subroutine
3679!!
3680!! MAIN OUTPUT VARIABLE(S): ::mask, ::ncorr, ::icorr
3681!!
3682!! REFERENCE(S) :
3683!!
3684!! FLOWCHART    : None
3685!! \n
3686!_ ================================================================================================================================
3687
3688SUBROUTINE mask_c_o &
3689& (imdep, jmdep, xdata, ydata, mask_in, fcrit, &
3690&  imar, jmar, zonal_res, merid_res, n_agg, x, y, mask, &
3691&  ncorr, icorr, jcorr)
3692
3693  !! 0. Variables and parameters declaration
3694
3695  !! 0.1 Input variables
3696
3697  INTEGER :: imdep,jmdep
3698  REAL :: xdata(imdep),ydata(jmdep)
3699  REAL :: mask_in(imdep,jmdep)
3700  REAL :: fcrit
3701  INTEGER :: imar,jmar
3702  REAL :: zonal_res,merid_res
3703  INTEGER :: n_agg
3704  REAL :: x(imar),y(jmar)
3705
3706  !! 0.2 Output variables
3707
3708  REAL, INTENT(OUT) :: mask(imar,jmar)
3709  INTEGER :: ncorr(imar,jmar)
3710  INTEGER,DIMENSION(imar,jmar,n_agg) :: icorr,jcorr
3711
3712  !! 0.4 Local variables
3713
3714  INTEGER i, j, ii, jj
3715  REAL a(imar),b(imar),c(jmar),d(jmar)
3716  INTEGER num_tot(imar,jmar), num_oce(imar,jmar)
3717  REAL,ALLOCATABLE :: distans(:)
3718  INTEGER ij_proche(1),i_proche,j_proche
3719!-
3720  INTEGER,DIMENSION(imar,jmar) :: ncorr_oce , ncorr_land
3721  INTEGER,DIMENSION(imar,jmar,n_agg) :: &
3722 &  icorr_oce, jcorr_oce , icorr_land, jcorr_land
3723!-
3724  INTEGER imdepp
3725  REAL,ALLOCATABLE :: xdatap(:)
3726  REAL,ALLOCATABLE :: mask_inp(:,:)
3727  LOGICAL :: extend
3728
3729!_ ================================================================================================================================
3730
3731  ncorr(:,:) = 0
3732  icorr(:,:,:) = -1; jcorr(:,:,:) = -1
3733  ncorr_land(:,:) = 0
3734  icorr_land(:,:,:) = -1; jcorr_land(:,:,:) = -1
3735  ncorr_oce(:,:) = 0
3736  icorr_oce(:,:,:) = -1; jcorr_oce(:,:,:) = -1
3737! do we have to extend the domain (-x...-x+360)?
3738  IF ( xdata(1)+360.-xdata(imdep) > 0.01 ) THEN
3739    extend = .TRUE.
3740    imdepp = imdep+1
3741  ELSE
3742    extend = .FALSE.
3743    imdepp = imdep
3744  ENDIF
3745!-
3746
3747  ALLOC_ERR=-1
3748  ALLOCATE(xdatap(imdepp), STAT=ALLOC_ERR)
3749  IF (ALLOC_ERR/=0) THEN
3750    WRITE(numout,*) "ERROR IN ALLOCATION of xdatap : ",ALLOC_ERR
3751    STOP
3752  ENDIF
3753
3754  ALLOC_ERR=-1
3755  ALLOCATE(mask_inp(imdepp,jmdep), STAT=ALLOC_ERR)
3756  IF (ALLOC_ERR/=0) THEN
3757    WRITE(numout,*) "ERROR IN ALLOCATION of mask_inp : ",ALLOC_ERR
3758    STOP
3759  ENDIF
3760!-
3761  xdatap(1:imdep) = xdata(1:imdep)
3762  mask_inp(1:imdep,:) = mask_in(1:imdep,:)
3763!-
3764  IF (extend) THEN
3765    xdatap(imdepp) = xdatap(1)+360.
3766    mask_inp(imdepp,:) = mask_inp(1,:)
3767  ENDIF
3768!-
3769
3770  ALLOC_ERR=-1
3771  ALLOCATE(distans(imdepp*jmdep), STAT=ALLOC_ERR)
3772  IF (ALLOC_ERR/=0) THEN
3773    WRITE(numout,*) "ERROR IN ALLOCATION of distans : ",ALLOC_ERR
3774    STOP
3775  ENDIF
3776! Definition des limites des boites de la grille d'arrivee.
3777  IF (imar > 1) THEN
3778    a(1) = x(1)-(x(2)-x(1))/2.0
3779    b(1) = (x(1)+x(2))/2.0
3780    DO i=2,imar-1
3781      a(i) = b(i-1)
3782      b(i) = (x(i)+x(i+1))/2.0
3783    ENDDO
3784    a(imar) = b(imar-1)
3785    b(imar) = x(imar)+(x(imar)-x(imar-1))/2.0
3786  ELSE
3787    a(1) = x(1)-zonal_res/2.
3788    b(1) = x(1)+zonal_res/2.
3789  ENDIF
3790!-
3791  IF (jmar > 1) THEN
3792    c(1) = y(1)-(y(2)-y(1))/2.0
3793    d(1) = (y(1)+y(2))/2.0
3794    DO j=2,jmar-1
3795      c(j) = d(j-1)
3796      d(j) = (y(j)+y(j+1))/2.0
3797    ENDDO
3798    c(jmar) = d(jmar-1)
3799    d(jmar) = y(jmar)+(y(jmar)-y(jmar-1))/2.0
3800  ELSE
3801    c(1) = y(1)-merid_res/2.
3802    d(1) = y(1)+merid_res/2.
3803  ENDIF
3804!-
3805  num_oce(1:imar,1:jmar) = 0
3806  num_tot(1:imar,1:jmar) = 0
3807!-
3808!  .....  Modif  P. Le Van ( 23/08/95 )  ....
3809!-
3810  DO ii=1,imar
3811    DO jj=1,jmar
3812      DO i=1,imdepp
3813        IF (    (     (xdatap(i)-a(ii) >= 1.e-5) &
3814 &               .AND.(xdatap(i)-b(ii) <= 1.e-5) ) &
3815 &          .OR.(     (xdatap(i)-a(ii) <= 1.e-5) &
3816 &               .AND.(xdatap(i)-b(ii) >= 1.e-5) ) ) THEN
3817          DO j=1,jmdep
3818            IF (    (     (ydata(j)-c(jj) >= 1.e-5) &
3819 &                   .AND.(ydata(j)-d(jj) <= 1.e-5) ) &
3820 &              .OR.(     (ydata(j)-c(jj) <= 1.e-5) &
3821 &                   .AND.(ydata(j)-d(jj) >= 1.e-5) ) ) THEN
3822              num_tot(ii,jj) = num_tot(ii,jj)+1
3823              IF (mask_inp(i,j) < 0.5) THEN
3824                num_oce(ii,jj) = num_oce(ii,jj)+1
3825!-------------- on a trouve un point oceanique. On le memorise.
3826                ncorr_oce(ii,jj) = ncorr_oce(ii,jj)+1
3827                IF ((i == imdepp).AND.extend) THEN
3828                  icorr_oce(ii,jj,ncorr_oce(ii,jj)) = 1
3829                ELSE
3830                  icorr_oce(ii,jj,ncorr_oce(ii,jj)) = i
3831                ENDIF
3832                jcorr_oce(ii,jj,ncorr_oce(ii,jj)) = j
3833              ELSE
3834!-------------- on a trouve un point continental. On le memorise.
3835                ncorr_land(ii,jj) = ncorr_land(ii,jj)+1
3836                IF ((i == imdepp).AND.extend) THEN
3837                  icorr_land(ii,jj,ncorr_land(ii,jj)) = 1
3838                ELSE
3839                  icorr_land(ii,jj,ncorr_land(ii,jj)) = i
3840                ENDIF
3841                jcorr_land(ii,jj,ncorr_land(ii,jj)) = j
3842              ENDIF
3843            ENDIF
3844          ENDDO
3845        ENDIF
3846      ENDDO
3847    ENDDO
3848  ENDDO
3849!-
3850  DO i=1,imar
3851    DO j=1,jmar
3852      IF (num_tot(i,j) > 0) THEN
3853        IF (    (     (num_oce(i,j) == 0) &
3854 &               .AND.(num_tot(i,j) > 0) ) &
3855 &          .OR.(     (num_oce(i,j) > 0) &
3856 &               .AND.(   REAL(num_oce(i,j)) &
3857 &                     <= REAL(num_tot(i,j))*(1.-fcrit) ) ) ) THEN
3858          mask(i,j) = un
3859          ncorr(i,j) = ncorr_land(i,j)
3860          icorr(i,j,:) = icorr_land(i,j,:)
3861          jcorr(i,j,:) = jcorr_land(i,j,:)
3862        ELSE
3863          mask(i,j) = zero
3864          ncorr(i,j) = ncorr_oce(i,j)
3865          icorr(i,j,:) = icorr_oce(i,j,:)
3866          jcorr(i,j,:) = jcorr_oce(i,j,:)
3867        ENDIF
3868      ELSE
3869        CALL dist_sphe(x(i),y(j),xdatap,ydata,imdepp,jmdep,distans)
3870        ij_proche(:) = MINLOC(distans)
3871        j_proche = (ij_proche(1)-1)/imdepp+1
3872        i_proche = ij_proche(1)-(j_proche-1)*imdepp
3873        mask(i,j) = mask_inp(i_proche,j_proche)
3874        IF ( (i_proche == imdepp).AND.extend)  i_proche=1
3875        ncorr(i,j) = 1
3876        icorr(i,j,1) = i_proche
3877        jcorr(i,j,1) = j_proche
3878      ENDIF
3879    ENDDO
3880  ENDDO
3881!----------------------
3882END SUBROUTINE mask_c_o
3883!-
3884!===
3885!-
3886!! ================================================================================================================================
3887!! SUBROUTINE   : dist_sphe
3888!!
3889!>\BRIEF        This subroutine computes the minimum distance between two points on Earth
3890!! according the great circle. \n
3891!!
3892!! DESCRIPTION  : None
3893!!
3894!! RECENT CHANGE(S): Laurent Li, 30/12/1996 : creation of this subroutine
3895!!
3896!! MAIN OUTPUT VARIABLE(S): ::distance
3897!!
3898!! REFERENCE(S) :
3899!!
3900!! FLOWCHART    : None
3901!! \n
3902!_ ================================================================================================================================
3903
3904SUBROUTINE dist_sphe (rf_lon,rf_lat,rlon,rlat,im,jm,distance)
3905
3906  !! 0. Variables and parameters declaration
3907
3908  !! 0.1 Input variables
3909
3910  INTEGER :: im, jm    !! dimensions
3911  REAL    :: rf_lon       !! longitude of the referenced point (degrees)
3912  REAL    :: rf_lat       !! latitude of the referenced point (degrees)
3913  REAL    :: rlon(im), rlat(jm) !! longitude and latitude of points
3914
3915  !! 0.2 Output variables
3916
3917  REAL :: distance(im,jm) !! distances in meters (m)
3918
3919  !! 0.4 Local variables
3920
3921  REAL :: rlon1, rlat1
3922  REAL :: rlon2, rlat2
3923  REAL :: dist
3924  REAL :: pa, pb, p
3925  INTEGER :: i,j
3926
3927!_ ================================================================================================================================
3928
3929  DO j=1,jm
3930    DO i=1,im
3931      rlon1=rf_lon
3932      rlat1=rf_lat
3933      rlon2=rlon(i)
3934      rlat2=rlat(j)
3935      pa = pi/2.0-rlat1*pir ! dist. entre pole n et point a
3936      pb = pi/2.0-rlat2*pir ! dist. entre pole n et point b
3937!-----
3938      p = (rlon1-rlon2)*pir ! angle entre a et b (leurs meridiens)
3939!-----
3940      dist = ACOS( COS(pa)*COS(pb)+SIN(pa)*SIN(pb)*COS(p))
3941      dist = R_Earth*dist     
3942      distance(i,j) = dist
3943    ENDDO
3944  ENDDO
3945!-----------------------
3946END SUBROUTINE dist_sphe
3947!-
3948!===
3949!-
3950
3951!! ================================================================================================================================
3952!! SUBROUTINE   : permute
3953!!
3954!>\BRIEF         This subroutine initializes an array of size n by random integers between 1 and n. 
3955!!
3956!! DESCRIPTION  : None
3957!!
3958!! RECENT CHANGE(S): None
3959!!
3960!! MAIN OUTPUT VARIABLE(S): ::ordre
3961!!
3962!! REFERENCE(S) :
3963!!
3964!! FLOWCHART    : None
3965!! \n
3966!_ ================================================================================================================================
3967
3968SUBROUTINE permute (n,ordre)
3969!---------------------------------------------------------------------
3970
3971  !! 0. Variables and parameters declaration
3972
3973  !! 0.1 Input variables
3974
3975  INTEGER,INTENT(IN) :: n   !! size of the array
3976
3977  !! 0.2 Output variables
3978
3979  INTEGER,DIMENSION(n),INTENT(OUT) :: ordre
3980
3981  !! 0.4 Local variables
3982
3983  INTEGER,DIMENSION(n) :: restant
3984  INTEGER :: ipique, i, n_rest
3985  REAL    :: rndnum
3986
3987!_ ================================================================================================================================
3988
3989  n_rest = n
3990  restant(:) = (/ (i, i=1,n) /)
3991!-
3992  DO i=1,n
3993    CALL random_number (rndnum)
3994    ipique = INT(rndnum*n_rest)+1
3995    ordre(i) = restant(ipique)
3996    restant(ipique:n_rest-1) = restant(ipique+1:n_rest)
3997    n_rest = n_rest-1
3998  ENDDO
3999!---------------------
4000END SUBROUTINE permute
4001!-
4002!===
4003!-----------------
4004END MODULE weather
Note: See TracBrowser for help on using the repository browser.