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

Last change on this file since 5277 was 5274, checked in by abarral, 9 hours ago

Replace yomcst.h by existing module

  • 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.8 KB
RevLine 
[524]1!
[2429]2! $Id: atm2geo.f90 5274 2024-10-25 13:41:23Z 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
[5274]8  USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
9          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
10          , R_ecc, R_peri, R_incl                                      &
11          , RA, RG, R1SA                                         &
12          , RSIGMA                                                     &
13          , R, RMD, RMV, RD, RV, RCPD                    &
14          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
15          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
16          , RCW, RCS                                                 &
17          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
18          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
19          , RALPD, RBETD, RGAMD
20IMPLICIT NONE
[3465]21
[5274]22
[3465]23  CHARACTER (len = 6)                :: clmodnam
24  CHARACTER (len = 20)               :: modname = 'atm2geo'
25  CHARACTER (len = 80)               :: abort_message
26
[1126]27!
28! Change wind local atmospheric coordinates to geocentric
29!
[3465]30! Geocentric :
31! axe x is eastward : crosses (0 N, 0 E) point.
32! axe y crosses (0 N, 90 E) point.
33! axe z is 'up' : crosses north pole
[1126]34  INTEGER, INTENT (in)                 :: im, jm
[3465]35  REAL, DIMENSION (im,jm), INTENT (in) :: pte  ! Eastward vector component
36  REAL, DIMENSION (im,jm), INTENT (in) :: ptn  ! Northward vector component
[1126]37  REAL, DIMENSION (im,jm), INTENT (in) :: plon, plat
[3465]38  REAL, DIMENSION (im,jm), INTENT(out) :: pxx, pyy, pzz  ! Component in the geocentric referential
39  REAL :: rad, reps
[776]40
[1126]41  rad = rpi / 180.0E0
[3465]42  reps = 1.0e-5
[1126]43 
44  pxx(:,:) = &
45       - pte(:,:) * SIN(rad * plon(:,:)) &
46       - ptn(:,:) * SIN(rad * plat(:,:)) * COS(rad * plon(:,:))
47
48  pyy(:,:) = &
49       + pte(:,:) * COS(rad * plon(:,:)) &
50       - ptn(:,:) * SIN(rad * plat(:,:)) * SIN(rad * plon(:,:))
51 
52  pzz(:,:) = &
53       + ptn(:,:) * COS(rad * plat (:,:))
54 
[3465]55  IF (grid_type==regular_lonlat) THEN
56  ! Value at North Pole 
57    IF (is_north_pole_dyn) THEN
58       pxx(:, 1) = - pte (1, 1)
59       pyy(:, 1) = - ptn (1, 1)
60       pzz(:, 1) = pzz(1,1) ! => 0
61    ENDIF
[1126]62
[3465]63  ! Value at South Pole
64    IF (is_south_pole_dyn) THEN
65      pxx(:,jm) = pxx(1,jm)
66       pyy(:,jm) = pyy(1,jm)
67       pzz(:,jm) = pzz(1,jm) ! => 0
68    ENDIF
69 
70  ELSE IF (grid_type==unstructured) THEN
71     ! Pole nord pour Dynamico
72     WHERE ( plat(:,:) >= 90.0d+0-reps )
73        pxx (:,:) = -ptn (:,:)
74        pyy (:,:) =  pte (:,:)
75        pzz (:,:) =  0.0e0
76     END WHERE
77
78  ELSE
79     abort_message='Problem: unknown grid type'
80     CALL abort_physic(modname,abort_message,1)
81  END IF
82
[1126]83 
84END SUBROUTINE atm2geo
Note: See TracBrowser for help on using the repository browser.