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

Last change on this file since 5133 was 5117, checked in by abarral, 5 months ago

rename modules properly lmdz_*
move some unused files to obsolete/
(lint) uppercase fortran keywords

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