Copyright | (C) 2014-2016 Hans-Christian Esperer |
---|---|
License | MIT |
Maintainer | Hans-Christian Esperer <hc@hcesperer.org> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Parse aviation weather reports. A qualified import is recommended.
Synopsis
- weatherParser :: (Monad f, CharParsing f) => f Weather
- data Weather
- = METAR {
- _reporttype :: ReportType
- _metardate :: Date
- _station :: Station
- _flags :: [Flag]
- _metarwind :: Maybe Wind
- _metarvisibility :: [Visibility]
- _runwayvis :: [(Runway, [Visibility], Maybe VisTrend)]
- _runwaycond :: [RunwayCondition]
- _wx :: [WeatherPhenomenon]
- _clouds :: [Cloud]
- _metarpressure :: Maybe Pressure
- _temperature :: Maybe Int
- _dewPoint :: Maybe Int
- _weathertrend :: [Trend]
- _remark :: Maybe Text
- _maintenance :: Bool
- | ATIS
- | SPECI
- | TAF {
- _reporttype :: ReportType
- _tafissuedat :: Date
- _flags :: [Flag]
- _station :: Station
- _tafvalidfrom :: Date
- _tafvaliduntil :: Date
- _tafinitialconditions :: [Transition]
- _tafchanges :: [Trend]
- | AIRMET
- | SIGMET
- | GAMET
- = METAR {
- class HasWeather c where
- weather :: Lens' c Weather
- clouds :: Traversal' c [Cloud]
- dewPoint :: Traversal' c (Maybe Int)
- flags :: Traversal' c [Flag]
- maintenance :: Traversal' c Bool
- metardate :: Traversal' c Date
- metarpressure :: Traversal' c (Maybe Pressure)
- metarvisibility :: Traversal' c [Visibility]
- metarwind :: Traversal' c (Maybe Wind)
- remark :: Traversal' c (Maybe Text)
- reporttype :: Traversal' c ReportType
- runwaycond :: Traversal' c [RunwayCondition]
- runwayvis :: Traversal' c [(Runway, [Visibility], Maybe VisTrend)]
- station :: Traversal' c Station
- tafchanges :: Traversal' c [Trend]
- tafinitialconditions :: Traversal' c [Transition]
- tafissuedat :: Traversal' c Date
- tafvalidfrom :: Traversal' c Date
- tafvaliduntil :: Traversal' c Date
- temperature :: Traversal' c (Maybe Int)
- weathertrend :: Traversal' c [Trend]
- wx :: Traversal' c [WeatherPhenomenon]
- class AsWeather r where
- _Weather :: Prism' r Weather
- _METAR :: Prism' r (ReportType, Date, Station, [Flag], Maybe Wind, [Visibility], [(Runway, [Visibility], Maybe VisTrend)], [RunwayCondition], [WeatherPhenomenon], [Cloud], Maybe Pressure, Maybe Int, Maybe Int, [Trend], Maybe Text, Bool)
- _ATIS :: Prism' r ()
- _SPECI :: Prism' r ()
- _TAF :: Prism' r (ReportType, Date, [Flag], Station, Date, Date, [Transition], [Trend])
- _AIRMET :: Prism' r ()
- _SIGMET :: Prism' r ()
- _GAMET :: Prism' r ()
- data Date = Date {}
- class HasDate c where
- newtype Station = ICAO Text
- data Flag
- class HasFlag c where
- class AsFlag r where
- data Wind = Wind {}
- class HasWind c where
- data Visibility
- class HasVisibility c where
- visibility :: Lens' c Visibility
- class AsVisibility r where
- _Visibility :: Prism' r Visibility
- _TenOrMore :: Prism' r ()
- _FiftyMetresOrLess :: Prism' r ()
- _TwoOrMore :: Prism' r ()
- _SpecificVisibility :: Prism' r (Distance, Maybe Direction)
- data Runway
- = AllRunways
- | SpecificRunway { }
- class HasRunway c where
- runway :: Lens' c Runway
- runwayDirection :: Traversal' c (Maybe Direction)
- runwayQFU :: Traversal' c Int
- class AsRunway r where
- _Runway :: Prism' r Runway
- _AllRunways :: Prism' r ()
- _SpecificRunway :: Prism' r (Int, Maybe Direction)
- data VisTrend
- class HasVisTrend c where
- class AsVisTrend r where
- _VisTrend :: Prism' r VisTrend
- _VisTrendUpward :: Prism' r ()
- _VisTrendDownward :: Prism' r ()
- _VisTrendNoDistinctTendency :: Prism' r ()
- data RunwayCondition
- class HasRunwayCondition c where
- class AsRunwayCondition r where
- _RunwayCondition :: Prism' r RunwayCondition
- _SpecificRunwayCondition :: Prism' r (Runway, RwyCoverType, Maybe Int, Maybe Int, RunwayBraking)
- _RwyClosed :: Prism' r Runway
- _ADClosed :: Prism' r ()
- data WeatherPhenomenon = Phenomenon {}
- class HasWeatherPhenomenon c where
- weatherPhenomenon :: Lens' c WeatherPhenomenon
- desc :: Lens' c (Maybe WPDesc)
- intensity :: Lens' c WPIntensity
- obfus :: Lens' c (Maybe WPObfuscation)
- other :: Lens' c (Maybe WPOther)
- prec :: Lens' c (Maybe WPPrecipitation)
- data Cloud
- class HasCloud c where
- class AsCloud r where
- data Pressure
- class HasPressure c where
- class AsPressure r where
- data Trend
- = BECMG { }
- | TEMPO {
- _tempoFrom :: Maybe Date
- _tempoTo :: Maybe Date
- _tempoTransitions :: [Transition]
- | PROB Int Trend
- | NOSIG
- | NOTAVAIL
- class HasTrend c where
- trend :: Lens' c Trend
- becmgFinished :: Traversal' c (Maybe Date)
- becmgStart :: Traversal' c (Maybe Date)
- becmgTransitions :: Traversal' c [Transition]
- tempoFrom :: Traversal' c (Maybe Date)
- tempoTo :: Traversal' c (Maybe Date)
- tempoTransitions :: Traversal' c [Transition]
- class AsTrend r where
- data WPDesc
- class HasWPDesc c where
- class AsWPDesc r where
- data WPPrecipitation
- class HasWPPrecipitation c where
- class AsWPPrecipitation r where
- _WPPrecipitation :: Prism' r WPPrecipitation
- _Drizzle :: Prism' r ()
- _Rain :: Prism' r ()
- _Snow :: Prism' r ()
- _ShowGrains :: Prism' r ()
- _IceCrystals :: Prism' r ()
- _IcePellets :: Prism' r ()
- _Hail :: Prism' r ()
- _SnowPellets :: Prism' r ()
- _NoPrecipitationDetected :: Prism' r ()
- _UnknownPrecipitation :: Prism' r ()
- data WPObfuscation
- class HasWPObfuscation c where
- class AsWPObfuscation r where
- data WPOther
- class HasWPOther c where
- class AsWPOther r where
- _WPOther :: Prism' r WPOther
- _DustOrSandwhirls :: Prism' r ()
- _Squalls :: Prism' r ()
- _Tornado :: Prism' r ()
- _Sandstorm :: Prism' r ()
- _Duststorm :: Prism' r ()
- data Distance
- class HasDistance c where
- class AsDistance r where
- data Direction
- class HasDirection c where
- class AsDirection r where
- _Direction :: Prism' r Direction
- _North :: Prism' r ()
- _South :: Prism' r ()
- _East :: Prism' r ()
- _West :: Prism' r ()
- _NorthWest :: Prism' r ()
- _NorthEast :: Prism' r ()
- _SouthWest :: Prism' r ()
- _SouthEast :: Prism' r ()
- _NDV :: Prism' r ()
- _RWYLeft :: Prism' r ()
- _RWYRight :: Prism' r ()
- _RWYCenter :: Prism' r ()
- data RwyCoverType
- = RCTDry
- | RCTMoist
- | RCTWet
- | RCTRime
- | RCTDrySnow
- | RCTWetSnow
- | RCTSlush
- | RCTIce
- | RCTFZRut
- | RCTUnknown
- class HasRwyCoverType c where
- class AsRwyCoverType r where
- _RwyCoverType :: Prism' r RwyCoverType
- _RCTDry :: Prism' r ()
- _RCTMoist :: Prism' r ()
- _RCTWet :: Prism' r ()
- _RCTRime :: Prism' r ()
- _RCTDrySnow :: Prism' r ()
- _RCTWetSnow :: Prism' r ()
- _RCTSlush :: Prism' r ()
- _RCTIce :: Prism' r ()
- _RCTFZRut :: Prism' r ()
- _RCTUnknown :: Prism' r ()
- data RunwayBraking
- class HasRunwayBraking c where
- class AsRunwayBraking r where
- _RunwayBraking :: Prism' r RunwayBraking
- _BrakingFriction :: Prism' r Int
- _BrakingEffect :: Prism' r Int
- data Vertical
- class HasVertical c where
- class AsVertical r where
- data WindDirection
- class HasWindDirection c where
- windDirection :: Lens' c WindDirection
- windfrom :: Traversal' c Int
- windmean :: Traversal' c Int
- windto :: Traversal' c Int
- class AsWindDirection r where
- data Cover
- = FEW
- | SCT
- | BKN
- | OVC
- | CoverNotSpecified
- class HasCover c where
- class AsCover r where
- data CloudType
- class HasCloudType c where
- class AsCloudType r where
- _CloudType :: Prism' r CloudType
- _Cumulonimbus :: Prism' r ()
- _ToweringCumulus :: Prism' r ()
- _Stratus :: Prism' r ()
- _Cumulus :: Prism' r ()
- _Stratocumulus :: Prism' r ()
- _Altostratus :: Prism' r ()
- _Altocumulus :: Prism' r ()
- _Cirrostratus :: Prism' r ()
- _Cirrus :: Prism' r ()
- _Unclassified :: Prism' r ()
- data WPIntensity
- class HasWPIntensity c where
- wPIntensity :: Lens' c WPIntensity
- class AsWPIntensity r where
- data Transition
- = TransWind Wind
- | TransVis [Visibility]
- | TransRunwayVis [(Runway, [Visibility], Maybe VisTrend)]
- | TransWX [WeatherPhenomenon]
- | TransClouds [Cloud]
- | TransPressure [Pressure]
- class HasTransition c where
- transition :: Lens' c Transition
- class AsTransition r where
- _Transition :: Prism' r Transition
- _TransWind :: Prism' r Wind
- _TransVis :: Prism' r [Visibility]
- _TransRunwayVis :: Prism' r [(Runway, [Visibility], Maybe VisTrend)]
- _TransWX :: Prism' r [WeatherPhenomenon]
- _TransClouds :: Prism' r [Cloud]
- _TransPressure :: Prism' r [Pressure]
- data Unit
- class HasUnit c where
- class AsUnit r where
- data ReportType
Documentation
weatherParser :: (Monad f, CharParsing f) => f Weather Source #
An attoparsec parser that can parse METAR messages.
Aviation weather, currently only METARs and TAFs are supported.
METAR | A METeorological Aerodrome Report |
| |
ATIS | An automatic terminal information service report |
SPECI | A non-scheduled METAR |
TAF | A terminal aerodrome forecast |
| |
AIRMET | An aviation wx hazard message of moderate severity |
SIGMET | A significant meteorological information message |
GAMET | A general aviation forecast message |
Instances
class HasWeather c where Source #
weather :: Lens' c Weather Source #
clouds :: Traversal' c [Cloud] Source #
dewPoint :: Traversal' c (Maybe Int) Source #
flags :: Traversal' c [Flag] Source #
maintenance :: Traversal' c Bool Source #
metardate :: Traversal' c Date Source #
metarpressure :: Traversal' c (Maybe Pressure) Source #
metarvisibility :: Traversal' c [Visibility] Source #
metarwind :: Traversal' c (Maybe Wind) Source #
remark :: Traversal' c (Maybe Text) Source #
reporttype :: Traversal' c ReportType Source #
runwaycond :: Traversal' c [RunwayCondition] Source #
runwayvis :: Traversal' c [(Runway, [Visibility], Maybe VisTrend)] Source #
station :: Traversal' c Station Source #
tafchanges :: Traversal' c [Trend] Source #
tafinitialconditions :: Traversal' c [Transition] Source #
tafissuedat :: Traversal' c Date Source #
tafvalidfrom :: Traversal' c Date Source #
tafvaliduntil :: Traversal' c Date Source #
temperature :: Traversal' c (Maybe Int) Source #
weathertrend :: Traversal' c [Trend] Source #
wx :: Traversal' c [WeatherPhenomenon] Source #
Instances
class AsWeather r where Source #
_Weather :: Prism' r Weather Source #
_METAR :: Prism' r (ReportType, Date, Station, [Flag], Maybe Wind, [Visibility], [(Runway, [Visibility], Maybe VisTrend)], [RunwayCondition], [WeatherPhenomenon], [Cloud], Maybe Pressure, Maybe Int, Maybe Int, [Trend], Maybe Text, Bool) Source #
_SPECI :: Prism' r () Source #
_TAF :: Prism' r (ReportType, Date, [Flag], Station, Date, Date, [Transition], [Trend]) Source #
_AIRMET :: Prism' r () Source #
Instances
AsWeather Weather Source # | |
Defined in Data.Aviation.WX _Weather :: Prism' Weather Weather Source # _METAR :: Prism' Weather (ReportType, Date, Station, [Flag], Maybe Wind, [Visibility], [(Runway, [Visibility], Maybe VisTrend)], [RunwayCondition], [WeatherPhenomenon], [Cloud], Maybe Pressure, Maybe Int, Maybe Int, [Trend], Maybe Text, Bool) Source # _ATIS :: Prism' Weather () Source # _SPECI :: Prism' Weather () Source # _TAF :: Prism' Weather (ReportType, Date, [Flag], Station, Date, Date, [Transition], [Trend]) Source # _AIRMET :: Prism' Weather () Source # |
An aeronautical weather station designator.
A flag describing an aviation meteorological report
COR | A message has been corrected after the beginning of its original validity period |
AMD | A message has been corrected prior to its original validity period |
AUTO | A message has been generated fully automatic without a plausibility check by a human |
Wind information.
Wind | |
|
data Visibility Source #
Vertical visibility.
TenOrMore | Ten kilometres or more. This is also used for P6SM which means 6 statute miles or more. Do note that 6SM is a little less than 10km (9.6km) |
FiftyMetresOrLess | Fifty metres or less. |
TwoOrMore | Two kilometres or more. |
SpecificVisibility Distance (Maybe Direction) | A specific visibility. |
Instances
Eq Visibility Source # | |
Defined in Data.Aviation.WX (==) :: Visibility -> Visibility -> Bool # (/=) :: Visibility -> Visibility -> Bool # | |
Show Visibility Source # | |
Defined in Data.Aviation.WX showsPrec :: Int -> Visibility -> ShowS # show :: Visibility -> String # showList :: [Visibility] -> ShowS # | |
HasVisibility Visibility Source # | |
Defined in Data.Aviation.WX | |
AsVisibility Visibility Source # | |
Defined in Data.Aviation.WX |
class HasVisibility c where Source #
visibility :: Lens' c Visibility Source #
Instances
HasVisibility Visibility Source # | |
Defined in Data.Aviation.WX |
class AsVisibility r where Source #
_Visibility :: Prism' r Visibility Source #
_TenOrMore :: Prism' r () Source #
_FiftyMetresOrLess :: Prism' r () Source #
_TwoOrMore :: Prism' r () Source #
_SpecificVisibility :: Prism' r (Distance, Maybe Direction) Source #
Instances
AsVisibility Visibility Source # | |
Defined in Data.Aviation.WX |
Runway specification.
AllRunways | All runways. |
SpecificRunway | A specific runway. |
|
A visibility trend specifically for runway conditions
VisTrendUpward | Visibility will improve (maybe do wait a bit) |
VisTrendDownward | Visibility will deteriorate (still, don't rush the take off and use proper phraseology at all times) |
VisTrendNoDistinctTendency | No expected change in runway visibility conditions |
class HasVisTrend c where Source #
class AsVisTrend r where Source #
data RunwayCondition Source #
Runway conditions.
SpecificRunwayCondition | Specific runway conditions exist. |
| |
RwyClosed | The runway is closed. |
| |
ADClosed | The whole aerodrome is closed. |
Instances
Eq RunwayCondition Source # | |
Defined in Data.Aviation.WX (==) :: RunwayCondition -> RunwayCondition -> Bool # (/=) :: RunwayCondition -> RunwayCondition -> Bool # | |
Show RunwayCondition Source # | |
Defined in Data.Aviation.WX showsPrec :: Int -> RunwayCondition -> ShowS # show :: RunwayCondition -> String # showList :: [RunwayCondition] -> ShowS # | |
HasRunwayCondition RunwayCondition Source # | |
Defined in Data.Aviation.WX runwayCondition :: Lens' RunwayCondition RunwayCondition Source # rwclosedRunway :: Traversal' RunwayCondition Runway Source # rwcondBrkCoeff :: Traversal' RunwayCondition RunwayBraking Source # rwcondCover :: Traversal' RunwayCondition RwyCoverType Source # rwcondCoverHeight :: Traversal' RunwayCondition (Maybe Int) Source # rwcondRunway :: Traversal' RunwayCondition Runway Source # rwcondSpread :: Traversal' RunwayCondition (Maybe Int) Source # | |
AsRunwayCondition RunwayCondition Source # | |
Defined in Data.Aviation.WX |
class HasRunwayCondition c where Source #
runwayCondition :: Lens' c RunwayCondition Source #
rwclosedRunway :: Traversal' c Runway Source #
rwcondBrkCoeff :: Traversal' c RunwayBraking Source #
rwcondCover :: Traversal' c RwyCoverType Source #
rwcondCoverHeight :: Traversal' c (Maybe Int) Source #
rwcondRunway :: Traversal' c Runway Source #
rwcondSpread :: Traversal' c (Maybe Int) Source #
Instances
class AsRunwayCondition r where Source #
_RunwayCondition :: Prism' r RunwayCondition Source #
_SpecificRunwayCondition :: Prism' r (Runway, RwyCoverType, Maybe Int, Maybe Int, RunwayBraking) Source #
_RwyClosed :: Prism' r Runway Source #
Instances
AsRunwayCondition RunwayCondition Source # | |
Defined in Data.Aviation.WX |
data WeatherPhenomenon Source #
A weather phenomenon. This can be an observed phenomenon in the case of METARs or an expected phenomenon in the case of TAFs.
Phenomenon | |
|
Instances
Eq WeatherPhenomenon Source # | |
Defined in Data.Aviation.WX (==) :: WeatherPhenomenon -> WeatherPhenomenon -> Bool # (/=) :: WeatherPhenomenon -> WeatherPhenomenon -> Bool # | |
Show WeatherPhenomenon Source # | |
Defined in Data.Aviation.WX showsPrec :: Int -> WeatherPhenomenon -> ShowS # show :: WeatherPhenomenon -> String # showList :: [WeatherPhenomenon] -> ShowS # | |
HasWeatherPhenomenon WeatherPhenomenon Source # | |
Defined in Data.Aviation.WX weatherPhenomenon :: Lens' WeatherPhenomenon WeatherPhenomenon Source # desc :: Lens' WeatherPhenomenon (Maybe WPDesc) Source # intensity :: Lens' WeatherPhenomenon WPIntensity Source # obfus :: Lens' WeatherPhenomenon (Maybe WPObfuscation) Source # other :: Lens' WeatherPhenomenon (Maybe WPOther) Source # prec :: Lens' WeatherPhenomenon (Maybe WPPrecipitation) Source # | |
HasWPIntensity WeatherPhenomenon Source # | |
Defined in Data.Aviation.WX |
class HasWeatherPhenomenon c where Source #
weatherPhenomenon :: Lens' c WeatherPhenomenon Source #
desc :: Lens' c (Maybe WPDesc) Source #
intensity :: Lens' c WPIntensity Source #
obfus :: Lens' c (Maybe WPObfuscation) Source #
Instances
A cloud specification.
VVis (Maybe Int) | No specific clouds could be observed, because the (given) ground visibility was too low or because the ground is covered in clouds. |
ObservedCloud Cover Vertical CloudType | Clouds were observed. |
A pressure value. This is intentionally coded individually and not converted to a specific reference.
QNH Int | The QNH value in hectopascals. QNH is the current pressure at sea level, corrected for pressure and temperature changes at the station level. |
Altimeter Int | The same as QNH, only in inches (Do you know the old joke?: * ATC: Liner 1723 descend to 3,000ft, the QNH is 1013mb. * Liner 1723: Uh, approach, can we have that in inches please? * ATC: Liner 1723 descend to 36,000 inches, the QNH is 1013mb. |
QFE Int | The current pressure at station level in hectopascals. |
QFF Int | The current pressure at sea level in hectopascals. |
class HasPressure c where Source #
class AsPressure r where Source #
The trend part of an observation message specifies expected changes in weather conditions within the next two hours. A Trend/Transition part of a TAF message specified expected changes in weather conditions within the specified range.
BECMG | A transition that will start within the defined time frame and be completed at the end of the defined time frame |
| |
TEMPO | A transition that will start within the defined time frame and be finished at the end of the defined time frame |
| |
PROB Int Trend | A probability specification. As one of my FIs (ex-atc at EDDF) used to put it: 30% means "I'm quite sure it won't happen but will still put it in here, in case it does after all." 40% means "I'm certain it will happen but will still put it with 40%, in case it does not happen after all." |
NOSIG | NOSIG is only applicable to METARs. It means that no significant changes are expected within the next two hours. |
NOTAVAIL | NOTAVAIL is only applicable to METARs. It means that the METAR message in question does not contain a TREND section. |
Instances
Eq Trend Source # | |
Show Trend Source # | |
HasTrend Trend Source # | |
Defined in Data.Aviation.WX trend :: Lens' Trend Trend Source # becmgFinished :: Traversal' Trend (Maybe Date) Source # becmgStart :: Traversal' Trend (Maybe Date) Source # becmgTransitions :: Traversal' Trend [Transition] Source # tempoFrom :: Traversal' Trend (Maybe Date) Source # | |
AsTrend Trend Source # | |
Defined in Data.Aviation.WX |
class HasTrend c where Source #
trend :: Lens' c Trend Source #
becmgFinished :: Traversal' c (Maybe Date) Source #
becmgStart :: Traversal' c (Maybe Date) Source #
becmgTransitions :: Traversal' c [Transition] Source #
tempoFrom :: Traversal' c (Maybe Date) Source #
tempoTo :: Traversal' c (Maybe Date) Source #
tempoTransitions :: Traversal' c [Transition] Source #
Instances
HasTrend Trend Source # | |
Defined in Data.Aviation.WX trend :: Lens' Trend Trend Source # becmgFinished :: Traversal' Trend (Maybe Date) Source # becmgStart :: Traversal' Trend (Maybe Date) Source # becmgTransitions :: Traversal' Trend [Transition] Source # tempoFrom :: Traversal' Trend (Maybe Date) Source # |
class AsTrend r where Source #
_Trend :: Prism' r Trend Source #
_BECMG :: Prism' r (Maybe Date, Maybe Date, [Transition]) Source #
_TEMPO :: Prism' r (Maybe Date, Maybe Date, [Transition]) Source #
_PROB :: Prism' r (Int, Trend) Source #
Instances
AsTrend Trend Source # | |
Defined in Data.Aviation.WX |
The description of a weather phenomenon.
Shallow | Shallow. |
Patches | Patches. |
WXPartial | Partial. |
LowDrifting | Low, drifting. |
Blowing | Blowing. |
Shower | Shower. |
Thunderstorm | Thunderstorm. |
Freezing | Freezing. |
Instances
Enum WPDesc Source # | |
Defined in Data.Aviation.WX | |
Eq WPDesc Source # | |
Ord WPDesc Source # | |
Show WPDesc Source # | |
HasWPDesc WPDesc Source # | |
AsWPDesc WPDesc Source # | |
Defined in Data.Aviation.WX _WPDesc :: Prism' WPDesc WPDesc Source # _Shallow :: Prism' WPDesc () Source # _Patches :: Prism' WPDesc () Source # _WXPartial :: Prism' WPDesc () Source # _LowDrifting :: Prism' WPDesc () Source # _Blowing :: Prism' WPDesc () Source # _Shower :: Prism' WPDesc () Source # _Thunderstorm :: Prism' WPDesc () Source # |
class AsWPDesc r where Source #
_WPDesc :: Prism' r WPDesc Source #
_Shallow :: Prism' r () Source #
_Patches :: Prism' r () Source #
_WXPartial :: Prism' r () Source #
_LowDrifting :: Prism' r () Source #
_Blowing :: Prism' r () Source #
_Shower :: Prism' r () Source #
_Thunderstorm :: Prism' r () Source #
Instances
AsWPDesc WPDesc Source # | |
Defined in Data.Aviation.WX _WPDesc :: Prism' WPDesc WPDesc Source # _Shallow :: Prism' WPDesc () Source # _Patches :: Prism' WPDesc () Source # _WXPartial :: Prism' WPDesc () Source # _LowDrifting :: Prism' WPDesc () Source # _Blowing :: Prism' WPDesc () Source # _Shower :: Prism' WPDesc () Source # _Thunderstorm :: Prism' WPDesc () Source # |
data WPPrecipitation Source #
The type of the precipitation
Drizzle | Drizzle. |
Rain | Rain. |
Snow | Snow. |
ShowGrains | Snow grains. |
IceCrystals | Ice crystals. |
IcePellets | Ice pellets. |
Hail | Hail. |
SnowPellets | Snow pellets. |
NoPrecipitationDetected | No precipication detected (fully automated measurement) |
UnknownPrecipitation | Unknown type of precipitation. |
Instances
class HasWPPrecipitation c where Source #
Instances
HasWPPrecipitation WPPrecipitation Source # | |
Defined in Data.Aviation.WX |
class AsWPPrecipitation r where Source #
_WPPrecipitation :: Prism' r WPPrecipitation Source #
_Drizzle :: Prism' r () Source #
_ShowGrains :: Prism' r () Source #
_IceCrystals :: Prism' r () Source #
_IcePellets :: Prism' r () Source #
_SnowPellets :: Prism' r () Source #
_NoPrecipitationDetected :: Prism' r () Source #
_UnknownPrecipitation :: Prism' r () Source #
Instances
data WPObfuscation Source #
Effects on the visibility by a weather phenomenon
Mist | Mist. Visibility impaired but still greater than 1000m |
Fog | Fog. Visibility less than 1000m. |
Smoke | Smoke. |
VolcanicAsh | Volcanic ash. |
Dust | Dust. |
Sand | Sand. |
Haze | Haze. |
Instances
class HasWPObfuscation c where Source #
Instances
HasWPObfuscation WPObfuscation Source # | |
Defined in Data.Aviation.WX |
class AsWPObfuscation r where Source #
_WPObfuscation :: Prism' r WPObfuscation Source #
_Smoke :: Prism' r () Source #
_VolcanicAsh :: Prism' r () Source #
Instances
AsWPObfuscation WPObfuscation Source # | |
Defined in Data.Aviation.WX _WPObfuscation :: Prism' WPObfuscation WPObfuscation Source # _Mist :: Prism' WPObfuscation () Source # _Fog :: Prism' WPObfuscation () Source # _Smoke :: Prism' WPObfuscation () Source # _VolcanicAsh :: Prism' WPObfuscation () Source # _Dust :: Prism' WPObfuscation () Source # _Sand :: Prism' WPObfuscation () Source # _Haze :: Prism' WPObfuscation () Source # |
Other important information about a weather phenomenon.
DustOrSandwhirls | Dust or sand whirls. |
Squalls | Squalls. |
Tornado | Tornado. |
Sandstorm | Sand storm. |
Duststorm | Dust storm. |
Instances
Enum WPOther Source # | |
Eq WPOther Source # | |
Ord WPOther Source # | |
Show WPOther Source # | |
HasWPOther WPOther Source # | |
AsWPOther WPOther Source # | |
class HasWPOther c where Source #
class AsWPOther r where Source #
_WPOther :: Prism' r WPOther Source #
_DustOrSandwhirls :: Prism' r () Source #
_Squalls :: Prism' r () Source #
_Tornado :: Prism' r () Source #
_Sandstorm :: Prism' r () Source #
_Duststorm :: Prism' r () Source #
The Distance.
Metres Int | The distance in metres. |
KM Int | The distance in km. |
SM Int | The distance in statute miles. |
NM Int | The distance in nautical miles. |
class HasDistance c where Source #
class AsDistance r where Source #
Directions.
North | North. |
South | South. |
East | East. |
West | West. |
NorthWest | Northwest. |
NorthEast | Northeast. |
SouthWest | Southwest. |
SouthEast | Southeast. |
NDV | No direction could be determined |
RWYLeft | Left runway for runways of the same QFU (part of the runway designator) |
RWYRight | Right runway for runways of the same QFU (part of the runway designator) |
RWYCenter | Centre runway for runways of the same QFU (part of the runway designator) |
Instances
Eq Direction Source # | |
Show Direction Source # | |
HasDirection Direction Source # | |
AsDirection Direction Source # | |
Defined in Data.Aviation.WX _Direction :: Prism' Direction Direction Source # _North :: Prism' Direction () Source # _South :: Prism' Direction () Source # _East :: Prism' Direction () Source # _West :: Prism' Direction () Source # _NorthWest :: Prism' Direction () Source # _NorthEast :: Prism' Direction () Source # _SouthWest :: Prism' Direction () Source # _SouthEast :: Prism' Direction () Source # _NDV :: Prism' Direction () Source # _RWYLeft :: Prism' Direction () Source # _RWYRight :: Prism' Direction () Source # _RWYCenter :: Prism' Direction () Source # |
class HasDirection c where Source #
class AsDirection r where Source #
_Direction :: Prism' r Direction Source #
_North :: Prism' r () Source #
_South :: Prism' r () Source #
_NorthWest :: Prism' r () Source #
_NorthEast :: Prism' r () Source #
_SouthWest :: Prism' r () Source #
_SouthEast :: Prism' r () Source #
_RWYLeft :: Prism' r () Source #
_RWYRight :: Prism' r () Source #
_RWYCenter :: Prism' r () Source #
Instances
AsDirection Direction Source # | |
Defined in Data.Aviation.WX _Direction :: Prism' Direction Direction Source # _North :: Prism' Direction () Source # _South :: Prism' Direction () Source # _East :: Prism' Direction () Source # _West :: Prism' Direction () Source # _NorthWest :: Prism' Direction () Source # _NorthEast :: Prism' Direction () Source # _SouthWest :: Prism' Direction () Source # _SouthEast :: Prism' Direction () Source # _NDV :: Prism' Direction () Source # _RWYLeft :: Prism' Direction () Source # _RWYRight :: Prism' Direction () Source # _RWYCenter :: Prism' Direction () Source # |
data RwyCoverType Source #
The runway contamination type.
RCTDry | The runway is not contaminated. |
RCTMoist | The runway is moist. |
RCTWet | The runway is wet. |
RCTRime | The runway is convered with rime. |
RCTDrySnow | The runway is covered with dry snow. |
RCTWetSnow | The runway is covered with wet snow. |
RCTSlush | The runway is covered with slush. |
RCTIce | The runway is covered with ice. |
RCTFZRut | The runway is covered with frozen ruts or ridges. |
RCTUnknown | The runway contamination type is unknown. |
Instances
class HasRwyCoverType c where Source #
rwyCoverType :: Lens' c RwyCoverType Source #
Instances
HasRwyCoverType RwyCoverType Source # | |
Defined in Data.Aviation.WX |
class AsRwyCoverType r where Source #
_RwyCoverType :: Prism' r RwyCoverType Source #
_RCTDry :: Prism' r () Source #
_RCTMoist :: Prism' r () Source #
_RCTWet :: Prism' r () Source #
_RCTRime :: Prism' r () Source #
_RCTDrySnow :: Prism' r () Source #
_RCTWetSnow :: Prism' r () Source #
_RCTSlush :: Prism' r () Source #
_RCTIce :: Prism' r () Source #
_RCTFZRut :: Prism' r () Source #
_RCTUnknown :: Prism' r () Source #
Instances
AsRwyCoverType RwyCoverType Source # | |
Defined in Data.Aviation.WX _RwyCoverType :: Prism' RwyCoverType RwyCoverType Source # _RCTDry :: Prism' RwyCoverType () Source # _RCTMoist :: Prism' RwyCoverType () Source # _RCTWet :: Prism' RwyCoverType () Source # _RCTRime :: Prism' RwyCoverType () Source # _RCTDrySnow :: Prism' RwyCoverType () Source # _RCTWetSnow :: Prism' RwyCoverType () Source # _RCTSlush :: Prism' RwyCoverType () Source # _RCTIce :: Prism' RwyCoverType () Source # _RCTFZRut :: Prism' RwyCoverType () Source # _RCTUnknown :: Prism' RwyCoverType () Source # |
data RunwayBraking Source #
The measured brake efficiency of a specific runway.
BrakingFriction Int | The friction coefficient. |
BrakingEffect Int | The braking coefficient. |
Instances
Eq RunwayBraking Source # | |
Defined in Data.Aviation.WX (==) :: RunwayBraking -> RunwayBraking -> Bool # (/=) :: RunwayBraking -> RunwayBraking -> Bool # | |
Show RunwayBraking Source # | |
Defined in Data.Aviation.WX showsPrec :: Int -> RunwayBraking -> ShowS # show :: RunwayBraking -> String # showList :: [RunwayBraking] -> ShowS # | |
HasRunwayBraking RunwayBraking Source # | |
Defined in Data.Aviation.WX | |
AsRunwayBraking RunwayBraking Source # | |
class HasRunwayBraking c where Source #
Instances
HasRunwayBraking RunwayBraking Source # | |
Defined in Data.Aviation.WX |
class AsRunwayBraking r where Source #
_RunwayBraking :: Prism' r RunwayBraking Source #
_BrakingFriction :: Prism' r Int Source #
_BrakingEffect :: Prism' r Int Source #
Instances
AsRunwayBraking RunwayBraking Source # | |
A vertical position specification.
Height Int | A vertical position with reference to the ground in feet. |
Altitude Int | A vertical position with reference to the mean sea level/QNH in feet. |
FlightLevel Int | A pressure altitude with reference to the standard QNH of 1013 hectopascals in hundrets of feet. |
VertNotSpec | Vertical position is not specified. |
class HasVertical c where Source #
class AsVertical r where Source #
data WindDirection Source #
The direction the wind is blowing from.
Variable | The wind is blowing in equal or almost equal strength from a wide variety of directions. |
Degrees Int | The wind is blowing from the specified direction. Directions can be given with reference to true or magnetic north, depending on the type of weather observation/forecast message. |
Varying | The wind is blowing from a specific direction range. |
Instances
Eq WindDirection Source # | |
Defined in Data.Aviation.WX (==) :: WindDirection -> WindDirection -> Bool # (/=) :: WindDirection -> WindDirection -> Bool # | |
Show WindDirection Source # | |
Defined in Data.Aviation.WX showsPrec :: Int -> WindDirection -> ShowS # show :: WindDirection -> String # showList :: [WindDirection] -> ShowS # | |
HasWindDirection WindDirection Source # | |
AsWindDirection WindDirection Source # | |
Defined in Data.Aviation.WX |
class HasWindDirection c where Source #
windDirection :: Lens' c WindDirection Source #
windfrom :: Traversal' c Int Source #
windmean :: Traversal' c Int Source #
windto :: Traversal' c Int Source #
Instances
HasWindDirection WindDirection Source # | |
class AsWindDirection r where Source #
_WindDirection :: Prism' r WindDirection Source #
_Variable :: Prism' r () Source #
Instances
AsWindDirection WindDirection Source # | |
Defined in Data.Aviation.WX |
The area that is covered.
FEW | 1-2 eights are covered. |
SCT | 3-4 eights are covered. |
BKN | 5-7 eights are covered. |
OVC | More than 7 eights are covered. |
CoverNotSpecified | Cover not specified |
The type of cloud.
Cumulonimbus | A cumulonimbus cloud. |
ToweringCumulus | A developing cb cloud. |
Stratus | A stratus cloud. |
Cumulus | A cumulus cloud. |
Stratocumulus | A stratocumulus cloud. |
Altostratus | An altostratus cloud. |
Altocumulus | An altocumulus cloud. |
Cirrostratus | A cirrostratus cloud. |
Cirrus | A cirrus cloud. |
Unclassified | An unclassified cloud. |
Instances
Enum CloudType Source # | |
Defined in Data.Aviation.WX succ :: CloudType -> CloudType # pred :: CloudType -> CloudType # fromEnum :: CloudType -> Int # enumFrom :: CloudType -> [CloudType] # enumFromThen :: CloudType -> CloudType -> [CloudType] # enumFromTo :: CloudType -> CloudType -> [CloudType] # enumFromThenTo :: CloudType -> CloudType -> CloudType -> [CloudType] # | |
Eq CloudType Source # | |
Show CloudType Source # | |
HasCloudType CloudType Source # | |
AsCloudType CloudType Source # | |
Defined in Data.Aviation.WX _CloudType :: Prism' CloudType CloudType Source # _Cumulonimbus :: Prism' CloudType () Source # _ToweringCumulus :: Prism' CloudType () Source # _Stratus :: Prism' CloudType () Source # _Cumulus :: Prism' CloudType () Source # _Stratocumulus :: Prism' CloudType () Source # _Altostratus :: Prism' CloudType () Source # _Altocumulus :: Prism' CloudType () Source # _Cirrostratus :: Prism' CloudType () Source # _Cirrus :: Prism' CloudType () Source # _Unclassified :: Prism' CloudType () Source # |
class HasCloudType c where Source #
class AsCloudType r where Source #
_CloudType :: Prism' r CloudType Source #
_Cumulonimbus :: Prism' r () Source #
_ToweringCumulus :: Prism' r () Source #
_Stratus :: Prism' r () Source #
_Cumulus :: Prism' r () Source #
_Stratocumulus :: Prism' r () Source #
_Altostratus :: Prism' r () Source #
_Altocumulus :: Prism' r () Source #
_Cirrostratus :: Prism' r () Source #
_Cirrus :: Prism' r () Source #
_Unclassified :: Prism' r () Source #
Instances
AsCloudType CloudType Source # | |
Defined in Data.Aviation.WX _CloudType :: Prism' CloudType CloudType Source # _Cumulonimbus :: Prism' CloudType () Source # _ToweringCumulus :: Prism' CloudType () Source # _Stratus :: Prism' CloudType () Source # _Cumulus :: Prism' CloudType () Source # _Stratocumulus :: Prism' CloudType () Source # _Altostratus :: Prism' CloudType () Source # _Altocumulus :: Prism' CloudType () Source # _Cirrostratus :: Prism' CloudType () Source # _Cirrus :: Prism' CloudType () Source # _Unclassified :: Prism' CloudType () Source # |
data WPIntensity Source #
The intensity of an observed or expected weather phenomenon.
Light | Light |
Moderate | Moderate |
Heavy | Heavy |
Vicinity | Only applicable to METARs. The weather phenomenon was observed in the vicinity of the observed area, not within the observed area itself. |
Recent | Only applicable to METARs. The weather phenomenon was recently observed in the past, but was not observed at the time the report was issued. |
Instances
class HasWPIntensity c where Source #
wPIntensity :: Lens' c WPIntensity Source #
Instances
HasWPIntensity WPIntensity Source # | |
Defined in Data.Aviation.WX | |
HasWPIntensity WeatherPhenomenon Source # | |
Defined in Data.Aviation.WX |
class AsWPIntensity r where Source #
_WPIntensity :: Prism' r WPIntensity Source #
_Light :: Prism' r () Source #
_Moderate :: Prism' r () Source #
_Heavy :: Prism' r () Source #
Instances
AsWPIntensity WPIntensity Source # | |
Defined in Data.Aviation.WX _WPIntensity :: Prism' WPIntensity WPIntensity Source # _Light :: Prism' WPIntensity () Source # _Moderate :: Prism' WPIntensity () Source # _Heavy :: Prism' WPIntensity () Source # _Vicinity :: Prism' WPIntensity () Source # _Recent :: Prism' WPIntensity () Source # |
data Transition Source #
A transition in weather conditions. A transition can either be temporary or permanent; this will be encoded in the container structure.
TransWind Wind | A change of wind strength or direction |
TransVis [Visibility] | A change of visibility |
TransRunwayVis [(Runway, [Visibility], Maybe VisTrend)] | A change of visibility for a specific runway |
TransWX [WeatherPhenomenon] | A change of weather phenomenon |
TransClouds [Cloud] | A change of ceiling or cloud layers |
TransPressure [Pressure] | A change of ceiling or cloud layers |
Instances
Eq Transition Source # | |
Defined in Data.Aviation.WX (==) :: Transition -> Transition -> Bool # (/=) :: Transition -> Transition -> Bool # | |
Show Transition Source # | |
Defined in Data.Aviation.WX showsPrec :: Int -> Transition -> ShowS # show :: Transition -> String # showList :: [Transition] -> ShowS # | |
HasTransition Transition Source # | |
Defined in Data.Aviation.WX | |
AsTransition Transition Source # | |
Defined in Data.Aviation.WX _Transition :: Prism' Transition Transition Source # _TransWind :: Prism' Transition Wind Source # _TransVis :: Prism' Transition [Visibility] Source # _TransRunwayVis :: Prism' Transition [(Runway, [Visibility], Maybe VisTrend)] Source # _TransWX :: Prism' Transition [WeatherPhenomenon] Source # _TransClouds :: Prism' Transition [Cloud] Source # |
class HasTransition c where Source #
transition :: Lens' c Transition Source #
Instances
HasTransition Transition Source # | |
Defined in Data.Aviation.WX |
class AsTransition r where Source #
_Transition :: Prism' r Transition Source #
_TransWind :: Prism' r Wind Source #
_TransVis :: Prism' r [Visibility] Source #
_TransRunwayVis :: Prism' r [(Runway, [Visibility], Maybe VisTrend)] Source #
_TransWX :: Prism' r [WeatherPhenomenon] Source #
_TransClouds :: Prism' r [Cloud] Source #
_TransPressure :: Prism' r [Pressure] Source #
Instances
AsTransition Transition Source # | |
Defined in Data.Aviation.WX _Transition :: Prism' Transition Transition Source # _TransWind :: Prism' Transition Wind Source # _TransVis :: Prism' Transition [Visibility] Source # _TransRunwayVis :: Prism' Transition [(Runway, [Visibility], Maybe VisTrend)] Source # _TransWX :: Prism' Transition [WeatherPhenomenon] Source # _TransClouds :: Prism' Transition [Cloud] Source # |
A speed unit.
Knots Int | Nautical miles per hour |
Miles Int | Statute miles per hour |
MPS Int | Unknown (miles per second?) |
KMH Int | Kilometres per hour |
data ReportType Source #
Instances
Enum ReportType Source # | |
Defined in Data.Aviation.WX succ :: ReportType -> ReportType # pred :: ReportType -> ReportType # toEnum :: Int -> ReportType # fromEnum :: ReportType -> Int # enumFrom :: ReportType -> [ReportType] # enumFromThen :: ReportType -> ReportType -> [ReportType] # enumFromTo :: ReportType -> ReportType -> [ReportType] # enumFromThenTo :: ReportType -> ReportType -> ReportType -> [ReportType] # | |
Eq ReportType Source # | |
Defined in Data.Aviation.WX (==) :: ReportType -> ReportType -> Bool # (/=) :: ReportType -> ReportType -> Bool # | |
Show ReportType Source # | |
Defined in Data.Aviation.WX showsPrec :: Int -> ReportType -> ShowS # show :: ReportType -> String # showList :: [ReportType] -> ShowS # |