/[lmdze]/trunk/dyn3d/vitvert.f90
ViewVC logotype

Contents of /trunk/dyn3d/vitvert.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 76 - (show annotations)
Fri Nov 15 18:45:49 2013 UTC (10 years, 6 months ago) by guez
File size: 796 byte(s)
Moved everything out of libf.
1 SUBROUTINE vitvert(convm , w)
2
3 ! From libf/dyn3d/vitvert.F, version 1.1.1.1 2004/05/19 12:53:05
4 ! Authors: P. Le Van , F. Hourdin
5
6 ! Objet : calcul de la vitesse verticale aux niveaux sigma
7
8 ! La vitesse verticale est orientee de haut en bas .
9 ! au sol, au niveau sigma(1), w(i, j, 1) = 0.
10 ! au sommet, au niveau sigma(llm+1) , la vit.verticale est aussi
11 ! egale a 0. et n'est pas stockee dans le tableau w .
12
13 USE dimens_m, ONLY : llm
14 USE paramet_m, ONLY : ip1jmp1
15 USE disvert_m, ONLY : bp
16
17 IMPLICIT NONE
18
19 real, intent(in):: convm(ip1jmp1, llm)
20 REAL, intent(out):: w(ip1jmp1, llm)
21
22 ! Local:
23 INTEGER l
24
25 !------------------------------------------------------
26
27 forall (l = 2: llm) w(:, l) = convm(:, l) - bp(l) * convm(:, 1)
28 w(:, 1) = 0.
29
30 END SUBROUTINE vitvert

  ViewVC Help
Powered by ViewVC 1.1.21