The subroutine converts geodetic(latitude and longitude) coordinates to Gauss Boaga (easting and northing) coordinates, according to ROME40 datum for Italy (MonteMario) coordinates.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=float), | intent(inout) | :: | lon |
geodetic longitude [radians] |
||
real(kind=float), | intent(inout) | :: | lat |
geodetic latitude [radians] |
||
real(kind=float), | intent(in) | :: | k |
scale factor |
||
real(kind=float), | intent(in) | :: | centM |
central meridian [radians] |
||
real(kind=float), | intent(in) | :: | lat0 |
latitude of origin [radians] |
||
real(kind=float), | intent(in) | :: | a |
semimajor axis [m] |
||
real(kind=float), | intent(in) | :: | e |
eccentricity |
||
real(kind=float), | intent(in) | :: | eb |
second eccentricity |
||
real(kind=float), | intent(in) | :: | falseN |
false northing |
||
real(kind=float), | intent(in) | :: | falseE |
false easting |
||
real(kind=float), | intent(out) | :: | x |
easting coordinate [m] |
||
real(kind=float), | intent(out) | :: | y |
northing coordinate [m] |
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
real(kind=float), | public, | parameter | :: | MAX_LAT | = | 84.5*degToRad | |
real(kind=float), | public, | parameter | :: | MAX_NORTHING | = | 10000000. | |
real(kind=float), | public, | parameter | :: | MIN_LAT | = | -80.5*degToRad | |
real(kind=float), | public, | parameter | :: | MIN_NORTHING | = | 0. |
SUBROUTINE ConvertGeodeticToGaussBoaga & ! (lon, lat, k, centM, lat0, a, e, eb, falseN, falseE, x, y) USE Units, ONLY: & !Imported parametes: pi USE StringManipulation, ONLY: & !Imported routines: ToString IMPLICIT NONE ! Arguments with intent(in): REAL (KIND = float), INTENT (INOUT) :: lon !!geodetic longitude [radians] REAL (KIND = float), INTENT (INOUT) :: lat !!geodetic latitude [radians] REAL (KIND = float), INTENT (IN) :: k !!scale factor REAL (KIND = float), INTENT (IN) :: centM !!central meridian [radians] REAL (KIND = float), INTENT (IN) :: lat0 !!latitude of origin [radians] REAL (KIND = float), INTENT (IN) :: a !! semimajor axis [m] REAL (KIND = float), INTENT (IN) :: e !! eccentricity REAL (KIND = float), INTENT (IN) :: eb !! second eccentricity REAL (KIND = float), INTENT (IN) :: falseN !!false northing REAL (KIND = float), INTENT (IN) :: falseE !!false easting !Arguments with intent(out): REAL (KIND = float), INTENT (OUT) :: x !!easting coordinate [m] REAL (KIND = float), INTENT (OUT) :: y !!northing coordinate [m] !Local variables: REAL (KIND = float), PARAMETER :: MIN_LAT = -80.5 * degToRad ! -80.5 degrees in radians REAL (KIND = float), PARAMETER :: MAX_LAT = 84.5 * degToRad ! 84.5 degrees in radians REAL (KIND = float), PARAMETER :: MIN_NORTHING = 0. REAL (KIND = float), PARAMETER :: MAX_NORTHING = 10000000. !------------end of declaration------------------------------------------------ !check out of range IF ( lat < MIN_LAT .OR. lat > MAX_LAT ) THEN CALL Catch ('error', 'GeoLib', & 'Converting Geodetic to Gauss Boaga: & latitude out of range ' , & code = consistencyError, & argument = ToString(lat*radToDeg)//' deg' ) END IF IF ( lon < -pi .OR. lon > 2*pi ) THEN CALL Catch ('error', 'GeoLib', & 'Converting Geodetic to Gauss Boaga: & longitude out of range ' , & code = consistencyError, & argument = ToString(lon*radToDeg)//' deg' ) END IF IF ( lat > -1.0e-9 .AND. lat < 0. ) THEN lat = 0.0 END IF IF ( lon < 0. ) THEN lon = lon + 2.*pi + 1.0e-10 END IF CALL ConvertGeodeticToTransverseMercator (lon, lat, k, centM, lat0, a, e, eb, & falseN, falseE, x, y) !Check out of range IF ( y < MIN_NORTHING .OR. y > MAX_NORTHING ) THEN CALL Catch ('error', 'GeoLib', & 'Converting Geodetic to Gauss Boaga: & northing out of range' , & code = consistencyError, argument = ToString(y) ) END IF END SUBROUTINE ConvertGeodeticToGaussBoaga