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