source: LMDZ6/trunk/libf/phylmd/atm2geo.f90 @ 5367

Last change on this file since 5367 was 5285, checked in by abarral, 7 weeks ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

  • 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
RevLine 
[524]1!
[2429]2! $Id: atm2geo.f90 5285 2024-10-28 13:33:29Z abarral $
[524]3!
[1126]4SUBROUTINE atm2geo ( im, jm, pte, ptn, plon, plat, pxx, pyy, pzz )
5  USE dimphy
6  USE mod_phys_lmdz_para
[3465]7  USE mod_grid_phy_lmdz, only: grid_type, unstructured, regular_lonlat
[5285]8  USE yomcst_mod_h
[5274]9IMPLICIT NONE
[3465]10
[5274]11
[3465]12  CHARACTER (len = 6)                :: clmodnam
13  CHARACTER (len = 20)               :: modname = 'atm2geo'
14  CHARACTER (len = 80)               :: abort_message
15
[1126]16!
17! Change wind local atmospheric coordinates to geocentric
18!
[3465]19! Geocentric :
20! axe x is eastward : crosses (0 N, 0 E) point.
21! axe y crosses (0 N, 90 E) point.
22! axe z is 'up' : crosses north pole
[1126]23  INTEGER, INTENT (in)                 :: im, jm
[3465]24  REAL, DIMENSION (im,jm), INTENT (in) :: pte  ! Eastward vector component
25  REAL, DIMENSION (im,jm), INTENT (in) :: ptn  ! Northward vector component
[1126]26  REAL, DIMENSION (im,jm), INTENT (in) :: plon, plat
[3465]27  REAL, DIMENSION (im,jm), INTENT(out) :: pxx, pyy, pzz  ! Component in the geocentric referential
28  REAL :: rad, reps
[776]29
[1126]30  rad = rpi / 180.0E0
[3465]31  reps = 1.0e-5
[1126]32 
33  pxx(:,:) = &
34       - pte(:,:) * SIN(rad * plon(:,:)) &
35       - ptn(:,:) * SIN(rad * plat(:,:)) * COS(rad * plon(:,:))
36
37  pyy(:,:) = &
38       + pte(:,:) * COS(rad * plon(:,:)) &
39       - ptn(:,:) * SIN(rad * plat(:,:)) * SIN(rad * plon(:,:))
40 
41  pzz(:,:) = &
42       + ptn(:,:) * COS(rad * plat (:,:))
43 
[3465]44  IF (grid_type==regular_lonlat) THEN
45  ! Value at North Pole 
46    IF (is_north_pole_dyn) THEN
47       pxx(:, 1) = - pte (1, 1)
48       pyy(:, 1) = - ptn (1, 1)
49       pzz(:, 1) = pzz(1,1) ! => 0
50    ENDIF
[1126]51
[3465]52  ! Value at South Pole
53    IF (is_south_pole_dyn) THEN
54      pxx(:,jm) = pxx(1,jm)
55       pyy(:,jm) = pyy(1,jm)
56       pzz(:,jm) = pzz(1,jm) ! => 0
57    ENDIF
58 
59  ELSE IF (grid_type==unstructured) THEN
60     ! Pole nord pour Dynamico
61     WHERE ( plat(:,:) >= 90.0d+0-reps )
62        pxx (:,:) = -ptn (:,:)
63        pyy (:,:) =  pte (:,:)
64        pzz (:,:) =  0.0e0
65     END WHERE
66
67  ELSE
68     abort_message='Problem: unknown grid type'
69     CALL abort_physic(modname,abort_message,1)
70  END IF
71
[1126]72 
73END SUBROUTINE atm2geo
Note: See TracBrowser for help on using the repository browser.