source: LMDZ4/trunk/libf/dyn3d/disvert0.F @ 1072

Last change on this file since 1072 was 999, checked in by Laurent Fairhead, 16 years ago
  • Modifs sur le parallelisme: masquage dans la physique
  • Inclusion strato
  • mise en coherence etat0
  • le mode offline fonctionne maintenant en parallele,
  • les fichiers de la dynamiques sont correctement sortis et peuvent etre reconstruit avec rebuild
  • la version parallele de la dynamique peut s'executer sans MPI (sur 1 proc)
  • L'OPENMP fonctionne maintenant sans la parallelisation MPI.

YM
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 disvert0(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig)
7
8c    Auteur :  P. Le Van .
9c
10      IMPLICIT NONE
11
12#include "dimensions.h"
13#include "paramet.h"
14#include "iniprint.h"
15#include "logic.h"
16c
17c=======================================================================
18c
19c
20c    s = sigma ** kappa   :  coordonnee  verticale
21c    dsig(l)            : epaisseur de la couche l ds la coord.  s
22c    sig(l)             : sigma a l'interface des couches l et l-1
23c    ds(l)              : distance entre les couches l et l-1 en coord.s
24c
25c=======================================================================
26c
27      REAL ap(llmp1),bp(llmp1),dpres(llm),nivsigs(llm),nivsig(llmp1)
28      REAL pa,preff,presnivs(llm)
29c
30c   declarations:
31c   -------------
32c
33      REAL sig(llm+1),dsig(llm)
34       real zzz(1:llm+1)
35       real dzz(1:llm)
36      real zk,zkm1,dzk1,dzk2,k0,k1
37c
38      INTEGER l
39      REAL snorm
40      REAL alpha,beta,gama,delta,deltaz,h
41      INTEGER np,ierr
42      REAL pi,x
43
44      REAL SSUM
45
46      pa        =  50 000.
47      preff     = 101 325.
48
49c
50c-----------------------------------------------------------------------
51c
52      pi=2.*ASIN(1.)
53
54      OPEN(99,file='sigma.def',status='old',form='formatted',
55     s   iostat=ierr)
56
57c-----------------------------------------------------------------------
58c   cas 1 on lit les options dans sigma.def:
59c   ----------------------------------------
60
61      IF (ierr.eq.0) THEN
62
63      READ(99,*) h           ! hauteur d'echelle 8.
64      READ(99,*) deltaz      ! epaiseur de la premiere couche 0.04
65      READ(99,*) beta        ! facteur d'acroissement en haut 1.3
66      READ(99,*) k0          ! nombre de couches dans la transition surf
67      READ(99,*) k1          ! nombre de couches dans la transition haute
68      CLOSE(99)
69      alpha=deltaz/(llm*h)
70      WRITE(lunout,*)'h,alpha,k0,k1,beta'
71
72c     read(*,*) h,deltaz,beta,k0,k1 ! 8 0.04 4 20 1.2
73
74      alpha=deltaz/tanh(1./k0)*2.
75      zkm1=0.
76      sig(1)=1.
77      do l=1,llm
78        sig(l+1)=(cosh(l/k0))**(-alpha*k0/h)
79     + *exp(-alpha/h*tanh((llm-k1)/k0)*beta**(l-(llm-k1))/log(beta))
80        zk=-h*log(sig(l+1))
81
82        dzk1=alpha*tanh(l/k0)
83        dzk2=alpha*tanh((llm-k1)/k0)*beta**(l-(llm-k1))/log(beta)
84        WRITE(lunout,*)l,sig(l+1),zk,zk-zkm1,dzk1,dzk2
85        zkm1=zk
86      enddo
87
88      sig(llm+1)=0.
89
90c
91       DO 2  l = 1, llm
92       dsig(l) = sig(l)-sig(l+1)
93   2   CONTINUE
94c
95
96      ELSE
97c-----------------------------------------------------------------------
98c   cas 2 ancienne discretisation (LMD5...):
99c   ----------------------------------------
100
101      write(lunout,*)'WARNING!!! Ancienne discretisation verticale'
102
103      h=7.
104      snorm  = 0.
105      DO l = 1, llm
106         x = 2.*asin(1.) * (FLOAT(l)-0.5) / float(llm+1)
107
108         IF (ok_strato) THEN
109           dsig(l) =(1.0 + 7.0 * SIN(x)**2)
110     &            *(0.5*(1.-tanh(1.*(x-asin(1.))/asin(1.))))**2       
111         ELSE
112           dsig(l) = 1.0 + 7.0 * SIN(x)**2
113         ENDIF
114
115         snorm = snorm + dsig(l)
116      ENDDO
117      snorm = 1./snorm
118      DO l = 1, llm
119         dsig(l) = dsig(l)*snorm
120      ENDDO
121      sig(llm+1) = 0.
122      DO l = llm, 1, -1
123         sig(l) = sig(l+1) + dsig(l)
124      ENDDO
125
126      ENDIF
127
128
129      DO l=1,llm
130        nivsigs(l) = FLOAT(l)
131      ENDDO
132
133      DO l=1,llmp1
134        nivsig(l)= FLOAT(l)
135      ENDDO
136
137c
138c    ....  Calculs  de ap(l) et de bp(l)  ....
139c    .........................................
140c
141c
142c   .....  pa et preff sont lus  sur les fichiers start par lectba  .....
143c
144
145      bp(llmp1) =   0.
146
147      DO l = 1, llm
148cc
149ccc    ap(l) = 0.
150ccc    bp(l) = sig(l)
151
152      bp(l) = EXP( 1. -1./( sig(l)*sig(l)) )
153      ap(l) = pa * ( sig(l) - bp(l) )
154c
155      ENDDO
156      ap(llmp1) = pa * ( sig(llmp1) - bp(llmp1) )
157
158      write(lunout,*)' BP '
159      write(lunout,*)  bp
160      write(lunout,*)' AP '
161      write(lunout,*)  ap
162
163      write(lunout,*)
164     .'Niveaux de pressions approximatifs aux centres des'
165      write(lunout,*)
166     .'couches calcules pour une pression de surface =',preff
167      write(lunout,*)
168     .'et altitudes equivalentes pour une hauteur d echelle de'
169      write(lunout,*)'8km'
170      DO l = 1, llm
171       dpres(l) = bp(l) - bp(l+1)
172       presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff )
173       write(lunout,*)'PRESNIVS(',l,')=',presnivs(l),'    Z ~ ',
174     .        log(preff/presnivs(l))*8.
175     .  ,'   DZ ~ ',8.*log((ap(l)+bp(l)*preff)/
176     .       max(ap(l+1)+bp(l+1)*preff,1.e-10))
177      ENDDO
178
179      write(lunout,*)' PRESNIVS '
180      write(lunout,*)presnivs
181
182      RETURN
183      END
Note: See TracBrowser for help on using the repository browser.