source: trunk/LMDZ.TITAN/libf/phytitan/profile.F @ 893

Last change on this file since 893 was 887, checked in by slebonnois, 12 years ago

SL: add rcm1d tool in Venus and Titan physics to run the code in 1D, and associated small modifications

File size: 5.7 KB
Line 
1      SUBROUTINE profile(unit,nlev,dzst,temp)
2      IMPLICIT NONE
3c=======================================================================
4c     Subroutine utilisee dans le modele 1-D  "rcm1d"
5c     pour l'initialisation du profil atmospherique
6c=======================================================================
7c
8c   VERSION VENUS
9c
10c   differents profils d'atmospheres. T=f(z)
11c   entree:
12c     unit    unite de lecture de "testphys1d.def"
13c     nlev    nombre de niveaux (nlev=llm+1, surf + couches 1 a llm)
14c     dzst    dz/T (avec dz = epaisseur de la couche en m)
15c     ichoice choix de l'atmosphere:
16c             1 Temperature constante
17c             2 profil Huygens lisse
18c             3
19c             4
20c             5
21c             6 T constante + perturbation gauss (level) (christophe 10/98)
22c             7 T constante + perturbation gauss   (km)  (christophe 10/98)
23c             8 Lecture du profile dans un fichier ASCII (profile)
24c     tref    temperature de reference
25c     isin    ajout d'une perturbation (isin=1)
26c     pic     pic perturbation gauss pour ichoice = 6 ou 7
27c     largeur largeur de la perturbation gauss pour ichoice = 6 ou 7
28c     hauteur hauteur de la perturbation gauss pour ichoice = 6 ou 7
29c
30c   sortie:
31c     temp    temperatures en K
32c     
33c=======================================================================
34c-----------------------------------------------------------------------
35c   declarations:
36c   -------------
37
38c   arguments:
39c   ----------
40
41       INTEGER nlev, unit
42       REAL dzst(nlev),temp(nlev)
43
44c   local:
45c   ------
46
47      INTEGER il,ichoice,isin,iter
48      REAL pi
49      REAL tref,t1,t2,t3,ww
50      REAL pic,largeur
51      REAL hauteur,tmp
52      REAL zkm(nlev)    ! altitude en km
53
54      isin = 0
55
56c-----------------------------------------------------------------------
57c   choix du profil:
58c   ----------------
59
60c la lecture se fait dans le rcm1d.def, ouvert par rcm1d.F
61      READ(unit,*)
62      READ(unit,*)
63      READ(unit,*)
64      READ(unit,*) ichoice
65      READ(unit,*) tref
66      READ(unit,*) isin
67      READ(unit,*) pic
68      READ(unit,*) largeur
69      READ(unit,*) hauteur
70
71c-----------------------------------------------------------------------
72c   ichoice=1 temperature constante:
73c   --------------------------------
74
75      IF(ichoice.EQ.1) THEN
76         temp(1) = tref
77         zkm(1)  = 0.0
78         DO il=2,nlev
79            temp(il)= tref
80            zkm(il) = zkm(il-1)+temp(il)*dzst(il)/1000.
81         ENDDO
82
83c-----------------------------------------------------------------------
84c   ichoice=2 Huygens lisse:
85c   ------------------------
86
87      ELSE IF(ichoice.EQ.2) THEN
88       print*,"Profil T a faire..."
89       stop
90c        temp(1) = 735.
91c        zkm(1)  = 0.0
92c        DO il=2,nlev
93c           zkm(il) = zkm(il-1)+temp(il-1)*dzst(il)/1000. ! approx avec T(l-1)
94c           if(zkm(il).lt.60.) then
95c             temp(il)=735.-7.95*zkm(il)
96c           else
97c             temp(il)=AMAX1(258.-3.*(zkm(il)-60.),168.)
98c           endif
99c           zkm(il) = zkm(il-1)+(temp(il-1)+temp(il))/2.*dzst(il)/1000.
100c        ENDDO
101
102c-----------------------------------------------------------------------
103c   ichoice=3
104c   ----------------------------
105
106      ELSE IF(ichoice.EQ.3) THEN
107       print*,"Profil T a faire..."
108       stop
109
110c-----------------------------------------------------------------------
111c   ichoice=4 :
112c   ------------------
113
114      ELSE IF(ichoice.EQ.4) THEN
115         print*,"Cas non defini..."
116         print*,"Stop dans profile.F"
117         STOP
118
119c-----------------------------------------------------------------------
120c   ichoice=5 :
121c   ----------------
122
123      ELSE IF(ichoice.EQ.5) THEN
124         print*,"Cas non defini..."
125         print*,"Stop dans profile.F"
126         STOP
127
128c-----------------------------------------------------------------------
129c   ichoice=6
130c   ---------
131
132      ELSE IF(ichoice.EQ.6) THEN
133      temp(1) = tref
134      zkm(1)  = 0.0
135      DO il=2,nlev
136        tmp=il-pic
137        temp(il)= tref + hauteur*exp(-tmp*tmp/largeur/largeur)
138        zkm(il) = zkm(il-1)+temp(il)*dzst(il)/1000.
139      ENDDO
140
141
142c-----------------------------------------------------------------------
143c   ichoice=7
144c   ---------
145
146      ELSE IF(ichoice.EQ.7) THEN
147      temp(1) = tref
148      zkm(1)  = 0.0
149      DO il=2,nlev
150        zkm(il) = zkm(il-1)+tref*dzst(il)/1000. ! approx
151        tmp=zkm(il)-pic
152        temp(il)= tref + hauteur*exp(-tmp*tmp*4/largeur/largeur)
153        zkm(il) = zkm(il-1)+(temp(il-1)+temp(il))/2.*dzst(il)/1000.
154      ENDDO
155
156c-----------------------------------------------------------------------
157c   ichoice=8
158c   ---------
159
160      ELSE IF(ichoice.GE.8) THEN
161      OPEN(11,file='profile',status='old',form='formatted',err=101)
162      DO il=1,nlev
163        READ (11,*) temp(il)
164      ENDDO
165      zkm(1) = 0.0
166      DO il=2,nlev
167        zkm(il) = zkm(il-1)+(temp(il-1)+temp(il))/2.*dzst(il)/1000.
168      ENDDO
169
170      GOTO 201
171101   STOP'fichier profile inexistant'
172201   CONTINUE
173      CLOSE(10)
174
175c-----------------------------------------------------------------------
176
177      ENDIF
178
179c-----------------------------------------------------------------------
180c   rajout eventuel d'une perturbation:
181c   -----------------------------------
182
183      IF(isin.EQ.1) THEN
184         pi=2.*ASIN(1.)
185         DO il=1,nlev
186        temp(il)=temp(il)+(1.-1000./(1000+zkm(il)*zkm(il)))*(
187     s      6.*SIN(zkm(il)*pi/6.)+9.*SIN(zkm(il)*pi/10.3) )
188         ENDDO
189      ENDIF
190
191
192c-----------------------------------------------------------------------
193c   Ecriture du profil de temperature dans un fichier profile.out
194c   -------------------------------------------------------------
195
196
197c     OPEN(12,file='profile.out')
198c         DO il=1,nlev
199c            write(12,*) temp(il)
200c           write(12,*) temp(il),zkm(il)
201c         ENDDO
202c     CLOSE(12)
203
204      RETURN
205      END
Note: See TracBrowser for help on using the repository browser.