source: ether_ndacc/trunk/dev_ndacc/livraison/src/keckhut/treat_files_list.f90.240708 @ 84

Last change on this file since 84 was 84, checked in by cbipsl, 14 years ago

import ether_ndacc

  • Property svn:executable set to *
File size: 12.6 KB
Line 
1PROGRAM treat_files_list
2
3USE fonctions_mod
4USE grid_ames_mod
5USE head_ames_mod
6USE struct_ames_mod
7USE lidar_mod
8
9IMPLICIT NONE
10
11CHARACTER(LEN=300)                              :: temp_string, temp_string2
12CHARACTER(LEN=250)                              :: filein,list_files,tmp_list
13CHARACTER(LEN=100)                              :: cmoismin,cmoismax,cheuremin,cheuremax ,temp_string3
14CHARACTER(LEN=100)                              :: rep_data,rep_so,chaine,chaine2,rep_lo,file_lo
15CHARACTER(LEN=50)                               :: link
16CHARACTER(LEN=8)                                :: tdate
17CHARACTER(LEN=7)                                :: col1, col2, col5, col6
18CHARACTER(LEN=3)                                :: col4,mois,annee
19CHARACTER(LEN=6)                                :: col3
20CHARACTER(LEN=10)                               :: ttime
21CHARACTER(LEN=5)                                :: tzone
22INTEGER, DIMENSION(8)                           :: tvalues
23CHARACTER(LEN=200)                              :: screen,line,line2
24INTEGER                                         :: i,j,indice,idatemesure,idatemesuremax,idatemesuremin,nblcomment
25INTEGER                                         :: unit,ios,ios2,iosres,debug,nbfile,ios3,lecture,ulog,nbfiles,ifile,temp_int,nbbc
26type(grid_ames)                                 :: sortie_asc,temp_ames
27type(struct_ames)                               :: sortie_ames
28LOGICAL                                         :: retour
29REAL                                            :: temp_real
30
31COMMON                                                                  screen,rep_so,debug
32COMMON                                                                  rep_lo,file_lo,ulog
33
34!lecture du fichier temporaire devant contenir la liste des fichiers de donnees a traiter
35call getarg(1,tmp_list)
36nbfiles=0
37debug=1
38ifile=0
39
40!ouverture liste des fichiers asc a traiter
41OPEN(   UNIT=2, &
42        FILE=tmp_list, &
43        FORM="formatted", &
44        ACCESS="sequential", &
45        STATUS="old", &
46        ACTION="read", &
47        POSITION="rewind", &
48        IOSTAT=ios3 )
49
50
51READ(2,IOSTAT=ios3, FMT='(A)') filein
52
53if (ios3 /= 0 ) then
54        screen="Impossible d ouvrir le fichier temporaire des fichiers de donnees a traiter : "//adjustl(trim(filein))
55        retour=printl()
56        STOP
57endif
58
59rep_data=filein
60screen="DATA DIRECTORY : "//rep_data
61retour=printl()
62
63mois=""
64annee=""
65
66READ(2,IOSTAT=ios3, FMT='(I)') nbfiles
67READ(2,IOSTAT=ios3,FMT='(I)') debug
68READ(2,IOSTAT=ios3,FMT=*) mois
69READ(2,IOSTAT=ios3,FMT=*) annee
70
71 !definition de l'entete
72 OPEN(   UNIT=1, &
73         FILE=trim(adjustl(rep_data))//"./conf.txt", &
74         FORM="formatted", &
75         ACCESS="sequential", &
76         STATUS="old", &
77         ACTION="read", &
78         POSITION="rewind", &
79         IOSTAT=ios2 )
80 
81 READ(1,IOSTAT=ios, FMT='(A)') line
82
83 IF (ios /= 0 ) THEN
84         screen="! Impossible d ouvrir le fichier de configuration"
85         retour=printl()
86         STOP
87 ENDIF
88
89 DO WHILE ( ios == 0)
90
91        IF (index(line,"station")>0) THEN
92               sortie_ames%head%station=line(9:)
93        ENDIF
94        IF (index(line,"instrument=")>0) THEN
95               sortie_ames%head%instrument=line(12:)
96        ENDIF
97        IF (index(line,"instrument2")>0) THEN
98               sortie_ames%head%instrument2=line(13:)
99        ENDIF
100        IF (index(line,"pi=")>0) THEN
101               sortie_ames%head%pi=line(4:)
102        ENDIF
103        IF (index(line,"pi2")>0) THEN
104               sortie_ames%head%pi2=line(5:)
105        ENDIF
106        IF (index(line,"lab")>0) THEN
107               sortie_ames%head%lab=line(5:)
108        ENDIF
109        IF (index(line,"specie")>0) THEN
110               sortie_ames%head%specie=line(8:)
111        ENDIF
112        IF (index(line,"altitude")>0) THEN
113               sortie_ames%head%altitude=line(10:)
114        ENDIF
115        IF (index(line,"latitude")>0) THEN
116               sortie_ames%head%latitude=line(10:)
117        ENDIF
118        IF (index(line,"longitude")>0) THEN
119               sortie_ames%head%longitude=line(11:)
120        ENDIF
121
122
123        READ(1,IOSTAT=ios, FMT='(A)') line
124END DO
125
126CLOSE(unit=1)
127
128
129!creation du fichier de sortie ames
130OPEN( UNIT=14, &
131        FILE="ohte"//trim(adjustl(annee))//trim(adjustl(mois))//".hal", &
132        FORM="formatted", &
133        ACCESS="sequential", &
134        STATUS="unknown", &
135        ACTION="readwrite", &
136        POSITION="rewind", &
137        IOSTAT=iosres )
138
139        if (iosres /= 0 ) then
140                screen="Impossible de creer le fichier des grilles"
141                retour=printl()
142                STOP
143        endif
144
145
146nbbc=0
147
148READ(2,IOSTAT=ios3, FMT='(A)') filein
149
150ALLOCATE(sortie_ames%grids_ames(nbfiles))
151
152DO WHILE ( ios3 == 0 )
153
154        filein=trim(adjustl(filein))
155        screen="current file data="//filein
156        retour=printl()
157
158        OPEN(   UNIT=1, &
159                FILE=filein, &
160                FORM="formatted", &
161                ACCESS="sequential", &
162                STATUS="old", &
163                ACTION="read", &
164                POSITION="rewind", &
165                IOSTAT=ios )
166
167        if (ios /= 0 ) then
168                screen="Impossible d ouvrir le fichier "//trim(adjustl(filein))
169                retour=printl()
170                STOP
171        endif
172        ifile=ifile+1
173
174        screen="-> Reading file : "//adjustl(trim(filein))
175        retour=printl()
176
177        !lecture des donnees et formatage des grilles
178        sortie_asc=lidar(filein,rep_data)
179        indice=size(sortie_asc%tabMesures(:,1))
180       
181        ALLOCATE(sortie_ames%grids_ames(ifile)%tabMesures(indice,6))
182
183        DO i=1,indice
184
185                temp_int=sortie_asc%tabMesures(i,1)
186                sortie_ames%grids_ames(ifile)%tabMesures(i,1)=temp_int
187
188                temp_int=sortie_asc%tabMesures(i,2)
189                sortie_ames%grids_ames(ifile)%tabMesures(i,2)=temp_int
190
191                temp_int=sortie_asc%tabMesures(i,3)
192                sortie_ames%grids_ames(ifile)%tabMesures(i,3)=temp_int
193
194        END DO
195
196        !DEALLOCATE(sortie_ames%grids_ames(ifile)%tabMesures(i,6))
197       
198        sortie_ames%grids_ames(ifile)%top(1)=sortie_asc%top(1)
199        sortie_ames%grids_ames(ifile)%top(2)=sortie_asc%top(2)
200        sortie_ames%grids_ames(ifile)%top(3)=sortie_asc%top(3)
201        sortie_ames%grids_ames(ifile)%top(4)=sortie_asc%top(4)
202        sortie_ames%grids_ames(ifile)%top(5)=sortie_asc%top(5)
203        sortie_ames%grids_ames(ifile)%top(6)=sortie_asc%top(6)
204        sortie_ames%grids_ames(ifile)%top(7)=sortie_asc%top(7)
205        sortie_ames%grids_ames(ifile)%top(8)=sortie_asc%top(8)
206        sortie_ames%grids_ames(ifile)%top(9)=trim(adjustl(sortie_ames%head%latitude))
207        sortie_ames%grids_ames(ifile)%top(10)=trim(adjustl(sortie_ames%head%longitude))
208        sortie_ames%grids_ames(ifile)%top(11)=trim(adjustl(sortie_ames%head%altitude))
209        sortie_ames%grids_ames(ifile)%datemesure=sortie_asc%datemesure
210        sortie_ames%grids_ames(ifile)%cmois=sortie_asc%cmois
211        sortie_ames%grids_ames(ifile)%cheure=sortie_asc%cheure
212       
213        DEALLOCATE(sortie_asc%tabMesures)
214
215        !lecture des mesures terminees => sortie_ames%grids_ames remplie
216
217        nbbc=nbbc+1
218        CLOSE(unit=1)
219        READ(2,IOSTAT=ios3, FMT='(A)') filein
220
221
222END DO
223
224CLOSE(unit=2)
225
226ifile=1
227
228idatemesuremax=0
229idatemesuremin=99999999
230nblcomment=0
231cheuremin=""
232cmoismin=""
233cheuremax=""
234cmoismax=""
235ifile=1
236
237!calcul date DEBUT et FIN mesures
238DO WHILE ( ifile <= nbfiles)
239        temp_string=sortie_ames%grids_ames(ifile)%datemesure
240        READ(temp_string, FMT=*) idatemesure
241
242        IF(idatemesure < idatemesuremin) THEN
243                idatemesuremin=idatemesure
244                cheuremin=sortie_ames%grids_ames(ifile)%cheure
245                cmoismin=sortie_ames%grids_ames(ifile)%cmois
246       ENDIF
247
248       IF (idatemesure > idatemesuremax) THEN
249                idatemesuremax=idatemesure
250                cheuremax=sortie_ames%grids_ames(ifile)%cheure
251                cmoismax=sortie_ames%grids_ames(ifile)%cmois
252
253       ENDIF
254
255       !nblcomment=nblcomment+1
256       ifile=ifile+1
257END DO
258
259
260!DATEMIN
261temp_string=""
262link=""
263retour=concat(temp_string,temp_string3,idatemesuremin,link,7,8)
264sortie_ames%head%datemin=temp_string3
265
266link="-"
267retour=concat(temp_string,cmoismin,-999,link,-1,-1)
268retour=concat(temp_string,temp_string3,idatemesuremin,link,1,4)
269
270link=" "
271retour=concat(temp_string,cheuremin,-999,link,-1,-1)
272sortie_ames%head%datemin=temp_string
273
274!DATEMAX
275temp_string=""
276link=""
277retour=concat(temp_string,temp_string3,idatemesuremax,link,7,8)
278sortie_ames%head%datemax=temp_string3
279link="-"
280retour=concat(temp_string,cmoismax,-999,link,-1,-1)
281retour=concat(temp_string,temp_string3,idatemesuremax,link,1,4)
282link=" "
283retour=concat(temp_string,cheuremax,-999,link,-1,-1)
284sortie_ames%head%datemax=temp_string
285
286!ecriture du fichier de sortie ames
287!head
288temp_string=""
289temp_string3=sortie_ames%head%pi
290link=""
291retour=concat(temp_string,temp_string3,-999,link,-1,-1)
292
293link=" "
294temp_string3=sortie_ames%head%instrument
295retour=concat(temp_string,temp_string3,-999,link,-1,-1)
296
297temp_string3=sortie_ames%head%station
298retour=concat(temp_string,temp_string3,-999,link,-1,-1)
299
300temp_string3=sortie_ames%head%specie
301retour=concat(temp_string,temp_string3,-999,link,-1,-1)
302
303temp_string3=sortie_ames%head%datemin
304retour=concat(temp_string,temp_string3,-999,link,-1,-1)
305
306temp_string3=sortie_ames%head%datemax
307retour=concat(temp_string,temp_string3,-999,link,-1,-1)
308WRITE(UNIT=14, FMT=*) trim(adjustl(temp_string))
309
310nblcomment=33+3*nbfiles
311
312temp_string="31"
313
314WRITE(UNIT=14, FMT=*) trim(adjustl(temp_string))//" 2110"
315
316temp_string=""
317temp_string3=sortie_ames%head%pi2
318retour=concat(temp_string,temp_string3,-999,link,-1,-1)
319WRITE(UNIT=14, FMT=*) trim(adjustl(temp_string))
320
321temp_string=""
322temp_string3=sortie_ames%head%lab
323retour=concat(temp_string,temp_string3,-999,link,-1,-1)
324WRITE(UNIT=14, FMT=*) trim(adjustl(temp_string))
325
326temp_string=""
327temp_string3=sortie_ames%head%instrument2
328retour=concat(temp_string,temp_string3,-999,link,-1,-1)
329WRITE(UNIT=14, FMT=*) trim(adjustl(temp_string))
330
331WRITE(UNIT=14, FMT=*) "NDACC"
332
333WRITE(UNIT=14, FMT=*) "1 1"
334
335link=""
336temp_string=""
337WRITE(temp_string2,FMT=*) idatemesuremin
338temp_string2=trim(adjustl(temp_string2))
339temp_string3=temp_string2(1:4)
340retour=concat(temp_string,temp_string3,-999,link,-1,-1)
341
342link=" "
343temp_string3=temp_string2(5:6)
344IF (temp_string3(1:1) == "0") THEN
345        temp_string3=temp_string2(6:6)
346ENDIF
347retour=concat(temp_string,temp_string3,-999,link,-1,-1)
348
349link=" "
350temp_string3=temp_string2(7:8)
351IF (temp_string3(1:1) == "0") THEN
352        temp_string3=temp_string2(8:8)
353ENDIF
354retour=concat(temp_string,temp_string3,-999,link,-1,-1)
355
356!DATE CREATION FICHIERS AMES
357call date_and_time (tdate, ttime, tzone, tvalues)
358link=""
359WRITE(temp_string3,FMT=*) tvalues(1:1)
360temp_string3=trim(adjustl(temp_string3))
361retour=concat(temp_string,temp_string3,-999,link,-1,-1)
362
363link=" "
364WRITE(temp_string3,FMT=*) tvalues(2:2)
365temp_string3=trim(adjustl(temp_string3))
366retour=concat(temp_string,temp_string3,-999,link,-1,-1)
367
368WRITE(temp_string3,FMT=*) tvalues(3:3)
369temp_string3=trim(adjustl(temp_string3))
370retour=concat(temp_string,temp_string3,-999,link,-1,-1)
371
372WRITE(UNIT=14, FMT=*) trim(adjustl(temp_string))
373
374WRITE(UNIT=14, FMT=*) "1000. 0.00"
375
376!ouverture fichier description format colonnes
377OPEN(   UNIT=2, &
378        FILE=trim(adjustl(rep_data))//"./data_format.txt", &
379        FORM="formatted", &
380        ACCESS="sequential", &
381        STATUS="old", &
382        ACTION="read", &
383        POSITION="rewind", &
384        IOSTAT=ios3 )
385
386
387READ(2,IOSTAT=ios3, FMT='(A)') line
388
389if (ios3 /= 0 ) then
390        screen="Impossible d ouvrir le fichier de format des colonnes"
391        retour=printl()
392        STOP
393endif
394
395DO WHILE ( ios3 == 0 )
396
397WRITE(UNIT=14, FMT=*) trim(adjustl(line))
398READ(2,IOSTAT=ios3, FMT='(A)') line
399
400END DO
401
402WRITE(UNIT=14, FMT=*) "0"
403WRITE(UNIT=14,FMT=*) "1"
404WRITE(UNIT=14, FMT=*) "LTA"
405
406
407!data
408DO ifile=1,nbfiles
409        temp_string=""
410        temp_string2=""
411        temp_string3=""
412        link=" "
413
414        temp_string3=sortie_ames%grids_ames(ifile)%top(1)
415        retour=concat(temp_string,temp_string3,-999,link,-1,-1)
416
417        temp_string3=sortie_ames%grids_ames(ifile)%top(2)
418        retour=concat(temp_string,temp_string3,-999,link,-1,-1)
419       
420        temp_string3=sortie_ames%grids_ames(ifile)%top(3)
421        retour=concat(temp_string,temp_string3,-999,link,-1,-1)
422
423        temp_string3=sortie_ames%grids_ames(ifile)%top(4)
424        retour=concat(temp_string,temp_string3,-999,link,-1,-1)
425
426        temp_string3=sortie_ames%grids_ames(ifile)%top(5)
427        retour=concat(temp_string,temp_string3,-999,link,-1,-1)
428
429        temp_string3=sortie_ames%grids_ames(ifile)%top(6)
430        retour=concat(temp_string,temp_string3,-999,link,-1,-1)
431
432        temp_string3=sortie_ames%grids_ames(ifile)%top(7)
433        retour=concat(temp_string,temp_string3,-999,link,-1,-1)
434
435        temp_string3=sortie_ames%grids_ames(ifile)%top(8)
436        retour=concat(temp_string,temp_string3,-999,link,-1,-1)
437
438        temp_string3=sortie_ames%grids_ames(ifile)%top(9)
439        retour=concat(temp_string,temp_string3,-999,link,-1,-1)
440
441        temp_string3=sortie_ames%grids_ames(ifile)%top(10)
442        retour=concat(temp_string,temp_string3,-999,link,-1,-1)
443
444        temp_string3=sortie_ames%grids_ames(ifile)%top(11)
445        retour=concat(temp_string,temp_string3,-999,link,-1,-1)
446
447        WRITE(UNIT=14, FMT=*) trim(adjustl(temp_string))
448
449        DO i=1,size(sortie_ames%grids_ames(ifile)%tabMesures(:,1))
450                temp_string=""
451                temp_string2=""
452
453                temp_int=sortie_ames%grids_ames(ifile)%tabMesures(i,1)
454                WRITE(col1, FMT='(I7)') temp_int
455
456                temp_int=sortie_ames%grids_ames(ifile)%tabMesures(i,2)
457                WRITE(col2, FMT='(I7)') temp_int
458
459                temp_int=sortie_ames%grids_ames(ifile)%tabMesures(i,3)
460                WRITE(col3, FMT='(I6)') temp_int
461
462                WRITE(UNIT=14, FMT=*) trim(adjustl(adjustr(col1)))//" "//trim(adjustr(col2))//" "//trim(adjustr(col3))
463
464                !WRITE(UNIT=14, FMT=*) temp_string
465
466
467        END DO
468        DEALLOCATE(sortie_ames%grids_ames(ifile)%tabMesures)
469END DO
470
471CLOSE(UNIT=14)
472
473END PROGRAM treat_files_list
474
Note: See TracBrowser for help on using the repository browser.