/[lmdze]/trunk/dyn3d/tourabs.f
ViewVC logotype

Annotation of /trunk/dyn3d/tourabs.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 82 - (hide annotations)
Wed Mar 5 14:57:53 2014 UTC (10 years, 3 months ago) by guez
File size: 2152 byte(s)
Changed all ".f90" suffixes to ".f".
1 guez 79 module tourabs_m
2 guez 3
3 guez 79 IMPLICIT NONE
4 guez 3
5 guez 79 contains
6 guez 27
7 guez 79 SUBROUTINE tourabs(ntetaSTD, vcov, ucov, vorabs)
8 guez 3
9 guez 79 ! Author: I. Musat, 28 October 2004, adaptation de tourpot
10     ! Objet : calcul de la vorticité absolue
11 guez 3
12 guez 79 USE dimens_m, ONLY: iim, jjm
13     USE paramet_m, ONLY: iip1, ip1jm, ip1jmp1
14     USE comconst, ONLY: rad
15     USE comgeom, ONLY: cu, cv, fext, rlatv, unsairez
16     USE filtreg_m, ONLY: filtreg
17     USE nr_util, ONLY: pi
18 guez 3
19 guez 79 INTEGER, intent(in):: ntetaSTD
20     REAL, intent(in):: vcov(ip1jm, ntetaSTD), ucov(ip1jmp1, ntetaSTD)
21 guez 3
22 guez 79 REAL, intent(out):: vorabs(ip1jm, ntetaSTD)
23     ! vorabs = Filtre(d(vcov)/dx - d(ucov)/dy) + fext
24 guez 3
25 guez 79 ! Variables locales:
26     INTEGER l, ij, i, j
27     REAL rot(ip1jm, ntetaSTD)
28 guez 3
29 guez 79 !--------------------------------------------------------------------
30 guez 3
31 guez 79 ! Calcul du rotationnel du vent puis filtrage
32 guez 3
33 guez 79 DO l = 1, ntetaSTD
34     DO i = 1, iip1
35     DO j = 1, jjm
36     ij = i + (j - 1) * iip1
37     IF (ij <= ip1jm - 1) THEN
38     IF (cv(ij) == 0. .OR. cv(ij+1) == 0. .OR. cu(ij) == 0. &
39     .OR. cu(ij+iip1) == 0.) THEN
40     rot(ij, l) = 0.
41     ELSE
42     rot(ij, l) = (vcov(ij + 1, l) / cv(ij + 1) - vcov(ij, l) &
43     / cv(ij)) / (2. * pi * RAD * cos(rlatv(j))) &
44     * real(iim) + (ucov(ij + iip1, l) / cu(ij + iip1) &
45     - ucov(ij, l) / cu(ij)) / (pi * RAD) * (real(jjm) - 1.)
46     ENDIF
47     ENDIF
48     end DO
49     end DO
50 guez 3
51 guez 79 ! correction pour rot(iip1, j, l)
52     ! rot(iip1, j, l) = rot(1, j, l)
53     DO ij = iip1, ip1jm, iip1
54     rot(ij, l) = rot(ij - iim, l)
55     end DO
56     end DO
57 guez 3
58 guez 79 CALL filtreg(rot, jjm, ntetaSTD, 2, 1, .FALSE.)
59 guez 3
60 guez 79 DO l = 1, ntetaSTD
61     DO ij = 1, ip1jm - 1
62     vorabs(ij, l) = (rot(ij, l) + fext(ij) * unsairez(ij))
63     end DO
64 guez 3
65 guez 79 ! correction pour vorabs(iip1, j, l)
66     ! vorabs(iip1, j, l)= vorabs(1, j, l)
67     DO ij = iip1, ip1jm, iip1
68     vorabs(ij, l) = vorabs(ij - iim, l)
69     end DO
70     end DO
71 guez 3
72 guez 79 END SUBROUTINE tourabs
73 guez 3
74 guez 79 end module tourabs_m

  ViewVC Help
Powered by ViewVC 1.1.21