module Flight.Igc
(
IgcRecord(..)
, HMS(..)
, Lat(..)
, Lng(..)
, AltBaro(..)
, AltGps(..)
, parse
, parseFromFile
, Altitude
, Degree
, Hour
, Minute
, Second
) where
import Prelude hiding (readFile)
import Data.ByteString.UTF8 (toString)
import Data.ByteString (readFile)
import Data.List (partition)
import Text.Parsec.Char (endOfLine, anyChar)
import Text.ParserCombinators.Parsec
( GenParser
, ParseError
, (<|>)
, char
, string
, many
, manyTill
, lookAhead
, oneOf
, noneOf
, count
, digit
, eof
, optionMaybe
, runParser
)
import qualified Text.ParserCombinators.Parsec as P (parse)
type Altitude = String
type Hour = String
type Minute = String
type Second = String
type Degree = String
data HMS = HMS Hour Minute Second
data Lat
= LatN Degree Minute
| LatS Degree Minute
data Lng
= LngW Degree Minute
| LngE Degree Minute
newtype AltBaro = AltBaro Altitude
newtype AltGps = AltGps Altitude
data IgcRecord
= B HMS Lat Lng AltBaro (Maybe AltGps)
| HFDTE String String String
| Ignore
deriving Show
showDegree :: String -> String
showDegree d = d ++ "°"
showMinute :: String -> String
showMinute (m0 : m1 : m) = [m0, m1] ++ "." ++ m ++ "'"
showMinute m = m
showHMS :: HMS -> String
showHMS (HMS hh mm ss) = hh ++ ":" ++ mm ++ ":" ++ ss
showLat :: Lat -> String
showLat (LatN d m) = showDegree d ++ " " ++ showMinute m ++ " N"
showLat (LatS d m) = showDegree d ++ " " ++ showMinute m ++ " S"
showLng :: Lng -> String
showLng (LngW d m) = showDegree d ++ " " ++ showMinute m ++ " W"
showLng (LngE d m) = showDegree d ++ " " ++ showMinute m ++ " E"
ltrimZero :: String -> String
ltrimZero = dropWhile ('0' ==)
instance Show HMS where
show = showHMS
instance Show Lat where
show = showLat
instance Show Lng where
show = showLng
instance Show AltBaro where
show (AltBaro x) = ltrimZero x ++ "m"
instance Show AltGps where
show (AltGps x) = ltrimZero x ++ "m"
showIgc :: [ IgcRecord ] -> String
showIgc xs =
unlines $ f <$> xs
where
f x = case x of
B{} -> "B"
_ -> show x
showIgcSummarize :: [ IgcRecord ] -> String
showIgcSummarize xs =
(\(bs, ys) -> showIgc ys ++ summarize bs) $ partition isB xs
where
summarize [] = "no B records"
summarize [ x ] = unlines [ show x, "... and no other B records" ]
summarize (x : y : _) = unlines [ show x
, show y
,"... plus " ++ show (length xs) ++ " other B records"
]
instance {-# OVERLAPPING #-} Show [ IgcRecord ] where
show = showIgcSummarize
isB :: IgcRecord -> Bool
isB B{} = True
isB HFDTE{} = False
isB Ignore = False
igcFile :: GenParser Char st [IgcRecord]
igcFile = do
hfdte <- manyTill anyChar (lookAhead (string "HFDTE")) *> headerLine
lines' <- manyTill anyChar (char 'B') *> many line
_ <- eof
return $ hfdte : lines'
headerLine :: GenParser Char st IgcRecord
headerLine = do
line' <- date
_ <- endOfLine
return line'
line :: GenParser Char st IgcRecord
line = do
line' <- fix <|> ignore
_ <- endOfLine
return line'
hms :: GenParser Char st HMS
hms = do
hh <- count 2 digit
mm <- count 2 digit
ss <- count 2 digit
return $ HMS hh mm ss
lat :: GenParser Char st Lat
lat = do
degs <- count 2 digit
mins <- count 5 digit
f <- const LatN <$> char 'N' <|> const LatS <$> char 'S'
return $ f degs mins
lng :: GenParser Char st Lng
lng = do
degs <- count 3 digit
mins <- count 5 digit
f <- const LngW <$> char 'W' <|> const LngE <$> char 'E'
return $ f degs mins
altBaro :: GenParser Char st AltBaro
altBaro = AltBaro <$> count 5 digit
altGps :: GenParser Char st AltGps
altGps = AltGps <$> count 5 digit
alt :: GenParser Char st (AltBaro, Maybe AltGps)
alt = do
_ <- oneOf "AV"
altBaro' <- altBaro
altGps' <- optionMaybe altGps
return (altBaro', altGps')
fix :: GenParser Char st IgcRecord
fix = do
_ <- char 'B'
hms' <- hms
lat' <- lat
lng' <- lng
(altBaro', altGps') <- alt
_ <- many (noneOf "\n")
return $ B hms' lat' lng' altBaro' altGps'
date :: GenParser Char st IgcRecord
date = do
_ <- string "HFDTE"
dd <- count 2 digit
mm <- count 2 digit
yy <- count 2 digit
return $ HFDTE dd mm yy
ignore :: GenParser Char st IgcRecord
ignore = do
_ <- many (noneOf "\n")
return Ignore
parse
:: String
-> Either ParseError [IgcRecord]
parse = P.parse igcFile "(stdin)"
parseFromFile
:: FilePath
-> IO (Either ParseError [IgcRecord])
parseFromFile fname =
runParser igcFile () fname . toString <$> readFile fname