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

Last change on this file since 1146 was 1146, checked in by Laurent Fairhead, 15 years ago

Réintegration dans le tronc des modifications issues de la branche LMDZ-dev
comprises entre la révision 1074 et 1145
Validation: une simulation de 1 jour en séquentiel sur PC donne les mêmes
résultats entre la trunk et la dev
LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.0 KB
Line 
1!
2! $Header$
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
11c%W%    %G%
12c=======================================================================
13c
14c   Author:    Frederic Hourdin      original: 15/01/93
15c   -------
16c
17c   Subject:
18c   ------
19c
20c   Method:
21c   --------
22c
23c   Interface:
24c   ----------
25c
26c      Input:
27c      ------
28c
29c      Output:
30c      -------
31c
32c=======================================================================
33      IMPLICIT NONE
34c-----------------------------------------------------------------------
35c   Declararations:
36c   ---------------
37
38#include "dimensions.h"
39#include "paramet.h"
40#include "comvert.h"
41#include "comconst.h"
42#include "comgeom.h"
43#include "academic.h"
44#include "ener.h"
45#include "temps.h"
46#include "control.h"
47#include "iniprint.h"
48
49c   Arguments:
50c   ----------
51
52      real time_0
53
54c   variables dynamiques
55      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
56      REAL teta(ip1jmp1,llm)                 ! temperature potentielle
57      REAL q(ip1jmp1,llm,nqtot)              ! champs advectes
58      REAL ps(ip1jmp1)                       ! pression  au sol
59      REAL masse(ip1jmp1,llm)                ! masse d'air
60      REAL phis(ip1jmp1)                     ! geopotentiel au sol
61
62c   Local:
63c   ------
64
65      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
66      REAL pks(ip1jmp1)                      ! exner au  sol
67      REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
68      REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
69      REAL phi(ip1jmp1,llm)                  ! geopotentiel
70      REAL ddsin,tetarappelj,tetarappell,zsig
71      real tetajl(jjp1,llm)
72      INTEGER i,j,l,lsup,ij
73
74      real zz,ran1
75      integer idum
76
77      REAL alpha(ip1jmp1,llm),beta(ip1jmp1,llm),zdtvr
78
79c-----------------------------------------------------------------------
80! 1. Initializations for Earth-like case
81! --------------------------------------
82      if (planet_type=="earth") then
83c
84        time_0=0.
85
86        im         = iim
87        jm         = jjm
88        day_ini    = 0
89        omeg       = 4.*asin(1.)/86400.
90        rad    = 6371229.
91        g      = 9.8
92        daysec = 86400.
93        dtvr    = daysec/FLOAT(day_step)
94        zdtvr=dtvr
95        kappa  = 0.2857143
96        cpp    = 1004.70885
97        preff     = 101325.
98        pa        =  50000.
99        etot0      = 0.
100        ptot0      = 0.
101        ztot0      = 0.
102        stot0      = 0.
103        ang0       = 0.
104
105        CALL iniconst
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 ! of if (zsig.gt.0.3)
134        ENDDO ! of DO l=1,llm
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:nqtot)=0.
161
162
163c   perturbation aleatoire sur la temperature
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      else
193        write(lunout,*)"iniacademic: planet types other than earth",
194     &                 " not implemented (yet)."
195        stop
196      endif ! of if (planet_type=="earth")
197      return
198      END
199c-----------------------------------------------------------------------
Note: See TracBrowser for help on using the repository browser.