/[lmdze]/trunk/libf/dyn3d/pression.f90
ViewVC logotype

Annotation of /trunk/libf/dyn3d/pression.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3 - (hide annotations)
Wed Feb 27 13:16:39 2008 UTC (16 years, 4 months ago) by guez
File size: 744 byte(s)
Initial import
1 guez 3 module pression_m
2    
3     IMPLICIT NONE
4    
5     contains
6    
7     SUBROUTINE pression(ngrid, ap, bp, ps, p)
8    
9     ! From dyn3d/pression.F, version 1.1.1.1 2004/05/19 12:53:07
10    
11     ! Authors : P. Le Van, F. Hourdin
12    
13     ! Calcule la pression p(l) aux différents niveaux l = 1 (niveau du
14     ! sol) à l = llm +1, ces niveaux correspondant aux interfaces des (llm)
15     ! couches, avec p(ij, llm +1) = 0 et p(ij, 1) = ps(ij).
16    
17     use dimens_m, only: llm
18    
19     INTEGER, intent(in):: ngrid
20     REAL, intent(in):: ap(llm + 1), bp(llm + 1)
21     real, intent(in):: ps(ngrid)
22     real, intent(out):: p(ngrid, llm + 1)
23    
24     INTEGER l
25    
26     !---------------------
27    
28     forall(l = 1: llm + 1) p(:, l) = ap(l) + bp(l) * ps(:)
29    
30     END SUBROUTINE pression
31    
32     end module pression_m

  ViewVC Help
Powered by ViewVC 1.1.21