source: LMDZ6/branches/Amaury_dev/libf/phylmd/atm2geo.F90 @ 5110

Last change on this file since 5110 was 5110, checked in by abarral, 2 months ago

Rename modules properly (mod_* -> lmdz_*) in phy_common

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 2.0 KB
Line 
1
2! $Id: atm2geo.F90 5110 2024-07-24 09:19:08Z abarral $
3
4SUBROUTINE atm2geo( im, jm, pte, ptn, plon, plat, pxx, pyy, pzz )
5  USE dimphy
6  USE lmdz_phys_para
7  USE lmdz_grid_phy, only: grid_type, unstructured, regular_lonlat
8  IMPLICIT NONE
9  INCLUDE 'YOMCST.h'
10
11  CHARACTER (len = 6)                :: clmodnam
12  CHARACTER (len = 20)               :: modname = 'atm2geo'
13  CHARACTER (len = 80)               :: abort_message
14
15! Change wind local atmospheric coordinates to geocentric
16
17! Geocentric :
18! axe x is eastward : crosses (0 N, 0 E) point.
19! axe y crosses (0 N, 90 E) point.
20! axe z is 'up' : crosses north pole
21  INTEGER, INTENT (in)                 :: im, jm
22  REAL, DIMENSION (im,jm), INTENT (in) :: pte  ! Eastward vector component
23  REAL, DIMENSION (im,jm), INTENT (in) :: ptn  ! Northward vector component
24  REAL, DIMENSION (im,jm), INTENT (in) :: plon, plat
25  REAL, DIMENSION (im,jm), INTENT(out) :: pxx, pyy, pzz  ! Component in the geocentric referential
26  REAL :: rad, reps
27
28  rad = rpi / 180.0E0
29  reps = 1.0e-5
30 
31  pxx(:,:) = &
32       - pte(:,:) * SIN(rad * plon(:,:)) &
33       - ptn(:,:) * SIN(rad * plat(:,:)) * COS(rad * plon(:,:))
34
35  pyy(:,:) = &
36       + pte(:,:) * COS(rad * plon(:,:)) &
37       - ptn(:,:) * SIN(rad * plat(:,:)) * SIN(rad * plon(:,:))
38 
39  pzz(:,:) = &
40       + ptn(:,:) * COS(rad * plat (:,:))
41 
42  IF (grid_type==regular_lonlat) THEN
43  ! Value at North Pole 
44    IF (is_north_pole_dyn) THEN
45       pxx(:, 1) = - pte (1, 1)
46       pyy(:, 1) = - ptn (1, 1)
47       pzz(:, 1) = pzz(1,1) ! => 0
48    ENDIF
49
50  ! Value at South Pole
51    IF (is_south_pole_dyn) THEN
52      pxx(:,jm) = pxx(1,jm)
53       pyy(:,jm) = pyy(1,jm)
54       pzz(:,jm) = pzz(1,jm) ! => 0
55    ENDIF
56 
57  ELSE IF (grid_type==unstructured) THEN
58     ! Pole nord pour Dynamico
59     WHERE ( plat(:,:) >= 90.0d+0-reps )
60        pxx (:,:) = -ptn (:,:)
61        pyy (:,:) =  pte (:,:)
62        pzz (:,:) =  0.0e0
63     END WHERE
64
65  ELSE
66     abort_message='Problem: unknown grid type'
67     CALL abort_physic(modname,abort_message,1)
68  END IF
69
70 
71END SUBROUTINE atm2geo
Note: See TracBrowser for help on using the repository browser.