source: LMDZ5/branches/LMDZ5V2.0-dev/libf/dyn3dpar/iniacademic.F90 @ 1472

Last change on this file since 1472 was 1472, checked in by lguez, 13 years ago

Conversion to free source form for "disvert" and "iniacademic", no
other change. Bug fix in "fisrtilp": "fraca" could appear in an
expression while not defined.

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