source: trunk/LMDZ.GENERIC/libf/bibio/writestd.F @ 773

Last change on this file since 773 was 135, checked in by aslmd, 14 years ago

CHANGEMENT ARBORESCENCE ETAPE 2 -- NON COMPLET

File size: 6.3 KB
Line 
1      SUBROUTINE writestd(champ,icount)
2
3c=======================================================================
4c
5c   Auteurs:   Jan Polcher, Frederic Hourdin
6c   --------
7c
8c   Objet:
9c   ------
10c
11c Subroutine qui ecrit les fichiers dans le format de transfert
12c vers le LMD.
13c format etabli par :
14c   Zhao-Xin Li, Frederic Hourdin, Emmanuelle Cohen-Solal,
15c   Jan Polcher .
16c Il peut etre utilise pour sortire  des evolutions
17c temporelles, des champs 2D (iim,jjm ou jjm,llm) ou des champs 3D.
18c le character # place devant le format determine la fin de la
19c description du champ et permet eventulellement de rajouter
20c des informations (avant le #).
21c le programme de lecture lit , dans la description, les variables
22c qu'il connait et saute apres jusquau #. A partir de la
23c il commence a lire le champ dans le format specifie.
24c
25c-----------------------------------------------------------------------
26c
27c   Interface:
28c   ----------
29c
30c   ARGUMENTS
31c   ---------
32c
33c champ: REAL (icount)
34c        champ contenant les valeurs et de longeur icount
35c icount: INTEGER
36c        nombre d'element dans le champ
37c
38c   COMMON:
39c   -------
40c
41c=======================================================================
42c  INCLUDE '/usr/local/lmdgraph/libio/lmdstd.h'
43c
44c     INTEGER bandmax
45c     PARAMETER(bandmax=24)
46c
47c     COMMON/lmdstdch/gtitre,gunites,gformat,gfichier,glistfich(100),
48c    $                gentete,gdatedep,gdatefin
49c       
50c     CHARACTER*100 gtitre    !du champ
51c     CHARACTER*20  gunites   !unites du champ
52c     CHARACTER*20  gformat   !formats FORTRAN ou zxliN (N=1,2,3) ou ''
53c     CHARACTER*100 gfichier  !nom du fichier contenant le champ
54c     CHARACTER*100 gentete   !nom generique (exemple desript. du RUN)
55c     CHARACTER*8   gdatedep  !date de depart de la moy. ou evol. temp.
56c     CHARACTER*8   gdatefin  !date de fin '' si une seule datefin
57c     CHARACTER*20  glistfich !liste de champs a sortir
58c
59c     COMMON/lmdstdnu/ gminimum,gmaximum,
60c    $                 gdeltajour(bandmax),gdeltapas(bandmax),
61c    $                 gnbetats(bandmax),gnbfich
62c
63c     REAL    gminimum        ! \    min et max
64c     REAL    gmaximum        ! /    du champ
65c     INTEGER gnbfich         ! nombre de fichier a sortir
66c pour les evolutions temporelles:
67c     INTEGER gnbetats        ! nombre d'etats par bande
68c     INTEGER gdeltapas       ! nombre de pas de temps entre 2 sorties
69c     REAL    gdeltajour      ! ecart en jour des sorties sur bandes
70c
71c=======================================================================
72c-----------------------------------------------------------------------
73c   Declarations:
74c   -------------
75
76      IMPLICIT NONE
77#include "lmdstd.h"
78
79c   Arguments:
80c   ----------
81
82      INTEGER icount
83      REAL champ(icount)
84
85c   Local:
86c   ------
87
88      INTEGER i,imin,imax
89      LOGICAL check, writeornot
90      INTEGER lnblnk,ismin,ismax
91      EXTERNAL lnblnk,ismin,ismax, isitor, to36
92
93      INTEGER indexfil
94      COMMON/indexfil/indexfil
95
96c-----------------------------------------------------------------------
97c   verification que le champ est dans la liste predefinie:
98c   -------------------------------------------------------
99
100      check = .FALSE.
101
102      IF (gnbfich .EQ. 0) THEN
103        writeornot = .TRUE.
104      ELSE
105        CALL isitor(gfichier,writeornot,gnbfich, glistfich)
106      ENDIF
107
108      IF (check) THEN
109        WRITE(*,*) 'MYWRITE:: writeornot=',writeornot
110      ENDIF
111
112c-----------------------------------------------------------------------
113      IF (writeornot) THEN
114c-----------------------------------------------------------------------
115
116      imin = ismin(icount,champ,1)
117      imax = ismax(icount,champ,1)
118      IF (check) THEN
119        WRITE(*,*) gentete(1:lnblnk(gentete))
120        WRITE(*,*) gtitre(1:lnblnk(gtitre))
121        WRITE(*,*) gdatedep
122        WRITE(*,*) gdatefin
123        WRITE(*,*) gunites(1:lnblnk(gunites))
124        WRITE(*,*) gdeltapas, gnbetats
125        WRITE(*,*) gdeltajour
126        WRITE(*,*) champ(imin),champ(imax)
127        WRITE(*,*) gformat(1:lnblnk(gformat))
128        WRITE(*,*) icount
129      ENDIF
130      WRITE(*,*) gtitre(1:lnblnk(gtitre)),'min,max:',
131     &  champ(imin),champ(imax),'  ',gunites(1:lnblnk(gunites))
132     
133c-----------------------------------------------------------------------
134c   creation eventuelle d'un nom pour le fichier d'ecriture du champ:
135c   -----------------------------------------------------------------
136
137      IF(lnblnk(gfichier).LT.1.OR.lnblnk(gfichier).GE.100) THEN
138         gfichier(1:5)='champ'
139         IF(indexfil.LT.1) indexfil=49
140         gfichier(6:6)=char(indexfil)
141         indexfil=indexfil+1
142         PRINT*,'nom du fichier  ',gfichier
143      ENDIF
144
145c-----------------------------------------------------------------------
146c   ecriture sur le fichier de sorties:
147c   -----------------------------------
148
149      OPEN (unit=55, file=gfichier(1:lnblnk(gfichier)))
150      WRITE(55,'(a)') gentete(1:lnblnk(gentete))
151      WRITE(55,'(a)') gtitre(1:lnblnk(gtitre))
152      WRITE(55,'(a)') gdatedep
153      WRITE(55,'(a)') gdatefin
154      WRITE(55,'(a)') gunites(1:lnblnk(gunites))
155      WRITE(55,*) gdeltapas, gnbetats
156      WRITE(55,*) gdeltajour
157      WRITE(55,*) champ(imin),champ(imax)
158      WRITE(55,'(a)') '#'//gformat(1:lnblnk(gformat))
159      WRITE(55,*) icount
160
161      IF (check) THEN
162        WRITE(*,'('//gformat(1:lnblnk(gformat))//')') champ(1)
163      ENDIF
164
165      IF (lnblnk(gformat).LE.1.OR.lnblnk(gformat).GE.20) THEN
166         DO 2230 i=1,icount
167            WRITE(55,*) champ(i)
1682230     CONTINUE
169      ELSE
170         IF (gformat(1:lnblnk(gformat)) .EQ. 'zxli1') THEN
171            CALL to36 (champ,icount,champ(imin),champ(imax),55, 1)
172         ELSE
173            IF (gformat(1:lnblnk(gformat)) .EQ. 'zxli2') THEN
174               CALL to36(champ,icount,champ(imin),champ(imax),55,2)
175            ELSE
176               IF (gformat(1:lnblnk(gformat)) .EQ. 'zxli3') THEN
177                  CALL to36(champ,icount,champ(imin),champ(imax),55,3)
178               ELSE
179                  WRITE(55,'('//gformat(1:lnblnk(gformat))//')')
180     &            (champ(i),i=1,icount)
181               ENDIF
182            ENDIF
183         ENDIF
184      ENDIF
185
186      CLOSE (unit=55)
187
188      gfichier=' '
189
190c-----------------------------------------------------------------------
191c   si on ecrit pas le champ (writeornot.EQ..f.):
192c   ---------------------------------------------
193
194      ELSE
195        WRITE(*,*) 'FILE    ',gfichier,'WAS NOT WRITEN'
196      ENDIF
197     
198      RETURN
199      END
200
Note: See TracBrowser for help on using the repository browser.