SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/latlontoxy1d.F90
Go to the documentation of this file.
00001 !     #########
00002        SUBROUTINE LATLONTOXY1D(PLAT0,PLON0,PRPK,PBETA,PLATOR,PLONOR, &
00003                                  PXHATM,PYHATM,PLAT,PLON,KN,PRADIUS)  
00004 !      ################################################
00005 !
00006 !!****  *SM_LATLONTOXY1D * - Routine to compute conformal coordinates
00007 !!
00008 !!
00009 !!     PURPOSE
00010 !!     -------
00011 !        This routine computes the cartesian conformal coordinates 
00012 !      of an array given in latitude-longitude coordinates
00013 !        Three map projections are available: 
00014 !      - polar-stereographic (PRPK=1),
00015 !      - lambert conformal  (0<PRPK<1),
00016 !      - mercator (PRPK=0).
00017 !
00018 !
00019 !!**   METHOD
00020 !!     ------
00021 !!       Spherical earth approximation is used. Longitude origin is 
00022 !!     set in Greenwich, and is positive eastwards. An anticlockwise 
00023 !!     rotation of XBETA degrees is applied to the conformal frame 
00024 !!     with respect to the geographical directions.
00025 !!
00026 !!       WARNING: ALL INPUT AND OUTPUT ANGLES ARE IN DEGREES...
00027 !!
00028 !!     EXTERNAL
00029 !!     --------
00030 !!       None
00031 !!
00032 !!     EXPLICIT ARGUMENTS
00033 !!     ------------------
00034 !!       PXHAT,PYHAT(:)  : 1D arrays of the "velocity" gridpoints
00035 !!                         cartesian conformal coordinates (meters,input).
00036 !!       PLATOR   : Latitude of the (1,1) point of the "mass" grid
00037 !!                      (degrees,input);
00038 !!       PLONOR   : Longitude of the (1,1) point of the "mass" grid
00039 !!                      (degrees,input);
00040 !!       PXHATM   : conformal coordinate x  (meters, mass-grid, input)
00041 !!       PYHATM   : conformal coordinate y  (meters, mass-grid, input)
00042 !!       PLAT    : latitude                (degrees, mass-grid, output)
00043 !!       PLON    : longitude               (degrees, mass-grid, output)
00044 !!
00045 !!     IMPLICIT ARGUMENTS
00046 !!     ------------------
00047 !!       Module MODD_CST         : contains Physical constants
00048 !!          XPI         : Pi;    
00049 !!          XRADIUS     : Earth radius (meters);
00050 !!
00051 !!
00052 !!     REFERENCE
00053 !!     ---------
00054 !!      Asencio N. et al., 1994, "Le projet de modele non-hydrostatique
00055 !!            commun CNRM-LA, specifications techniques", 
00056 !!            Note CNRM/GMME, 26, 139p, (Chapter 2).
00057 !!      Ducrocq V., 1994, "Generation de la grille dans le modele",
00058 !!            Note interne MNH, 5 mai, 3p.
00059 !!      Joly A., 1992, "Geographic parameters for ARPEGE/ALADIN",
00060 !!            Internal note ARPEGE/ALADIN, february 27,28p.
00061 !!      Levallois J., 1970, "Geodesie generale", Tome 2, Collection
00062 !!             de l'IGN, Eyrolles, Paris, 408p.
00063 !!       
00064 !!     AUTHOR
00065 !!     ------
00066 !!      P.M.       *LA*
00067 !!
00068 !!     MODIFICATION
00069 !!     ------------
00070 !!       Original PM  24/05/94
00071 !!       Updated  PM  27/07/94
00072 !!       Updated  VD  23/08/94
00073 !!       Updated  VM  24/10/95 projection from north pole (PRPK<0) and 
00074 !!                             longitudes set between PLON0-180. and PLON0+180.
00075 !!
00076 !-------------------------------------------------------------------------------
00077 !
00078 !*     0.     DECLARATIONS
00079 !             ------------
00080 !
00081 USE MODD_CSTS
00082 !
00083 !
00084 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00085 USE PARKIND1  ,ONLY : JPRB
00086 !
00087 IMPLICIT NONE
00088 !
00089 !*     0.1    Declarations of arguments and results
00090 !
00091 INTEGER,             INTENT(IN) :: KN
00092 REAL,                INTENT(IN) :: PLAT0
00093 REAL,                INTENT(IN) :: PLON0
00094 REAL,                INTENT(IN) :: PRPK
00095 REAL,                INTENT(IN) :: PBETA
00096 REAL,                INTENT(IN) :: PLATOR ! Latitude of the origine point
00097 REAL,                INTENT(IN) :: PLONOR ! Longitude of the origine point
00098 REAL, DIMENSION(KN), INTENT(IN) :: PLAT,PLON
00099 REAL, DIMENSION(KN), INTENT(OUT):: PXHATM,PYHATM
00100 REAL, OPTIONAL,      INTENT(IN) :: PRADIUS
00101 !
00102 !*     0.2    Declarations of local variables
00103 ! 
00104 REAL,DIMENSION(KN) :: ZLAT,ZLON
00105 REAL :: ZRPK,ZLAT0,ZLON0,ZLATOR,ZLONOR
00106 REAL :: ZRDSDG,ZCLAT0,ZSLAT0,ZCLATOR,ZSLATOR
00107 REAL :: ZRO0,ZGA0,ZBETA,ZCGAM,ZSGAM
00108 REAL :: ZXP,ZYP,ZRACLAT0,ZXE,ZYE
00109 REAL :: ZRADIUS
00110 !
00111 REAL,DIMENSION(KN) :: ZCLAT,ZSLAT,ZRO,ZGA,ZXPR,ZYPR
00112 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00113 !
00114 !
00115 !-------------------------------------------------------------------------------
00116 !
00117 !*     1.     PRELIMINARY CALCULATION FOR ALL PROJECTIONS
00118 !             -------------------------------------------
00119 !
00120 IF (LHOOK) CALL DR_HOOK('LATLONTOXY1D',0,ZHOOK_HANDLE)
00121 ZRDSDG = XPI/180.         ! Degree to radian conversion factor
00122 !
00123 ! By definition, (PLONOR,PLATOR) are the geographical 
00124 ! coordinates, and (ZXBM0,ZYBM0) the conformal cartesian 
00125 ! coordinates of the (1,1) point of the "mass" grid.
00126 !
00127 !
00128 ZLON(:)=PLON(:)
00129 ZLON(:)=ZLON(:)+NINT((PLON0-ZLON(:))/360.)*360.
00130 !
00131 ZLONOR=PLONOR
00132 ZLONOR=ZLONOR+NINT((PLON0-ZLONOR)/360.)*360.
00133 !
00134 ZRADIUS = XRADIUS
00135 IF (PRESENT(PRADIUS)) ZRADIUS = PRADIUS
00136 !
00137 !------------------------------------------------------------------------------
00138 !
00139 !*     2.     POLAR SEREOGRAPHIC AND LAMBERT CONFORMAL CASES
00140 !             ----------------------------------------------
00141 !                   (PRPK=1 P-stereo, 0<PRPK<1 Lambert)
00142 !
00143 IF(PRPK  /=  0.) THEN
00144 !
00145   IF (PRPK<0.) THEN     ! projection from north pole
00146     ZRPK=-PRPK
00147     ZBETA=-PBETA
00148     ZLAT0=-PLAT0
00149     ZLON0=PLON0+180.
00150     ZLATOR=-PLATOR
00151     ZLONOR=ZLONOR+180.
00152     ZLAT(:)=-PLAT(:)
00153     ZLON(:)=ZLON(:)+180.
00154   ELSE                  ! projection from south pole
00155     ZRPK=PRPK
00156     ZBETA=PBETA
00157     ZLAT0=PLAT0
00158     ZLON0=PLON0
00159     ZLATOR=PLATOR
00160     ZLONOR=ZLONOR
00161     ZLAT(:)=PLAT(:)
00162     ZLON(:)=ZLON(:)
00163   ENDIF    
00164 !
00165 !*     2.1    Preliminary calculations
00166 !
00167   ZCLAT0  = COS(ZRDSDG*ZLAT0)
00168   ZSLAT0  = SIN(ZRDSDG*ZLAT0)
00169   ZCLATOR = COS(ZRDSDG*ZLATOR)
00170   ZSLATOR = SIN(ZRDSDG*ZLATOR)
00171   ZRO0    = (ZRADIUS/ZRPK)*(ABS(ZCLAT0))**(1.-ZRPK)    &
00172             * ((1.+ZSLAT0)*ABS(ZCLATOR)/(1.+ZSLATOR))**ZRPK  
00173   ZGA0    = (ZRPK*(ZLONOR-ZLON0)-ZBETA)*ZRDSDG
00174   ZXP     = -ZRO0*SIN(ZGA0)
00175   ZYP     = ZRO0*COS(ZGA0)
00176 !
00177 !*    2.2    Conformal coordinates in meters
00178 !
00179   ZCLAT(:)  = COS(ZRDSDG*ZLAT(:))
00180   ZSLAT(:)  = SIN(ZRDSDG*ZLAT(:))
00181   ZRO(:)    = (ZRADIUS/ZRPK)*(ABS(ZCLAT0))**(1.-ZRPK)    &
00182                * ((1.+ZSLAT0)*ABS(ZCLAT(:))/(1.+ZSLAT(:)))**ZRPK  
00183   ZGA(:)    = (ZRPK*(ZLON(:)-ZLON0)-ZBETA)*ZRDSDG
00184 !
00185   PXHATM(:) = ZXP+ZRO(:)*SIN(ZGA(:))
00186   PYHATM(:) = ZYP-ZRO(:)*COS(ZGA(:))
00187 !
00188   IF (PRPK<0.) THEN     ! projection from north pole
00189     PYHATM(:)=-PYHATM(:)
00190   ENDIF
00191 !
00192 !-------------------------------------------------------------------------------
00193 !
00194 !*  3.        MERCATOR PROJECTION WITH ROTATION
00195 !             ---------------------------------
00196 !                       (PRPK=0)
00197 !
00198 ELSE
00199 !
00200 !*  3.1       Preliminary calculations
00201 !
00202   ZCGAM    = COS(-ZRDSDG*PBETA)
00203   ZSGAM    = SIN(-ZRDSDG*PBETA)
00204   ZRACLAT0 = ZRADIUS*COS(ZRDSDG*PLAT0)
00205   ZXE      = - ZRACLAT0*(PLONOR-PLON0)*ZRDSDG 
00206   ZYE      = - ZRACLAT0*LOG(TAN(XPI/4.+PLATOR*ZRDSDG/2.))
00207 !
00208 !*  3.2       Conformal coordinates
00209 !
00210   ZXPR(:)   = ZRACLAT0*(ZLON(:)-PLON0)*ZRDSDG+ZXE
00211   ZYPR(:)   = ZRACLAT0*LOG(TAN(XPI/4.+PLAT(:)*ZRDSDG/2.))+ZYE
00212   !
00213   PXHATM = ZXPR(:)*ZCGAM-ZYPR(:)*ZSGAM
00214   PYHATM = ZXPR(:)*ZSGAM+ZYPR(:)*ZCGAM
00215 !
00216 !-------------------------------------------------------------------------------
00217 !
00218 !*  4.        EXIT
00219 !             ----
00220 !
00221 END IF
00222 IF (LHOOK) CALL DR_HOOK('LATLONTOXY1D',1,ZHOOK_HANDLE)
00223 !-------------------------------------------------------------------------------
00224 END SUBROUTINE LATLONTOXY1D