source: LMDZ5/branches/testing/libf/dyn3dmem/iniacademic_loc.F90 @ 2056

Last change on this file since 2056 was 2056, checked in by Laurent Fairhead, 10 years ago

Merged trunk changes r1997:2055 into testing branch

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