source: trunk/LMDZ.VENUS/libf/phyvenus/writeg1d.F @ 894

Last change on this file since 894 was 888, checked in by slebonnois, 12 years ago

SL: small modifications to the tools, to Venus default .def files and to outputs (including forgotten modifications linked to the 1D); + bug corrections in phytitan

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