Changeset 1126


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

Location:
LMDZ4/branches
Files:
1 edited
2 moved

Legend:

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

    r1125 r1126  
    22! $Header$
    33!
    4 C
    5       SUBROUTINE atm2geo ( im, jm, pte, ptn, plon, plat, pxx, pyy, pzz )
    6       USE dimphy
    7       USE mod_phys_lmdz_para
    8       IMPLICIT NONE
    9       include 'dimensions.h'
    10 cc
    11 cc Change wind local atmospheric coordinates to
    12 cc geocentric
    13 cc
    14 cxxx      INCLUDE 'param.h'
    15 c
    16       INTEGER, INTENT (in)              :: im, jm
    17       REAL, DIMENSION (im,jm), INTENT (in) :: pte, ptn
    18       REAL, DIMENSION (im,jm), INTENT (in) :: plon, plat
    19       REAL, DIMENSION (im,jm), INTENT(out) :: pxx, pyy, pzz
    20 c
    21       REAL, PARAMETER :: rpi = 3.141592653E0
    22       REAL, PARAMETER :: rad = rpi / 180.0E0
    23 c
    24       REAL, DIMENSION (im,jm) :: zsinlon, zcoslon
    25       REAL, DIMENSION (im,jm) :: zsinlat, zcoslat
    26 c
    27       LOGICAL, SAVE :: linit = .FALSE.
    28 c$OMP THREADPRIVATE(linit)
     4SUBROUTINE atm2geo ( im, jm, pte, ptn, plon, plat, pxx, pyy, pzz )
     5  USE dimphy
     6  USE mod_phys_lmdz_para
     7  IMPLICIT NONE
     8  INCLUDE 'dimensions.h'
     9  INCLUDE 'YOMCST.h'
     10!
     11! Change wind local atmospheric coordinates to geocentric
     12!
     13  INTEGER, INTENT (in)                 :: im, jm
     14  REAL, DIMENSION (im,jm), INTENT (in) :: pte, ptn
     15  REAL, DIMENSION (im,jm), INTENT (in) :: plon, plat
     16  REAL, DIMENSION (im,jm), INTENT(out) :: pxx, pyy, pzz
     17 
     18  REAL :: rad
    2919
    30 cym utilise pour le couple, ne fonctionne que en MPI seul
    31 c
    32 cxxx      IF ( .NOT. linit ) THEN
    33           zsinlon = SIN (rad * plon)
    34           zcoslon = COS (rad * plon)
    35           zsinlat = SIN (rad * plat)
    36           zcoslat = COS (rad * plat)
    37           linit = .TRUE.
    38 cxxx      ENDIF
    39 c
    40       pxx = - zsinlon * pte - zsinlat * zcoslon * ptn
    41       pyy =   zcoslon * pte - zsinlat * zsinlon * ptn
    42       pzz =   zcoslat * ptn
    4320
    44 c
    45 c Value at North Pole
    46       IF (is_north_pole) THEN
    47         pxx ( :,  1) = - ptn ( 1, 1)
    48         pyy ( :,  1) = - pte ( 1, 1)
    49         pzz ( :,  1) = 0.0
    50       ENDIF
    51 c Value at South Pole
    52      
    53       IF (is_south_pole) THEN
    54         pxx ( :, jm) = + ptn ( 1, jm)
    55         pyy ( :, jm) = + pte ( 1, jm)
    56         pzz ( :, jm) = 0.0
    57       ENDIF
    58  
    59       RETURN
    60       END SUBROUTINE atm2geo
     21  rad = rpi / 180.0E0
     22 
     23  pxx(:,:) = &
     24       - pte(:,:) * SIN(rad * plon(:,:)) &
     25       - ptn(:,:) * SIN(rad * plat(:,:)) * COS(rad * plon(:,:))
     26
     27  pyy(:,:) = &
     28       + pte(:,:) * COS(rad * plon(:,:)) &
     29       - ptn(:,:) * SIN(rad * plat(:,:)) * SIN(rad * plon(:,:))
     30 
     31  pzz(:,:) = &
     32       + ptn(:,:) * COS(rad * plat (:,:))
     33 
     34! Value at North Pole 
     35  IF (is_north_pole) THEN
     36     pxx(:, 1) = pxx(1,1)
     37     pyy(:, 1) = pyy(1,1)
     38     pzz(:, 1) = pzz(1,1)
     39  ENDIF
     40
     41! Value at South Pole
     42  IF (is_south_pole) THEN
     43     pxx(:,jm) = pxx(1,jm)
     44     pyy(:,jm) = pyy(1,jm)
     45     pzz(:,jm) = pzz(1,jm)
     46  ENDIF
     47 
     48END SUBROUTINE atm2geo
  • 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
  • LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/atm2geo.F90

    r1125 r1126  
    22! $Header$
    33!
    4 C
    5       SUBROUTINE atm2geo ( im, jm, pte, ptn, plon, plat, pxx, pyy, pzz )
    6       USE dimphy
    7       USE mod_phys_lmdz_para
    8       IMPLICIT NONE
    9       include 'dimensions.h'
    10 cc
    11 cc Change wind local atmospheric coordinates to
    12 cc geocentric
    13 cc
    14 cxxx      INCLUDE 'param.h'
    15 c
    16       INTEGER, INTENT (in)              :: im, jm
    17       REAL, DIMENSION (im,jm), INTENT (in) :: pte, ptn
    18       REAL, DIMENSION (im,jm), INTENT (in) :: plon, plat
    19       REAL, DIMENSION (im,jm), INTENT(out) :: pxx, pyy, pzz
    20 c
    21       REAL, PARAMETER :: rpi = 3.141592653E0
    22       REAL, PARAMETER :: rad = rpi / 180.0E0
    23 c
    24       REAL, DIMENSION (im,jm) :: zsinlon, zcoslon
    25       REAL, DIMENSION (im,jm) :: zsinlat, zcoslat
    26 c
    27       LOGICAL, SAVE :: linit = .FALSE.
    28 c$OMP THREADPRIVATE(linit)
     4SUBROUTINE atm2geo ( im, jm, pte, ptn, plon, plat, pxx, pyy, pzz )
     5  USE dimphy
     6  USE mod_phys_lmdz_para
     7  IMPLICIT NONE
     8  INCLUDE 'dimensions.h'
     9  INCLUDE 'YOMCST.h'
     10!
     11! Change wind local atmospheric coordinates to geocentric
     12!
     13  INTEGER, INTENT (in)                 :: im, jm
     14  REAL, DIMENSION (im,jm), INTENT (in) :: pte, ptn
     15  REAL, DIMENSION (im,jm), INTENT (in) :: plon, plat
     16  REAL, DIMENSION (im,jm), INTENT(out) :: pxx, pyy, pzz
     17 
     18  REAL :: rad
    2919
    30 cym utilise pour le couple, ne fonctionne que en MPI seul
    31 c
    32 cxxx      IF ( .NOT. linit ) THEN
    33           zsinlon = SIN (rad * plon)
    34           zcoslon = COS (rad * plon)
    35           zsinlat = SIN (rad * plat)
    36           zcoslat = COS (rad * plat)
    37           linit = .TRUE.
    38 cxxx      ENDIF
    39 c
    40       pxx = - zsinlon * pte - zsinlat * zcoslon * ptn
    41       pyy =   zcoslon * pte - zsinlat * zsinlon * ptn
    42       pzz =   zcoslat * ptn
    4320
    44 c
    45 c Value at North Pole
    46       IF (is_north_pole) THEN
    47         pxx ( :,  1) = - ptn ( 1, 1)
    48         pyy ( :,  1) = - pte ( 1, 1)
    49         pzz ( :,  1) = 0.0
    50       ENDIF
    51 c Value at South Pole
    52      
    53       IF (is_south_pole) THEN
    54         pxx ( :, jm) = + ptn ( 1, jm)
    55         pyy ( :, jm) = + pte ( 1, jm)
    56         pzz ( :, jm) = 0.0
    57       ENDIF
    58  
    59       RETURN
    60       END SUBROUTINE atm2geo
     21  rad = rpi / 180.0E0
     22 
     23  pxx(:,:) = &
     24       - pte(:,:) * SIN(rad * plon(:,:)) &
     25       - ptn(:,:) * SIN(rad * plat(:,:)) * COS(rad * plon(:,:))
     26
     27  pyy(:,:) = &
     28       + pte(:,:) * COS(rad * plon(:,:)) &
     29       - ptn(:,:) * SIN(rad * plat(:,:)) * SIN(rad * plon(:,:))
     30 
     31  pzz(:,:) = &
     32       + ptn(:,:) * COS(rad * plat (:,:))
     33 
     34! Value at North Pole 
     35  IF (is_north_pole) THEN
     36     pxx(:, 1) = pxx(1,1)
     37     pyy(:, 1) = pyy(1,1)
     38     pzz(:, 1) = pzz(1,1)
     39  ENDIF
     40
     41! Value at South Pole
     42  IF (is_south_pole) THEN
     43     pxx(:,jm) = pxx(1,jm)
     44     pyy(:,jm) = pyy(1,jm)
     45     pzz(:,jm) = pzz(1,jm)
     46  ENDIF
     47 
     48END SUBROUTINE atm2geo
Note: See TracChangeset for help on using the changeset viewer.