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

Last change on this file since 1524 was 1126, checked in by slebonnois, 11 years ago

SL: update of Titan photochemical module to include computation of chemistry up to 1300 km

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