source: trunk/LMDZ.PLUTO.old/libf/phypluto/profile.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: 7.2 KB
Line 
1      SUBROUTINE profile(nlev,zkm,temp)
2! to use  'getin'
3      USE ioipsl_getincom
4      IMPLICIT NONE
5c=======================================================================
6c     Subroutine utilisee dans le modele 1-D  "testphys1d"
7c     pour l'initialisation du profil atmospherique
8c=======================================================================
9c
10c   differents profils d'atmospheres. T=f(z)
11c   entree:
12c     nlev    nombre de niveaux
13c     zkm     alititudes en km
14c     ichoice choix de l'atmosphere:
15c             1 Temperature constante
16c             2 profil Savidjari
17c             3 Lindner (profil polaire)
18c             4 Inversion pour Francois
19c             5 Seiff (moyen)
20c             6 T constante + perturbation gauss (level) (christophe 10/98)
21c             7 T constante + perturbation gauss   (km)  (christophe 10/98)
22c             8 Lecture du profile dans un fichier ASCII (profile)
23c     tref    temperature de reference
24c     isin    ajout d'une perturbation (isin=1)
25c     pic     pic perturbation gauss pour ichoice = 6 ou 7
26c     largeur largeur de la perturbation gauss pour ichoice = 6 ou 7
27c     hauteur hauteur de la perturbation gauss pour ichoice = 6 ou 7
28c
29c   sortie:
30c     temp    temperatures en K
31c     
32c=======================================================================
33c-----------------------------------------------------------------------
34c   declarations:
35c   -------------
36
37c   arguments:
38c   ----------
39
40       INTEGER nlev, unit
41       REAL zkm(nlev),temp(nlev)
42
43c   local:
44c   ------
45
46      INTEGER il,ichoice,nseiff,iseiff,isin,iter
47      REAL pi
48      PARAMETER(nseiff=37)
49      REAL tref,t1,t2,t3,ww
50      REAL tseiff(nseiff)
51      DATA tseiff/214.,213.8,213.4,212.4,209.3,205.,201.4,197.8,
52     $           194.6,191.4,188.2,185.2,182.5,180.,177.5,175,
53     $           172.5,170.,167.5,164.8,162.4,160.,158.,156.,
54     $           154.1,152.2,150.3,148.7,147.2,145.7,144.2,143.,
55     $           142.,141.,140,139.5,139./
56      REAL pic,largeur
57      REAL hauteur,tmp
58      REAL phitop,ttop
59      REAL tsurf,r,rcp,g,s(nlev)
60
61c-----------------------------------------------------------------------
62c   read input profile type:
63c--------------------------
64
65      ichoice=1 ! default value for ichoice
66      call getin("ichoice",ichoice)
67      tref=200 ! default value for tref
68      call getin("tref",tref)
69      isin=0 ! default value for isin (=0 means no perturbation)
70      call getin("isin",isin)
71      pic=26.522 ! default value for pic
72      call getin("pic",pic)
73      largeur=10 ! default value for largeur
74      call getin("largeur",largeur)
75      hauteur=30 ! default value for hauteur
76      call getin("hauteur",hauteur)
77
78c-----------------------------------------------------------------------
79c   ichoice=1 temperature constante:
80c   --------------------------------
81
82      IF(ichoice.EQ.1) THEN
83         DO il=1,nlev
84            temp(il)=tref
85         ENDDO
86
87c-----------------------------------------------------------------------
88c   ichoice=2 savidjari:
89c   --------------------
90
91      ELSE IF(ichoice.EQ.2) THEN
92ccc         DO il=1,7
93cc            temp(il)=AMAX1(219.-2.5*zkm(il),140.)
94c pour pluton on prend en compte un profil lineaire qui va de 40 K au sol à 100 K à 50km
95ccc            temp(il)=38       
96cc            temp(il)=6*zkm(il)+40
97ccc         ENDDO
98ccc         DO il=8,nlev
99ccc            temp(il)=100
100ccc         ENDDO
101
102
103         temp(1)=44.
104         temp(2)=44.
105         temp(3)=44.
106         temp(4)=44.
107         temp(5)=44.
108         temp(6)=44.
109         temp(7)=44.
110         temp(8)=44.
111         temp(9)=44.
112         temp(10)=44.
113         temp(11)=44.
114         temp(12)=44.
115         temp(13)=44.
116         temp(14)=44.
117         temp(15)=44.
118         temp(16)=44.
119         temp(17)=44.
120         temp(18)=45.85745
121         temp(19)=56.81386
122         temp(20)=71.71157
123         temp(21)=79.29989
124         temp(22)=82.10749
125         temp(23)=83.93003
126         temp(24)=85.58517
127         temp(25)=85.60072
128c-----------------------------------------------------------------------
129c   ichoice=3 Lindner:
130c   ------------------
131
132      ELSE IF(ichoice.EQ.3) THEN
133         DO il=1,nlev
134            IF(zkm(il).LT.2.5) THEN
135               temp(il)=150.+30.*zkm(il)/2.5
136            ELSE IF(zkm(il).LT.5.) THEN
137               temp(il)=180.
138            ELSE
139               temp(il)=AMAX1(180.-2.*(zkm(il)-5.),130.)
140            ENDIF
141         ENDDO
142
143c-----------------------------------------------------------------------
144c   ichoice=4 Inversion pour Francois:
145c   ------------------
146
147      ELSE IF(ichoice.EQ.4) THEN
148         DO il=1,nlev
149            IF(zkm(il).LT.20.) THEN
150               temp(il)=135.
151            ELSE
152               temp(il)=AMIN1(135.+5.*(zkm(il)-20.),200.)
153            ENDIF
154         ENDDO
155
156
157c-----------------------------------------------------------------------
158c   ichoice=5 Seiff:
159c   ----------------
160
161      ELSE IF(ichoice.EQ.5) THEN
162         DO il=1,nlev
163            iseiff=INT(zkm(il)/2.)+1
164            IF(iseiff.LT.nseiff-1) THEN
165               temp(il)=tseiff(iseiff)+(zkm(il)-2.*(iseiff-1))*
166     $         (tseiff(iseiff+1)-tseiff(iseiff))/2.
167            ELSE
168               temp(il)=tseiff(nseiff)
169            ENDIF
170         ENDDO
171c IF(ichoice.EQ.6) THEN
172c           DO iter=1,6
173c           t2=temp(1)
174c           t3=temp(2)
175c           DO il=2,nlev-1
176c              t1=t2
177c              t2=t3
178c              t3=temp(il+1)
179c              ww=tanh(zkm(il)/20.)
180c              ww=ww*ww*ww
181c              temp(il)=t2+ww*.5*(t1-2.*t2+t3)
182c           ENDDO
183c           ENDDO
184c        ENDIF
185
186c-----------------------------------------------------------------------
187c   ichoice=6
188c   ---------
189
190      ELSE IF(ichoice.EQ.6) THEN
191      DO il=1,nlev
192        tmp=il-pic
193        temp(il)=tref + hauteur*exp(-tmp*tmp/largeur/largeur)
194      ENDDO
195
196
197c-----------------------------------------------------------------------
198c   ichoice=7
199c   ---------
200
201      ELSE IF(ichoice.EQ.7) THEN
202      DO il=1,nlev
203        tmp=zkm(il)-pic
204        temp(il)=tref + hauteur*exp(-tmp*tmp*4/largeur/largeur)
205      ENDDO
206
207c-----------------------------------------------------------------------
208c   ichoice=8
209c   ---------
210
211      ELSE IF(ichoice.GE.8) THEN
212      OPEN(11,file='profile',status='old',form='formatted',err=101)
213      DO il=1,nlev
214        READ (11,*) temp(il)
215      ENDDO
216
217      GOTO 201
218101   STOP'fichier profile inexistant'
219201   CONTINUE
220      CLOSE(10)
221
222c-----------------------------------------------------------------------
223
224      ENDIF
225
226c-----------------------------------------------------------------------
227c   rajout eventuel d'une perturbation:
228c   -----------------------------------
229
230      IF(isin.EQ.1) THEN
231         pi=2.*ASIN(1.)
232         DO il=1,nlev
233c       if (nlev.EQ.501) then
234c         if (zkm(il).LE.70.5) then
235c       temp(il)=temp(il)+(1.-1000./(1000+zkm(il)*zkm(il)))*(
236c    s      6.*SIN(zkm(il)*pi/6.)+9.*SIN(zkm(il)*pi/10.3) )
237c         endif
238c       else
239        temp(il)=temp(il)+(1.-1000./(1000+zkm(il)*zkm(il)))*(
240     s      6.*SIN(zkm(il)*pi/6.)+9.*SIN(zkm(il)*pi/10.3) )
241c       endif
242         ENDDO
243      ENDIF
244
245
246c-----------------------------------------------------------------------
247c   Ecriture du profil de temperature dans un fichier profile.out
248c   -------------------------------------------------------------
249
250
251      OPEN(12,file='profile.out',form='formatted')
252          DO il=1,nlev
253            write(12,*) temp(il)
254          ENDDO
255      CLOSE(12)
256
257      RETURN
258      END
Note: See TracBrowser for help on using the repository browser.