SURFEX v8.1
General documentation of Surfex
read_direct.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE read_direct (UG, U, USS, &
7  HPROGRAM,HSCHEME,HSUBROUTINE,HFILENAME,HFIELD,OMULTITYPE)
8 ! #########################################################
9 !
10 !!**** *READ_DIRECT1* reads a latlon file and call treatment subroutine
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !! METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !! AUTHOR
28 !! ------
29 !!
30 !! V. Masson Meteo-France
31 !!
32 !! MODIFICATION
33 !! ------------
34 !!
35 !! Original 11/09/95
36 !!
37 !! V. Masson, March 2010 Optimization of some lat/lon boundaries computations
38 !! J.Escobar 06/2013 for REAL4/8 add EPSILON management
39 !----------------------------------------------------------------------------
40 !
41 !* 0. DECLARATION
42 ! -----------
43 !
44 USE modd_surf_par, ONLY : xundef
45 USE modd_surfex_mpi, ONLY : nrank, nproc, npio
46 !
48 USE modd_surf_atm_n, ONLY : surf_atm_t
49 USE modd_sso_n, ONLY : sso_t
50 !
52 !
53 USE modd_arch, ONLY : little_endian_arch
54 !
55 USE modd_data_cover_par, ONLY : jpcover, ntype
56 !
57 USE modi_get_luout
58 USE modi_open_namelist
59 USE modi_close_namelist
60 USE modi_open_file
61 USE modi_close_file
62 USE modi_readhead
63 USE modi_ini_ssowork
64 USE modi_pt_by_pt_treatment
66 !
67 USE modi_uncompress_field
68 !
69 USE yomhook ,ONLY : lhook, dr_hook
70 USE parkind1 ,ONLY : jprb
71 !
72 USE modi_abor1_sfx
73 !
76 USE modi_refresh_pgdwork
77 !
78 USE modd_csts ,ONLY : xsurf_epsilon
79 !
80 IMPLICIT NONE
81 !
82 !* 0.1 Declaration of arguments
83 ! ------------------------
84 !
85 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
86 TYPE(surf_atm_t), INTENT(INOUT) :: U
87 TYPE(sso_t), INTENT(INOUT) :: USS
88 !
89  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! Type of program
90  CHARACTER(LEN=6), INTENT(IN) :: HSCHEME ! Scheme treated
91  CHARACTER(LEN=6), INTENT(IN) :: HSUBROUTINE ! Name of the subroutine to call
92  CHARACTER(LEN=28), INTENT(IN) :: HFILENAME ! Name of the field file.
93  CHARACTER(LEN=20), INTENT(IN) :: HFIELD ! Name of the field.
94 LOGICAL, OPTIONAL, INTENT(IN) :: OMULTITYPE
95 !
96 !* 0.2 Declaration of local variables
97 ! ------------------------------
98 !
99  CHARACTER(LEN=28) :: YFILENAME ! Name of the field file without header
100  CHARACTER(LEN=28) :: YFILEHDR ! Name of the field file header
101 !
102  CHARACTER(LEN=7) :: YTYPE ! type of numerical field stored in the
103 ! ! direct access file ('INTEGER','REAL ')
104  CHARACTER(LEN=100):: YSTRING ! string
105  CHARACTER(LEN=88 ):: YSTRING1 ! part of string STRING
106 !
107  CHARACTER(LEN=2), DIMENSION(1) :: YCPT16 ! value of a data point
108  CHARACTER(LEN=4), DIMENSION(:), ALLOCATABLE :: YCPT32
109 !
110  CHARACTER, DIMENSION(:), ALLOCATABLE :: YVALUE8 ! value of a data point
111  CHARACTER(LEN=2), DIMENSION(:), ALLOCATABLE :: YVALUE16 ! value of a data point
112  CHARACTER(LEN=4), DIMENSION(:), ALLOCATABLE :: YVALUE32R ! value of a data point
113  CHARACTER(LEN=8), DIMENSION(:), ALLOCATABLE :: YVALUE64 ! value of a data point
114 !
115 REAL, DIMENSION(1) :: ZCPT
116 !
117 REAL :: ZGLBLATMIN ! minimum latitude of data box in the file
118 REAL :: ZGLBLONMIN ! minimum longitude of data box in the file
119 REAL :: ZGLBLATMAX ! maximum latitude of data box in the file
120 REAL :: ZGLBLONMAX ! maximum longitude of data box in the file
121 REAL :: ZNODATA, ZNODATA2 ! value below which data are not considered
122 REAL :: ZDLAT ! latitude mesh in the data file
123 REAL :: ZDLON ! longitude mesh in the data file
124 REAL :: ZLONMIN ! minimum longitude of mask mesh
125 REAL :: ZLONMAX ! maximum longitude of mask mesh
126 REAL :: ZLATMIN ! minimum latitude of mask mesh
127 REAL :: ZLATMAX ! maximum latitude of mask mesh
128 REAL :: ZSHIFT ! shift on longitudes
129 INTEGER :: IFACT ! Factor integer to real
130 INTEGER(KIND=2) :: INODATA, INODATA2
131 !
132 REAL, DIMENSION(:), ALLOCATABLE :: ZVALUE
133 REAL, DIMENSION(:), POINTER :: ZLAT ! latitude of data points
134 REAL, DIMENSION(:), POINTER :: ZLON ! longitude of data points
135 REAL(KIND=4), DIMENSION(:), ALLOCATABLE :: ZVALUE32 ! value of a data point
136 REAL, DIMENSION(:), ALLOCATABLE :: ZINTER ! value of a record of data points
137 REAL, DIMENSION(:), ALLOCATABLE :: ZVALUE_WORK ! value of a valid data points
138 REAL, DIMENSION(:), ALLOCATABLE :: ZLAT_WORK ! latitude of a valid data points
139 REAL, DIMENSION(:), ALLOCATABLE :: ZLON_WORK ! longitude of a valid data points
140 !
141 INTEGER :: IINDEX ! index of a character in string STRING1
142 INTEGER :: IBITS ! number of bits of a record in the
143  ! direct access file (16,32,64)
144 INTEGER :: IRECLENGTH ! record length
145 INTEGER :: IREC ! record number
146 INTEGER :: IGLB, IGLBHDR ! logical units
147 INTEGER :: ILUOUT ! output listing logical unit
148 INTEGER :: IERR ! return codes
149 !
150 INTEGER :: INBLINE ! number of latitude rows (number of lines
151 INTEGER :: INBCOL ! number of longitude rows (number of columns)
152 INTEGER :: ILINE1,ILINE2 ! limits of index of lines
153 INTEGER :: ICOL ! number of columns in mask domain
154 INTEGER :: ICOLINDEX ! column index in record
155 INTEGER :: ISIZE
156 INTEGER :: IWORK, IDEB, IPAS ! index of these data
157 INTEGER :: JLOOP, JLON, JLAT, JLINE, JCOL, JL, ICPT, INB, JTYPE
158 INTEGER :: ILINE_COMPRESS
159 INTEGER :: INB_LINE_READ
160 INTEGER(KIND=8) :: IPOS
161 !
162 INTEGER, DIMENSION(360) :: IMASK
163 INTEGER, DIMENSION(2) :: ICOL1, ICOL2 ! limits of index of columns
164 !
165 INTEGER(KIND=4), DIMENSION(:), ALLOCATABLE :: ICPT0 ! loop index
166 INTEGER(KIND=4), DIMENSION(:), ALLOCATABLE :: IVALUE32 ! value of a data point
167 INTEGER(KIND=8), DIMENSION(:), ALLOCATABLE :: IVALUE64 ! value of a data point
168 !
169  CHARACTER(LEN=6) :: YACCESS
170 LOGICAL :: GSWAP ! T: swap has been done
171 LOGICAL :: GMULTITYPE, GCOMPRESS
172 !
173 REAL(KIND=JPRB) :: ZHOOK_HANDLE
174 !----------------------------------------------------------------------------
175 !
176 IF (lhook) CALL dr_hook('READ_DIRECT',0,zhook_handle)
177  CALL get_luout(hprogram,iluout)
178 !
179 !* 1. Openning of global field
180 ! ------------------------
181 !
182 !* 1.1 Logical unit attributions
183 ! -------------------------
184 !
185 yfilename=adjustl(adjustr(hfilename)//'.dir')
186 yfilehdr =adjustl(adjustr(hfilename)//'.hdr')
187 !
188 !* 1.2 Openning of header
189 ! ------------------
190 !
191  CALL open_namelist(hprogram,iglbhdr,yfilehdr)
192 !
193 !* 1.3 Reading in header of direct access characteristics
194 ! --------------------------------------------------
195 !
196 DO jloop=1,11
197  READ(iglbhdr,'(A100)') ystring
198  IF (ystring(1:10)=='recordtype') EXIT
199 END DO
200 !
201 rewind(iglbhdr)
202 !
203 ystring1=ystring(12:100)
204 !
205 !* string analysis
206 !
207 iindex=index(ystring1,'n') ! n for integer
208 IF (iindex/=0) THEN
209  ytype='INTEGER'
210 ELSE
211  ytype='REAL '
212 END IF
213 iindex=index(ystring1,'8')
214 IF (iindex/=0) ibits=8
215 iindex=index(ystring1,'1')
216 IF (iindex/=0) ibits=16
217 iindex=index(ystring1,'3')
218 IF (iindex/=0) ibits=32
219 iindex=index(ystring1,'4')
220 IF (iindex/=0) ibits=64
221 !
222 !----------------------------------------------------------------------------
223 !
224 !* 2. Reading of the global field
225 ! ---------------------------
226 !
227 !* 2.1 Head of data file
228 ! -----------------
229 !
230  CALL readhead(iglbhdr,zglblatmin,zglblatmax,zglblonmin,zglblonmax, &
231  inbline,inbcol,znodata,zdlat,zdlon,zlat,zlon,ierr,ifact,&
232  gcompress)
233 IF (ierr/=0) CALL abor1_sfx('READ_DIRECT: PB IN FILE HEADER')
234 !
235 IF (gcompress .AND. (ytype/='INTEGER' .OR. ibits/=16)) &
236  CALL abor1_sfx('READ_DIRECT: COMPRESSED FILES ARE POSSIBLE ONLY WITH INTEGER 16 BYTES FOR THE MOMENT')
237 !
238 gmultitype = .false.
239 IF (PRESENT(omultitype)) gmultitype = omultitype
240 !
241 IF (gmultitype) THEN
242  DEALLOCATE(nsize_all)
243  ALLOCATE(nsize_all(u%NDIM_FULL,sum(ntype)))
244  nsize_all(:,:) = 0
245  IF (catype=='MAJ') THEN
246  DEALLOCATE(nvalnbr,nvalcount,xvallist)
247  ALLOCATE(nvalnbr(u%NDIM_FULL,sum(ntype)))
248  ALLOCATE(nvalcount(u%NDIM_FULL,jpvalmax,sum(ntype)))
249  ALLOCATE(xvallist(u%NDIM_FULL,jpvalmax,sum(ntype)))
250  nvalnbr(:,:) = 0
251  nvalcount(:,:,:) = 0
252  xvallist(:,:,:) = xundef
253  ELSE
254  DEALLOCATE(xall)
255  ALLOCATE(xall(u%NDIM_FULL,sum(ntype),1))
256  xall(:,:,:) = 0.
257  ENDIF
258 ENDIF
259 !
260 IF(ytype=='INTEGER')THEN
261  IF(hfield(1:3)=='CTI'.OR.hfield=='sand fraction'.OR.hfield=='clay fraction'.OR.&
262  hfield=='organic carbon'.OR.hfield(1:4)=='SAND'.OR. hfield(1:4)=='CLAY'.OR.hfield(1:3)=='SOC')THEN
263  ifact=100
264  ELSEIF (hfield=='water depth') THEN
265  ifact=10
266  ENDIF
267 ENDIF
268 !
269 !* 2.2 Closing of header
270 ! -----------------
271 !
272  CALL close_namelist(hprogram,iglbhdr)
273 !
274 !* 2.3 Dimension of work arrays
275 ! ------------------------
276 !
277 ! ires c'est le nombre de lignes qu'on lit dans un demi degré (multiple de 60)
278 inb_line_read = inbline / ((zglblatmax-zglblatmin)*2.)
279 IF (inb_line_read>60) inb_line_read = max(inb_line_read/3,60)
280 ! on lit toujours 60 lignes d'un coup
281 isize = inb_line_read * inbcol
282 !
283 ALLOCATE(zlat_work(isize))
284 ALLOCATE(zlon_work(isize))
285 ALLOCATE(zvalue_work(isize))
286 IF (gcompress.OR.gmultitype) THEN
287  ALLOCATE (zinter(isize))
288  zinter(:) = 0.
289 ENDIF
290 !
291 !----------------------------------------------------------------------------
292 !
293 !* 3. Adapt subgrid mesh to input file resolution
294 ! -------------------------------------------
295 !
296 IF (hsubroutine=='A_OROG') CALL ini_ssowork(xmeshlength,zdlat,zdlon)
297 !
298 !----------------------------------------------------------------------------
299 !
300 !* 7. Openning of direct access file
301 ! ------------------------------
302 !
303 !* 7.1 Record length
304 ! -------------
305 !
306 ireclength = ibits/8 * inbcol
307 ALLOCATE (zvalue(inbcol))
308 zvalue(:) = 0.
309 !
310 IF (gcompress) THEN
311  ALLOCATE(ycpt32(inbline))
312  ALLOCATE(icpt0(inbline))
313 ENDIF
314 !
315 IF (ytype=='INTEGER' .AND. ibits== 8) THEN
316  ALLOCATE (yvalue8(inbcol))
317 ELSEIF (ytype=='INTEGER' .AND. ibits==16) THEN
318  ALLOCATE (yvalue16(inbcol))
319 ELSEIF (ytype=='INTEGER' .AND. ibits==32) THEN
320  ALLOCATE (ivalue32(inbcol))
321  ELSEIF (ytype=='INTEGER' .AND. ibits==64) THEN
322  ALLOCATE (ivalue64(inbcol))
323 ELSEIF (ytype=='REAL ' .AND. ibits==32) THEN
324  ALLOCATE (yvalue32r(inbcol))
325 ELSEIF (ytype=='REAL ' .AND. ibits==64) THEN
326  ALLOCATE (yvalue64(inbcol))
327 ENDIF
328 !
329 !* 7.2 Openning of direct access file
330 ! ------------------------------
331 !
332 yaccess = 'DIRECT'
333 IF (gcompress) THEN
334  yaccess='STREAM'
335  little_endian_arch = .false.
336 ENDIF
337 !
338  CALL open_file(hprogram,iglb,yfilename,'UNFORMATTED', &
339  haction='READ',haccess=yaccess,krecl=ireclength )
340 !
341 ! we read numbers of elements by line of the grid at the beginning
342 IF (gcompress) THEN
343  READ(iglb) ycpt32
344  icpt0(:) = transfer(ycpt32(:),1_4,inbline)
345 ENDIF
346 !
347 !----------------------------------------------------------------------------
348 !
349 !* 4. loop on mask meshes (lat)
350 ! -------------------
351 !
352 imask(:) = 0
353 icpt = 0
354 DO jlat = 1,360
355  IF ( .NOT. any(llatlonmask(:,jlat)) ) cycle
356  zlatmin = (jlat-180)/2. - 0.5
357  zlatmax = (jlat-180)/2.
358  IF ( .NOT. any(zlat(:)<zlatmax .AND. zlat(:)>=zlatmin) ) cycle
359  icpt = icpt + 1
360  imask(icpt) = jlat
361 ENDDO
362 !
363 !INB: number of lat to be read
364 inb = icpt
365 !
366 !IPAS: number of lat to be read for each task
367 ipas = ceiling(inb*1./nproc)
368 !
369 gswap = .false.
370 !
371 !first lat read for this task
372 ideb = ipas*nrank
373 !
374 icpt = 0
375 !
376 jl = ipas + 1
377 !
378 IF (gcompress) iline_compress = 1
379 !
380 inodata = znodata
381 inodata2 = ishftc(inodata,8)
382 znodata2 = inodata2
383 !
384 DO
385  !
386  !the file is read from the top to the bottom (quicker)
387  jl = jl - 1
388  IF (jl==0) EXIT
389  !
390  IF (ideb+jl>inb) cycle
391  !
392  !lat read by this task for this loop index JL
393  jlat = imask(ideb+jl)
394  !
395  zlatmin = (jlat-180)/2. - 0.5
396  zlatmax = (jlat-180)/2.
397  !
398  !----------------------------------------------------------------------------
399  !
400  !* 5. index limits on latitude
401  ! ------------------------
402  !
403  iline1=max(min(int((zglblatmax-zdlat/2.-zlatmax)/zdlat+1.),inbline),0)+1
404  iline2=max(min(int((zglblatmax-zdlat/2.-zlatmin)/zdlat+1.),inbline),0)
405  !
406  !----------------------------------------------------------------------------
407  !
408  !* 8. Loop on lines
409  ! -------------
410  !
411  ! first IPOS for this task is the first information plus the
412  ! number of elements by lines before the first to read
413  IF (gcompress.AND.(jl==ipas.OR.iline_compress<iline1)) THEN
414  ipos = 0
415  IF (iline1>1) THEN
416  DO jloop=1,iline1-1
417  ipos = ipos + icpt0(jloop)
418  ENDDO
419  ENDIF
420  ipos = ipos*2 + 1 + inbline*4
421  iline_compress = iline1
422  ELSE
423  ipos = 0
424  ENDIF
425  !
426  DO jline = iline1,iline2
427  !
428  !----------------------------------------------------------------------------
429  !
430  !* 10. Reading in the direct access file
431  ! ---------------------------------
432  !
433  !* 10.1 Record number
434  ! -------------
435  !
436  irec = jline
437  !
438  !* 10.2 Reading the correct data type and conversion into real
439  ! ------------------------------------------------------
440  !
441  IF (ytype=='INTEGER' .AND. ibits== 8) THEN
442  READ(iglb,rec=irec) yvalue8(:)
443  zvalue(:)=yvalue8(:)
444  ! negative values are shifted to positive values according to binary coding
445  WHERE (zvalue(:)<0.) zvalue(:) = nint(256.+zvalue(:))
446  !
447  ELSE IF (ytype=='INTEGER' .AND. ibits==16) THEN
448  !
449  IF (gcompress) THEN
450  IF (ipos/=0) THEN
451  READ(iglb,pos=ipos) yvalue16(1:icpt0(jline))
452  ipos = 0
453  ELSE
454  READ(iglb) yvalue16(1:icpt0(jline))
455  ENDIF
456  zvalue(1:icpt0(jline))=yvalue16(1:icpt0(jline))
457  iline_compress = iline_compress + 1
458  ELSE
459  READ(iglb,rec=irec) yvalue16(:)
460  zvalue(:)=yvalue16(:)
461  ENDIF
462  !
463  IF (icpt==0.AND..NOT.gcompress) THEN
464  IF ( (hfield(1:5)=="COVER" .AND. (any(zvalue>jpcover.AND.zvalue/=znodata) .OR. &
465  any(zvalue<0..AND.zvalue/=znodata) .OR. all(zvalue==256.)) ) .OR. &
466  (znodata/=0 .AND. (all(zvalue==znodata2))) .OR. &
467  ((hfield(1:4)=="SAND" .OR. hfield(1:4)=="CLAY") .AND. &
468  (any(zvalue>100..AND.zvalue/=znodata) .OR. any(zvalue<0..AND.zvalue/=znodata)) ) .OR. &
469  (hfield(1:3)=="SOC" .AND. (any(zvalue>15000..AND.zvalue/=znodata) .OR. any(zvalue<0..AND.zvalue/=znodata)) ) .OR. &
470  ((hfield(1:5)/="COVER" .AND. hfield(1:4)/="SAND" .AND. hfield(1:4)/="CLAY" .AND. &
471  hfield(1:3)/="SOC" .AND. any(zvalue>15000..AND.zvalue/=znodata) ) ) ) THEN
472  icpt = icpt + 1
473  IF (gswap) CALL abor1_sfx('READ_DIRECT: SWAP ALREADY DONE, CANNOT BE REDONE')
475  gswap = .true.
476  IF (nrank==npio) THEN
477  WRITE(iluout,*) '*******************************************************************'
478  WRITE(iluout,*) 'Architecture of the machine needs to swap LITTLE_ENDIAN_ARCH to ', &
480  WRITE(iluout,*) '*******************************************************************'
481  ENDIF
482  jl = ipas + 1 !back to first lat
483  IF (hfield(1:5)=="COVER") u%LCOVER(:) = .false.
484  CALL refresh_pgdwork(hsubroutine)
485  EXIT ! rereads the file
486  ENDIF
487  ENDIF
488  !
489  !
490  ELSE IF (ytype=='INTEGER' .AND. ibits==32) THEN
491  READ(iglb,rec=irec) ivalue32(:)
492  zvalue(:)=ivalue32(:)
493  !
494  ELSE IF (ytype=='INTEGER' .AND. ibits==64) THEN
495  READ(iglb,rec=irec) ivalue64(:)
496  zvalue(:)=ivalue64(:)
497  !
498  ELSE IF (ytype=='REAL ' .AND. ibits==32) THEN
499  READ(iglb,rec=irec) yvalue32r(:)
500  zvalue(:)=yvalue32r(:)
501  !
502  IF (icpt==0) THEN
503  IF ( any(abs(zvalue)>0. .AND. abs(zvalue)<1.e-50) &
504  .OR. any(abs(zvalue)>1.e20) ) THEN
505  icpt = icpt + 1
506  IF (gswap) CALL abor1_sfx('READ_DIRECT: SWAP ALREADY DONE, CANNOT BE REDONE')
508  gswap = .true.
509  IF (nrank==npio) THEN
510  WRITE(iluout,*) '*******************************************************************'
511  WRITE(iluout,*) 'Architecture of the machine needs to swap LITTLE_ENDIAN_ARCH to ', &
513  WRITE(iluout,*) '*******************************************************************'
514  ENDIF
515  jl = ipas + 1
516  CALL refresh_pgdwork(hsubroutine)
517  EXIT
518  ENDIF
519  END IF
520  !
521  ELSE IF (ytype=='REAL ' .AND. ibits==64) THEN
522  READ(iglb,rec=irec) yvalue64(:)
523  zvalue(:)=yvalue64(:)
524  !
525  IF (icpt==0) THEN
526  IF ( any(abs(zvalue)>0. .AND. abs(zvalue)<1.e-50) &
527  .OR. any(abs(zvalue)>1.e20) ) THEN
528  icpt = icpt + 1
529  IF (gswap) CALL abor1_sfx('READ_DIRECT: SWAP ALREADY DONE, CANNOT BE REDONE')
531  gswap = .true.
532  IF (nrank==npio) THEN
533  WRITE(iluout,*) '*******************************************************************'
534  WRITE(iluout,*) 'Architecture of the machine needs to swap LITTLE_ENDIAN_ARCH to ', &
536  WRITE(iluout,*) '*******************************************************************'
537  ENDIF
538  jl = ipas + 1
539  CALL refresh_pgdwork(hsubroutine)
540  EXIT
541  ENDIF
542  ENDIF
543  ELSE
544  CALL abor1_sfx('READ_DIRECT1: DATA TYPE NOT SUPPORTED')
545  END IF
546  !
547  IF(hfield=='CTI')THEN
548  WHERE(zvalue(:)<0.0) zvalue(:)=znodata
549  ENDIF
550  !
551  IF (gcompress) THEN
552  WHERE (zvalue(1:icpt0(jline))<0.) zvalue(1:icpt0(jline)) = nint(32768*2.+zvalue(1:icpt0(jline)))
553  zinter(1:icpt0(jline)) = zvalue(1:icpt0(jline))
554  CALL uncompress_field(inbcol,4000.,zinter(1:icpt0(jline)),zvalue(:))
555  ENDIF
556  !
557  !----------------------------------------------------------------------------
558  !
559  !* 4. loop on mask meshes (lon)
560  ! -------------------
561  !
562  DO jlon=1,720
563  !
564  IF (.NOT. llatlonmask(jlon,jlat)) cycle
565  !
566  zlonmin = jlon /2. - 0.5
567  zlonmax = jlon /2.
568  !
569  !----------------------------------------------------------------------------
570  !
571  !* 5. limits on longitude
572  ! -------------------
573  !
574  !* 5.1 left domain border is set just higher than the global field min. longitude
575  ! -----------------------------------------------------------------
576  !
577  zshift = 360. * nint((zlonmin-zglblonmin-180.*(1-xsurf_epsilon))/360.)
578  !
579  zglblonmin = zglblonmin + zshift
580  zglblonmax = zglblonmax + zshift
581  !
582  !* 5.2 index limits on longitude
583  ! -------------------------
584  !
585  icol1(1)=max(min(int((zlonmin-zglblonmin-zdlon/2.)/zdlon+1.),inbcol),0)+1
586  icol2(1)=max(min(int((zlonmax-zglblonmin-zdlon/2.)/zdlon+1.),inbcol),0)
587  !
588  !* Does right domain border goes outside the global field longitude range?
589  !* Does it then goes into the global field domain by the other side?
590  !* Then a second part of the global field domain must be considered
591  !
592  icol1(2)=1
593  icol2(2)=max(min(int((zlonmax-zglblonmin-zdlon/2.-360.)/zdlon+1.),inbcol),0)
594  !
595  !----------------------------------------------------------------------------
596  !
597  !* 6. Loop on longitude limits
598  ! ------------------------
599  !
600  DO jloop=1,2
601  !
602  icol = icol2(jloop) - icol1(jloop) + 1
603  !
604  IF (icol<1) cycle
605  !
606  !----------------------------------------------------------------------------
607  !
608  !* 11. Loop on columns
609  ! ---------------
610  !
611  iwork=0
612  !
613  DO jcol=1,icol
614  !
615  !* 11.1 Recovers point value
616  ! --------------------
617  !
618  icolindex = jcol+icol1(jloop)-1
619  !
620  !* 11.2 Test with respect to the 'no data' value
621  ! ----------------------------------------
622  !
623  IF (abs(zvalue(icolindex)-znodata)<=1.e-10) cycle
624  !
625  !* 11.3 copy of the correct values in a work array
626  ! ------------------------------------------
627  !
628  iwork = iwork + 1
629  zlat_work(iwork) = zlat(jline)
630  zlon_work(iwork) = zlon(icolindex)
631  zvalue_work(iwork) = zvalue(icolindex)
632  !
633  END DO
634  !-------------------------------------------------------------------------------
635  !
636  IF (.NOT.gmultitype.AND.ifact/=1) THEN
637  WHERE(zvalue_work(1:iwork)/=znodata)
638  zvalue_work(1:iwork)=zvalue_work(1:iwork)/float(ifact)
639  END WHERE
640  ENDIF
641  !
642  !* 12. Call to the adequate subroutine (point by point treatment)
643  ! ----------------------------------------------------------
644  !
645  IF (iwork>0) &
646  CALL pt_by_pt_treatment(ug, u, uss, &
647  iluout, zlat_work(1:iwork),zlon_work(1:iwork), &
648  zvalue_work(1:iwork), &
649  hsubroutine, omultitype=gmultitype, kfact=ifact)
650 !
651 !-------------------------------------------------------------------------------
652  END DO
653 !-------------------------------------------------------------------------------
654  END DO
655 !-------------------------------------------------------------------------------
656  END DO
657 !-------------------------------------------------------------------------------
658 END DO
659 !
660 !-------------------------------------------------------------------------------
661 !
662 
663 DEALLOCATE(zlat)
664 DEALLOCATE(zlon)
665 !
666 DEALLOCATE(zlat_work )
667 DEALLOCATE(zlon_work )
668 DEALLOCATE(zvalue_work)
669 !
670 DEALLOCATE (zvalue)
671 IF (ALLOCATED(zinter)) DEALLOCATE (zinter)
672 IF (ALLOCATED(yvalue8)) DEALLOCATE (yvalue8 )
673 IF (ALLOCATED(yvalue16)) DEALLOCATE (yvalue16)
674 IF (ALLOCATED(yvalue32r)) DEALLOCATE (yvalue32r)
675 IF (ALLOCATED(yvalue64)) DEALLOCATE (yvalue64)
676 IF (ALLOCATED(ivalue32)) DEALLOCATE (ivalue32)
677 IF (ALLOCATED(ivalue64)) DEALLOCATE (ivalue64)
678 IF (ALLOCATED(zvalue32)) DEALLOCATE (zvalue32)
679 !
680  CALL close_file(hprogram,iglb)
681 IF (lhook) CALL dr_hook('READ_DIRECT',1,zhook_handle)
682 !
683 !-------------------------------------------------------------------------------
684 !
685 END SUBROUTINE read_direct
real, dimension(:,:,:), allocatable xvallist
subroutine open_file(HPROGRAM, KUNIT, HFILE, HFORM, HACTION, HACCESS, KR
Definition: open_file.F90:7
character(len=3) catype
logical, dimension(720, 360) llatlonmask
integer, dimension(:,:), allocatable nsize_all
subroutine uncompress_field(KLONG, PSEUIL, PFIELD_IN, PFIELD_OUT)
real, dimension(:,:,:), allocatable xall
subroutine read_direct(UG, U, USS, HPROGRAM, HSCHEME, HSUBROUTINE, HFILENAME, HFI
Definition: read_direct.F90:8
subroutine refresh_pgdwork(HSUBROUTINE)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
real, save xsurf_epsilon
Definition: modd_csts.F90:88
integer, dimension(:,:), allocatable nvalnbr
subroutine ini_ssowork(PMESHLENGTH, PDLAT, PDLON)
Definition: ini_ssowork.F90:7
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine close_file(HPROGRAM, KUNIT)
Definition: close_file.F90:7
subroutine pt_by_pt_treatment(UG, U, USS, KLUOUT, PLAT, PLON, PVALUE, HSUBROUTINE
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
intent(out) overrides sub arrays one Sort by the least significant key first sum(iindex(1:n))
logical lhook
Definition: yomhook.F90:15
integer, dimension(:,:,:), allocatable nvalcount
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)
subroutine readhead(KGLB, PGLBLATMIN, PGLBLATMAX, PGLBLONMIN, PGLBLONM
Definition: readhead.F90:7
integer, parameter jpvalmax
ERROR in index
Definition: ecsort_shared.h:90
logical, dimension(nnwl), parameter little_endian_arch
Definition: modd_arch.F90:33