Ignore:
Timestamp:
Mar 17, 2009, 12:24:48 PM (15 years ago)
Author:
jghattas
Message:
  • Correction de bug sur les poles pour le changement de repere avant et apres couplage avec l'ocean.
  • Passage au F90

Olivier Marti + JG

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/geo2atm.F90

    r1072 r1126  
    55  USE dimphy
    66  USE mod_phys_lmdz_para
    7    
     7
    88  IMPLICIT NONE
    9   include 'dimensions.h'
     9  INCLUDE 'dimensions.h'
     10  INCLUDE 'YOMCST.h'
    1011
    11 ! Change wind corrdinates from cartesian geocentric to local spherical
     12! Change wind coordinates from cartesian geocentric to local spherical
    1213! NB! Fonctionne probablement uniquement en MPI seul (sans OpenMP)
    1314!
     
    1718  REAL, DIMENSION (im,jm), INTENT(OUT) :: pu, pv, pr
    1819
    19   REAL, PARAMETER :: rpi = 3.141592653E0
    20   REAL, PARAMETER :: rad = rpi / 180.0E0
     20  REAL :: rad
     21
     22
     23  rad = rpi / 180.0E0
    2124 
    22   REAL, DIMENSION (im,jm) :: zsinlon, zcoslon
    23   REAL, DIMENSION (im,jm) :: zsinlat, zcoslat
     25  pu(:,:) = &
     26       - px(:,:) * SIN(rad * plon(:,:)) &
     27       + py(:,:) * COS(rad * plon(:,:))
    2428
    25   zsinlon = SIN (rad * plon)
    26   zcoslon = COS (rad * plon)
    27   zsinlat = SIN (rad * plat)
    28   zcoslat = COS (rad * plat)
     29  pv(:,:) = &
     30       - px(:,:) * SIN(rad * plat(:,:)) * COS(rad * plon(:,:)) &
     31       - py(:,:) * SIN(rad * plat(:,:)) * SIN(rad * plon(:,:)) &
     32       + pz(:,:) * COS(rad * plat(:,:)) 
    2933
    30   pu = - px * zsinlon         + py * zcoslon
    31   pv = - px * zsinlat*zcoslon - py * zsinlat*zsinlon + pz * zcoslat 
    32   pr =   px * zcoslat*zcoslon + py * zcoslat*zsinlon + pz * zsinlat
     34  pr(:,:) = &
     35       + px(:,:) * COS(rad * plat(:,:)) * COS(rad * plon(:,:)) &
     36       + py(:,:) * COS(rad * plat(:,:)) * SIN(rad * plon(:,:)) &
     37       + pz(:,:) * SIN(rad * plat(:,:))
    3338
    34 ! Value at North Pole
     39  ! Value at North Pole
    3540  IF (is_north_pole) THEN
    36      pu(:,1) = - py(1,1)
    37      pv(:,1) = - px(1,1)
    38      pr(:,1) = 0.
     41     pu(:, 1) = pu(1, 1)
     42     pv(:, 1) = pv(1, 1)
     43     pr(:, 1) = pr(1, 1)
    3944  ENDIF
    40 
    41 ! Value at South Pole     
     45 
     46  ! Value at South Pole     
    4247  IF (is_south_pole) THEN
    43      pu(:,jm) = py(1,jm)
    44      pv(:,jm) = px(1,jm)
    45      pr(:,jm) = 0.
     48     pu(:,jm) = pu(1,jm)
     49     pv(:,jm) = pv(1,jm)
     50     pr(:,jm) = pr(1,jm)
    4651  ENDIF
    47  
     52  
    4853END SUBROUTINE geo2atm
Note: See TracChangeset for help on using the changeset viewer.