source: trunk/libf/dyn3dpar/iniacademic.F @ 60

Last change on this file since 60 was 52, checked in by aslmd, 15 years ago

chantier principal du commit
--- version LMDZ5 qui fonctionne pour tests geantes
--- prochaine etape, tests sur GNOME

M libf/dyn3dpar/comconst.h
M libf/dyn3dpar/conf_planete.F90
ajout du flux de chaleur intrinseque: ihf
[par defaut il est nul]

M libf/dyn3dpar/gcm.F
changements cosmetiques
[pour diff plus efficace avec version non par]

M libf/dyn3dpar/iniacademic.F
possibilites de variations latitudinales
de temperature plus originales
[seulement pour planet_type.eq."giant"]

M libf/dyn3dpar/leapfrog_p.F

  1. ajout d'une tendance causee par le flux de chaleur intrinseque

(seulement prise en compte si planet_type.eq."giant")

  1. correction bugs problematiques a la compilation et au run

--> probleme dans les boucles (l'indice etait llm et non l)
--> ajout de SAVE pour les variables paralleles
--> correction des declarations de variables manquantes

M libf/dyn3dpar/calfis_p.F
correction d'une deuxieme parenthese manquante sur ALLOCATE(zteta(klon,llm))

M libf/phylmd/regr_lat_time_climoz_m.F90
erreur a la compilation avec FCM... il s'agit d'une routine terrestre
il y a visiblement un probleme avec o3_in
en attendant, les lignes sont commentees avec !AS

A deftanks/giant 8 fichiers
ajout de fichiers de configuration typiques pour les geantes gazeuses
[experimental pour le moment... on est loin de jupiter]

--> comparaisons entre un run ancien [avec LMDZ5-dev sur SVN ipsl sans cp var]
et run avec version sur ce SVN planeto donne des resultats similaires

pratique

A ioipsl
A ioipsl/compile_ioipsl.bash
A ioipsl/util 16 fichiers
script et utilitaire pour compiler IOIPSL de facon independante
il suffit d'executer ./compile_ioipsl.bash

M arch/arch-AMD64_CICLAD.path
si IOIPSL a ete compile avec la methode precedente, les bons
PATH sont definis dans ce fichier [le NETCDF est aussi OK]

M 000-README-svn
mise a jour options "svn status"

M mars/libf/phymars/meso_callkeys.h
mise a jour mineure du fichier
[ecri_phys etait defini mais pas dans la liste]

File size: 9.1 KB
Line 
1!
2! $Id: iniacademic.F 1446 2010-10-22 09:27:25Z emillour $
3!
4c
5c
6      SUBROUTINE iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
7
8      USE filtreg_mod
9      USE infotrac, ONLY : nqtot
10      USE control_mod, ONLY: day_step,planet_type
11#ifdef CPP_IOIPSL
12      USE IOIPSL
13#else
14! if not using IOIPSL, we still need to use (a local version of) getin
15      USE ioipsl_getincom
16#endif
17      USE Write_Field
18 
19
20c%W%    %G%
21c=======================================================================
22c
23c   Author:    Frederic Hourdin      original: 15/01/93
24c   -------
25c
26c   Subject:
27c   ------
28c
29c   Method:
30c   --------
31c
32c   Interface:
33c   ----------
34c
35c      Input:
36c      ------
37c
38c      Output:
39c      -------
40c
41c=======================================================================
42      IMPLICIT NONE
43c-----------------------------------------------------------------------
44c   Declararations:
45c   ---------------
46
47#include "dimensions.h"
48#include "paramet.h"
49#include "comvert.h"
50#include "comconst.h"
51#include "comgeom.h"
52#include "academic.h"
53#include "ener.h"
54#include "temps.h"
55#include "iniprint.h"
56#include "logic.h"
57
58c   Arguments:
59c   ----------
60
61      real time_0
62
63c   variables dynamiques
64      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
65      REAL teta(ip1jmp1,llm)                 ! temperature potentielle
66      REAL q(ip1jmp1,llm,nqtot)               ! champs advectes
67      REAL ps(ip1jmp1)                       ! pression  au sol
68      REAL masse(ip1jmp1,llm)                ! masse d'air
69      REAL phis(ip1jmp1)                     ! geopotentiel au sol
70
71c   Local:
72c   ------
73
74      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
75      REAL pks(ip1jmp1)                      ! exner au  sol
76      REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
77      REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
78      REAL phi(ip1jmp1,llm)                  ! geopotentiel
79      REAL ddsin,tetastrat,zsig,tetapv,w_pv  ! variables auxiliaires
80      real tetajl(jjp1,llm)
81      INTEGER i,j,l,lsup,ij
82
83      REAL teta0,ttp,delt_y,delt_z,eps ! Constantes pour profil de T
84      REAL k_f,k_c_a,k_c_s         ! Constantes de rappel
85      LOGICAL ok_geost             ! Initialisation vent geost. ou nul
86      LOGICAL ok_pv                ! Polar Vortex
87      REAL phi_pv,dphi_pv,gam_pv   ! Constantes pour polar vortex
88     
89      real zz,ran1
90      integer idum
91
92      REAL alpha(ip1jmp1,llm),beta(ip1jmp1,llm),zdtvr
93
94c-----------------------------------------------------------------------
95! 1. Initializations for Earth-like case
96! --------------------------------------
97c
98
99        print *, 'This is iniacademic'
100
101        ! initialize planet radius, rotation rate,...
102        call conf_planete
103
104        time_0=0.
105        day_ref=1
106        annee_ref=0
107
108        im         = iim
109        jm         = jjm
110        day_ini    = 1
111        dtvr    = daysec/REAL(day_step)
112        zdtvr=dtvr
113        etot0      = 0.
114        ptot0      = 0.
115        ztot0      = 0.
116        stot0      = 0.
117        ang0       = 0.
118
119        if (llm.eq.1) then
120          ! specific initializations for the shallow water case
121          kappa=1
122        endif
123       
124        CALL iniconst
125        CALL inigeom
126        CALL inifilr
127
128        if (llm.eq.1) then
129          ! initialize fields for the shallow water case, if required
130          if (.not.read_start) then
131            phis(:)=0.
132            q(:,:,:)=0
133            CALL sw_case_williamson91_6(vcov,ucov,teta,masse,ps)
134          endif
135        endif
136
137        if (iflag_phys.eq.2) then
138          ! initializations for the academic case
139         
140!         if (planet_type=="earth") then
141
142          ! 1. local parameters
143          ! by convention, winter is in the southern hemisphere
144          ! Geostrophic wind or no wind?
145          ok_geost=.TRUE.
146          CALL getin('ok_geost',ok_geost)
147          ! Constants for Newtonian relaxation and friction
148          k_f=1.                !friction
149          CALL getin('k_j',k_f)
150          k_f=1./(daysec*k_f)
151          k_c_s=4.  !cooling surface
152          CALL getin('k_c_s',k_c_s)
153          k_c_s=1./(daysec*k_c_s)
154          k_c_a=40. !cooling free atm
155          CALL getin('k_c_a',k_c_a)
156          k_c_a=1./(daysec*k_c_a)
157          ! Constants for Teta equilibrium profile
158          teta0=315.     ! mean Teta (S.H. 315K)
159          CALL getin('teta0',teta0)
160          print *, 'iniacademic - teta0 ', teta0
161          print *, 'iniacademic - rad ', rad
162          ttp=200.       ! Tropopause temperature (S.H. 200K)
163          CALL getin('ttp',ttp)
164          eps=0.         ! Deviation to N-S symmetry(~0-20K)
165          CALL getin('eps',eps)
166          delt_y=60.     ! Merid Temp. Gradient (S.H. 60K)
167          CALL getin('delt_y',delt_y)
168          delt_z=10.     ! Vertical Gradient (S.H. 10K)
169          CALL getin('delt_z',delt_z)
170          ! Polar vortex
171          ok_pv=.false.
172          CALL getin('ok_pv',ok_pv)
173          phi_pv=-50.            ! Latitude of edge of vortex
174          CALL getin('phi_pv',phi_pv)
175          phi_pv=phi_pv*pi/180.
176          dphi_pv=5.             ! Width of the edge
177          CALL getin('dphi_pv',dphi_pv)
178          dphi_pv=dphi_pv*pi/180.
179          gam_pv=4.              ! -dT/dz vortex (in K/km)
180          CALL getin('gam_pv',gam_pv)
181         
182          ! 2. Initialize fields towards which to relax
183          ! Friction
184          knewt_g=k_c_a
185          DO l=1,llm
186           zsig=presnivs(l)/preff
187           knewt_t(l)=(k_c_s-k_c_a)*MAX(0.,(zsig-0.7)/0.3)
188           kfrict(l)=k_f*MAX(0.,(zsig-0.7)/0.3)
189          ENDDO
190          DO j=1,jjp1
191            clat4((j-1)*iip1+1:j*iip1)=cos(rlatu(j))**4
192          ENDDO
193         
194          ! Potential temperature
195          DO l=1,llm
196           zsig=presnivs(l)/preff
197           tetastrat=ttp*zsig**(-kappa)
198           tetapv=tetastrat
199           IF ((ok_pv).AND.(zsig.LT.0.1)) THEN
200               tetapv=tetastrat*(zsig*10.)**(kappa*cpp*gam_pv/1000./g)
201           ENDIF
202           DO j=1,jjp1
203             ! Troposphere
204             ddsin=sin(rlatu(j))
205             tetajl(j,l)=teta0-delt_y*ddsin*ddsin+eps*ddsin
206     &           -delt_z*(1.-ddsin*ddsin)*log(zsig)
207             !! Aymeric -- tests particuliers
208             if (planet_type=="giant") then
209             tetajl(j,l)=teta0+(delt_y*
210     &          ((sin(rlatu(j)*3.14159*eps+0.0001))**2)
211     &          / ((rlatu(j)*3.14159*eps+0.0001)**2))
212     &          -delt_z*log(zsig)
213!!!             ddsin=sin(2.5*3.14159*rlatu(j))
214!!!             tetajl(j,l)=teta0-delt_y*ddsin*ddsin
215!!!!     &           -delt_z*(1.-ddsin*ddsin)*log(zsig)
216             endif
217             ! Profil stratospherique isotherme (+vortex)
218             w_pv=(1.-tanh((rlatu(j)-phi_pv)/dphi_pv))/2.
219             tetastrat=tetastrat*(1.-w_pv)+tetapv*w_pv             
220             tetajl(j,l)=MAX(tetajl(j,l),tetastrat) 
221           ENDDO
222          ENDDO ! of DO l=1,llm
223 
224!          CALL writefield('theta_eq',tetajl)
225
226          do l=1,llm
227            do j=1,jjp1
228              do i=1,iip1
229                 ij=(j-1)*iip1+i
230                 tetarappel(ij,l)=tetajl(j,l)
231              enddo
232            enddo
233          enddo
234          PRINT *, 'iniacademic - check',tetajl(:,int(llm/2)),rlatu(:)
235
236
237!         else
238!          write(lunout,*)"iniacademic: planet types other than earth",
239!     &                   " not implemented (yet)."
240!          stop
241!         endif ! of if (planet_type=="earth")
242
243          ! 3. Initialize fields (if necessary)
244          IF (.NOT. read_start) THEN
245            ! surface pressure
246            ps(:)=preff
247            ! ground geopotential
248            phis(:)=0.
249           
250            CALL pression ( ip1jmp1, ap, bp, ps, p       )
251            CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
252            CALL massdair(p,masse)
253
254            ! bulk initialization of temperature
255            teta(:,:)=tetarappel(:,:)
256           
257            ! geopotential
258            CALL geopot(ip1jmp1,teta,pk,pks,phis,phi)
259           
260            ! winds
261            if (ok_geost) then
262              call ugeostr(phi,ucov)
263            else
264              ucov(:,:)=0.
265            endif
266            vcov(:,:)=0.
267           
268            ! bulk initialization of tracers
269            if (planet_type=="earth") then
270              ! Earth: first two tracers will be water
271              do i=1,nqtot
272                if (i.eq.1) q(:,:,i)=1.e-10
273                if (i.eq.2) q(:,:,i)=1.e-15
274                if (i.gt.2) q(:,:,i)=0.
275              enddo
276            else
277              q(:,:,:)=0
278            endif ! of if (planet_type=="earth")
279
280            ! add random perturbation to temperature
281            idum  = -1
282            zz = ran1(idum)
283            idum  = 0
284            do l=1,llm
285              do ij=iip2,ip1jm
286                teta(ij,l)=teta(ij,l)*(1.+0.005*ran1(idum))
287              enddo
288            enddo
289
290            ! maintain periodicity in longitude
291            do l=1,llm
292              do ij=1,ip1jmp1,iip1
293                teta(ij+iim,l)=teta(ij,l)
294              enddo
295            enddo
296
297          ENDIF ! of IF (.NOT. read_start)
298        endif ! of if (iflag_phys.eq.2)
299       
300      END
301c-----------------------------------------------------------------------
Note: See TracBrowser for help on using the repository browser.