source: trunk/LMDZ.PLUTO.old/libf/phypluto/writeg1d.F @ 3436

Last change on this file since 3436 was 3175, checked in by emillour, 11 months ago

Pluto PCM:
Add the old Pluto LMDZ for reference (required prior step to making
an LMDZ.PLUTO using the same framework as the other physics packages).
TB+EM

File size: 6.8 KB
Line 
1      SUBROUTINE writeg1d(ngrid,nx,x,nom,titre)
2      IMPLICIT NONE
3
4c.......................................................................
5c
6c  ecriture de x pour GRADS-1D
7c
8c  in :
9c         * ngrid      ---> pour controler que l'on est bien en 1D
10c         * nx         ---> taille du vecteur a stocker
11c                             "1" pour une variable de surface
12c                             "nlayer" pour une variable de centre de couche
13c                             "nlayer+1" pour une variable d'interface
14c         * x          ---> variable a stocker
15c         * nom        ---> nom "pour grads"
16c         * titre      ---> titre "pour grads"
17c
18c.......................................................................
19c
20#include "comg1d.h"
21
22c
23c.......................................................................
24c  declaration des arguments
25c
26      INTEGER ngrid,nx,i
27      REAL*4 xr4(1000)
28      REAL x(nx)
29      CHARACTER*(*) nom,titre
30c
31c  declaration des arguments
32c.......................................................................
33c  declaration des variables locales
34c
35      INTEGER ilayer,ivar
36      LOGICAL test
37c
38c  declaration des variables locales
39c.......................................................................
40c  controle 1D
41c
42c     print*,'ngrid=',ngrid
43      IF (ngrid.NE.1) return
44c
45c  controle 1D
46c.......................................................................
47c  copy => force en reel 4 pour l'ecriture dans grads1d.dat
48
49      do i=1,nx
50        xr4(i) = x(i)
51      enddo
52
53c  copy => force en reel 4 pour l'ecriture dans grads1d.dat
54c.......................................................................
55c  ouverture du fichier au premier appel
56
57
58      g1d_nomfich='g1d.dat'
59
60      IF (g1d_premier) THEN
61        OPEN (g1d_unitfich,FILE=g1d_nomfich
62     &       ,FORM='unformatted',ACCESS='direct',RECL=4)
63        g1d_irec=0
64        g1d_nvar=0
65        g1d_premier=.false.
66      ENDIF
67
68c  ouverture du fichier au premier appel
69c.......................................................................
70c  pour l'ecriture du fichier ctl
71
72      test=.true.
73      DO ivar=1,g1d_nvar
74        IF (nom.EQ.g1d_nomvar(ivar)) test=.false.
75        IF (nx .GT. 1000) then
76          print*,'ERROR:  nx > 1000 dans writeg1d.F'
77          print*,'Changer la dimension de xr4'
78          call exit(1)
79        ENDIF
80      ENDDO
81      IF (test) THEN
82        g1d_nvar=g1d_nvar+1
83        g1d_nomvar(g1d_nvar)=nom
84        g1d_titrevar(g1d_nvar)=titre
85        IF (nx.EQ.1) THEN
86           g1d_dimvar(g1d_nvar)=0
87        ELSEIF (nx.EQ.g1d_nlayer) THEN
88           g1d_dimvar(g1d_nvar)=g1d_nlayer
89        ELSEIF (nx.EQ.g1d_nlayer+1) THEN
90           g1d_dimvar(g1d_nvar)=g1d_nlayer+1
91        ELSE
92           PRINT *,'._. probleme de dimension dans GRADS-1D ._.'
93           print*,'NX = ',nx
94           print*,'g1d_nlayer = ',g1d_nlayer
95        ENDIF
96      ENDIF
97c
98c  pour l'ecriture du fichier ctl
99c.......................................................................
100c  ecriture
101c
102     
103c      if (mod((it-1),ecrig1d).eq.0) then
104c      IF (nx.EQ.1) THEN
105c        g1d_irec=g1d_irec+1
106c        WRITE(g1d_unitfich,REC=g1d_irec) xr4(1)
107c      ELSE
108c        DO ilayer=1,g1d_nlayer
109c          g1d_irec=g1d_irec+1
110c          WRITE(g1d_unitfich,REC=g1d_irec) xr4(ilayer)
111c        ENDDO
112c      ENDIF
113c      endif
114c
115c  ecriture
116c.......................................................................
117c
11810001 CONTINUE
119c
120c.......................................................................
121c
122      RETURN
123      END
124
125
126
127
128
129c *********************************************************************
130c *********************************************************************
131
132      SUBROUTINE endg1d(ngrid,nlayer,zlayer,ndt)
133      IMPLICIT NONE
134c.......................................................................
135c
136c  ecriture du fichier de controle pour GRADS-1D
137c
138c  in :
139c         * ngrid      ---> pour controler que l'on est bien en 1D
140c         * nlayer     ---> nombre de couches
141c         * zlayer     ---> altitude au centre de chaque couche (km)
142c         * ndt        ---> nombre de pas de temps
143c
144c.......................................................................
145c
146#include "comg1d.h"
147#include "comcstfi.h"
148
149
150c
151c.......................................................................
152c  declaration des arguments
153c
154      INTEGER ngrid,nlayer
155      REAL zlayer(nlayer)
156      INTEGER ndt
157c
158c  declaration des arguments
159c.......................................................................
160c  declaration des variables locales
161c
162      INTEGER ivar,ilayer
163c
164
165
166!      integer saveG1D
167
168c  declaration des variables locales
169c.......................................................................
170c  contole 1D
171c
172      IF (ngrid.NE.1) GOTO 10001
173c
174c  contole 1D
175c.......................................................................
176c
177      IF (nlayer.ne.g1d_nlayer)
178     &PRINT *,'._. probleme de dimension dans GRADS-1D (endg1d.F) '
179c
180c.......................................................................
181c
182      CLOSE (g1d_unitfich)
183c
184c.......................................................................
185
186
187      OPEN (g1d_unitctl,FILE=g1d_nomctl,FORM='formatted',RECL=4*100)
188      WRITE (g1d_unitctl,'(a4,2x,a1,a20)') 'DSET','^',g1d_nomfich
189      WRITE (g1d_unitctl,'(a5,2x,a20)') 'UNDEF ','1.E+30'
190      WRITE (g1d_unitctl,'(a11)') 'FORMAT YREV'
191      WRITE (g1d_unitctl,'(a5,2x,a30)') 'TITLE ','champs 1D'
192      WRITE (g1d_unitctl,'(a5,i4,a20)') 'XDEF ',1,' LINEAR 0 1'
193      WRITE (g1d_unitctl,'(a5,i4,a20)') 'YDEF ',1,' LINEAR 0 1'
194      WRITE (g1d_unitctl,'(a5,i4,a20)') 'ZDEF ',g1d_nlayer,' LEVELS'
195      WRITE (g1d_unitctl,'(5(1x,f13.5))')
196     &      (zlayer(ilayer),ilayer=1,g1d_nlayer)
197
198c     Writing true timestep in g1d.ctl (in planet "minutes"= sol/(60*24)
199!      ivar =min( max(int(1440.*dtphys/daysec +0.5),1) , 99)   
200!      WRITE (g1d_unitctl,'(a4,2x,i10,a19,i2,a2)')
201!     &      'TDEF ',ndt,' LINEAR 01JAN2000 ', ivar,'MN '
202
203!      ivar =min( max(int(1440.*dtphys*saveG1D/daysec +0.5),1) , 99)
204!      ! not sure ivar is right, but it doesnt matter
205!      WRITE (g1d_unitctl,'(a4,2x,i10,a19,i2,a2)')
206!     &      'TDEF ',ndt/saveG1D,' LINEAR 01JAN2000 ', ivar,'MN '
207
208c     Writing true timestep in g1d.ctl (in planet "minutes"= sol/(60*24)
209c      ivar =min( max(int(1440.*dtphys*ecrig1d/daysec +0.5),1) , 99)   
210c      WRITE (g1d_unitctl2,'(a4,2x,i10,a19,i2,a2)')
211c     &      'TDEF ',int(ndt/ecrig1d),' LINEAR 01JAN2000 ', ivar,'MN '
212
213      WRITE (g1d_unitctl,'(a5,i5)') 'VARS ',g1d_nvar
214      DO ivar=1,g1d_nvar
215      WRITE (g1d_unitctl,'(a9,3x,i4,i3,1x,a39)')
216     &       g1d_nomvar(ivar),g1d_dimvar(ivar),99,g1d_titrevar(ivar)
217      ENDDO
218      WRITE (g1d_unitctl,'(a7)') 'ENDVARS'
219      CLOSE (g1d_unitctl)
220c
221c.......................................................................
222c
22310001 CONTINUE
224c
225c.......................................................................
226c
227      RETURN
228      END
Note: See TracBrowser for help on using the repository browser.