source: LMDZ4/trunk/libf/dyn3dpar/iniacademic.F @ 774

Last change on this file since 774 was 774, checked in by Laurent Fairhead, 17 years ago

Suite du merge entre la version et la HEAD: quelques modifications de
Yann sur le

LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.5 KB
Line 
1!
2! $Header$
3!
4c
5c
6      SUBROUTINE iniacademic(nq,vcov,ucov,teta,q,masse,ps,phis,time_0)
7
8c%W%    %G%
9c=======================================================================
10c
11c   Author:    Frederic Hourdin      original: 15/01/93
12c   -------
13c
14c   Subject:
15c   ------
16c
17c   Method:
18c   --------
19c
20c   Interface:
21c   ----------
22c
23c      Input:
24c      ------
25c
26c      Output:
27c      -------
28c
29c=======================================================================
30      IMPLICIT NONE
31c-----------------------------------------------------------------------
32c   Declararations:
33c   ---------------
34
35#include "dimensions.h"
36#include "paramet.h"
37#include "comvert.h"
38#include "comconst.h"
39#include "comgeom.h"
40#include "academic.h"
41#include "ener.h"
42#include "temps.h"
43#include "control.h"
44
45c   Arguments:
46c   ----------
47
48      integer nq
49      real time_0
50
51c   variables dynamiques
52      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
53      REAL teta(ip1jmp1,llm)                 ! temperature potentielle
54      REAL q(ip1jmp1,llm,nq)               ! champs advectes
55      REAL ps(ip1jmp1)                       ! pression  au sol
56      REAL masse(ip1jmp1,llm)                ! masse d'air
57      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
58      REAL pks(ip1jmp1)                      ! exner au  sol
59      REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
60      REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
61      REAL phis(ip1jmp1)                     ! geopotentiel au sol
62      REAL phi(ip1jmp1,llm)                  ! geopotentiel
63
64
65
66
67
68c   Local:
69c   ------
70
71      REAL ddsin,tetarappelj,tetarappell,zsig
72      real tetajl(jjp1,llm)
73      INTEGER i,j,l,lsup,ij
74
75      real zz,ran1
76      integer idum
77
78      REAL alpha(ip1jmp1,llm),beta(ip1jmp1,llm),zdtvr
79
80c-----------------------------------------------------------------------
81
82c
83      time_0=0.
84
85      im         = iim
86      jm         = jjm
87      day_ini    = 0
88      omeg       = 4.*asin(1.)/86400.
89      rad    = 6371229.
90      g      = 9.8
91      daysec = 86400.
92      dtvr    = daysec/FLOAT(day_step)
93      zdtvr=dtvr
94      kappa  = 0.2857143
95      cpp    = 1004.70885
96      preff     = 101325.
97      pa        =  50 000.
98      etot0      = 0.
99      ptot0      = 0.
100      ztot0      = 0.
101      stot0      = 0.
102      ang0       = 0.
103      pa         = 0.
104
105      CALL inicons0
106      CALL inigeom
107      CALL inifilr
108
109      ps=0.
110      phis=0.
111c---------------------------------------------------------------------
112
113      taurappel=10.*daysec
114
115c---------------------------------------------------------------------
116c   Calcul de la temperature potentielle :
117c   --------------------------------------
118
119      DO l=1,llm
120       zsig=ap(l)/preff+bp(l)
121       if (zsig.gt.0.3) then
122         lsup=l
123         tetarappell=1./8.*(-log(zsig)-.5)
124         DO j=1,jjp1
125            ddsin=sin(rlatu(j))-sin(pi/20.)
126            tetajl(j,l)=300.*(1+1./18.*(1.-3.*ddsin*ddsin)+tetarappell)
127         ENDDO
128        else
129c   Choix isotherme au-dessus de 300 mbar
130         do j=1,jjp1
131            tetajl(j,l)=tetajl(j,lsup)*(0.3/zsig)**kappa
132         enddo
133        endif
134      ENDDO
135
136      do l=1,llm
137         do j=1,jjp1
138            do i=1,iip1
139               ij=(j-1)*iip1+i
140               tetarappel(ij,l)=tetajl(j,l)
141            enddo
142         enddo
143      enddo
144
145c     call dump2d(jjp1,llm,tetajl,'TEQ   ')
146
147      ps=1.e5
148      phis=0.
149      CALL pression ( ip1jmp1, ap, bp, ps, p       )
150      CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
151      CALL massdair(p,masse)
152
153c  intialisation du vent et de la temperature
154      teta(:,:)=tetarappel(:,:)
155      CALL geopot(ip1jmp1,teta,pk,pks,phis,phi)
156      call ugeostr(phi,ucov)
157      vcov=0.
158      q(:,:,1   )=1.e-10
159      q(:,:,2   )=1.e-15
160      q(:,:,3:nq)=0.
161
162
163c   perturbation al\351atoire sur la temp\351rature
164      idum  = -1
165      zz = ran1(idum)
166      idum  = 0
167      do l=1,llm
168         do ij=iip2,ip1jm
169            teta(ij,l)=teta(ij,l)*(1.+0.005*ran1(idum))
170         enddo
171      enddo
172
173      do l=1,llm
174         do ij=1,ip1jmp1,iip1
175            teta(ij+iim,l)=teta(ij,l)
176         enddo
177      enddo
178
179
180
181c     PRINT *,' Appel test_period avec tetarappel '
182c     CALL  test_period ( ucov,vcov,tetarappel,q,p,phis )
183c     PRINT *,' Appel test_period avec teta '
184c     CALL  test_period ( ucov,vcov,teta,q,p,phis )
185
186c   initialisation d'un traceur sur une colonne
187      j=jjp1*3/4
188      i=iip1/2
189      ij=(j-1)*iip1+i
190      q(ij,:,3)=1.
191
192      return
193      END
194c-----------------------------------------------------------------------
Note: See TracBrowser for help on using the repository browser.