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

Contents of /trunk/dyn3d/tourpot.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (show annotations)
Thu Jun 13 14:40:06 2019 UTC (4 years, 11 months ago) by guez
File size: 1352 byte(s)
Change all `.f` suffixes to `.f90`. (The opposite was done in revision
82.)  Because of change of philosopy in GNUmakefile: we already had a
rewritten rule for `.f`, so it does not make the makefile longer to
replace it by a rule for `.f90`. And it spares us options of
makedepf90 and of the compiler. Also we prepare the way for a simpler
`CMakeLists.txt`.

1 module tourpot_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE tourpot(vcov, ucov, massebxy, vorpot)
8
9 ! From LMDZ4/libf/dyn3d/tourpot.F, version 1.1.1.1, 2004/05/19 12:53:06
10
11 ! Author: P. Le Van
12 ! Objet : calcul du tourbillon potentiel
13
14 USE comgeom, ONLY: fext_2d
15 USE dimensions, ONLY: iim, jjm, llm
16 use filtreg_v_m, only: filtreg_v
17
18 REAL, intent(in):: vcov(:, :, :) ! (iim + 1, jjm, llm)
19 REAL, intent(in):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm)
20 REAL, intent(in):: massebxy(:, :, :) ! (iim + 1, jjm, llm) mass of grid cell
21
22 real, intent(out):: vorpot(:, :, :) ! (iim + 1, jjm, llm)
23 ! = (Filtre(d(vcov)/dx - d(ucov)/dy) + fext) / massebxy
24
25 ! Local:
26
27 REAL rot(iim + 1, jjm, llm)
28 ! relative vorticity multiplied by cell area, in m2 s-1
29
30 INTEGER l, i, j
31
32 !---------------------------------------------------------------
33
34 ! Calcul du rotationnel du vent puis filtrage
35
36 forall (i = 1: iim, j = 1: jjm) rot(i, j, :) &
37 = vcov(i + 1, j, :) - vcov(i, j, :) + ucov(i, j + 1, :) - ucov(i, j, :)
38 rot(iim + 1, :, :) = rot(1, :, :)
39
40 CALL filtreg_v(rot, intensive = .true.)
41
42 forall (l = 1: llm) vorpot(:iim, :, l) &
43 = (rot(:iim, :, l) + fext_2d(:iim, :)) / massebxy(:iim, :, l)
44 vorpot(iim + 1, :, :)= vorpot(1, :, :)
45
46 END SUBROUTINE tourpot
47
48 end module tourpot_m

  ViewVC Help
Powered by ViewVC 1.1.21