--- trunk/libf/dyn3d/comvert.f90 2008/10/15 16:19:57 20 +++ trunk/libf/dyn3d/comvert.f90 2010/04/06 17:52:58 32 @@ -7,8 +7,8 @@ private llm real ap(llm+1), pa ! in Pa - real bp(llm+1), dpres(llm) - real presnivs(llm) ! pressions approximatives des milieux couches, en Pa + real bp(llm+1) + real presnivs(llm) ! pressions approximatives des milieux de couches, en Pa real, parameter:: preff = 101325. ! in Pa real nivsigs(llm), nivsig(llm+1) @@ -22,15 +22,15 @@ ! Auteur : P. Le Van ! This procedure sets the vertical grid. - ! It defines the host variables "ap", "bp", "dpres", "presnivs", - ! "nivsigs" and "nivsig". + ! It defines the host variables "ap", "bp", "presnivs", "nivsigs" + ! and "nivsig". ! "pa" should be defined before this procedure is called. - use comconst, only: pi + use numer_rec, only: pi REAL s(llm+1) - ! (atmospheric hybrid sigma-pressure coordinate at the interface - ! between layers "l" and "l-1") + ! "s(l)" is the atmospheric hybrid sigma-pressure coordinate at + ! the interface between layers "l" and "l-1" real ds(llm) ! "ds(l)" : épaisseur de la couche "l" dans la coordonnée "s" @@ -118,10 +118,8 @@ bp(llm + 1) = 0. ap = pa * (s - bp) - forall (l = 1: llm) - dpres(l) = bp(l) - bp(l+1) - presnivs(l) = 0.5 * (ap(l) + bp(l) * preff + ap(l+1) + bp(l+1) * preff) - end forall + forall (l = 1: llm) presnivs(l) = 0.5 & + * (ap(l) + bp(l) * preff + ap(l+1) + bp(l+1) * preff) END SUBROUTINE disvert