module Data.Geo.Route.Plan( Plan , mkPlan , mkPlan' ) where import Prelude(Show) import Control.Lens(lens) import Control.Monad(Monad((>>=))) import Data.Bool((&&)) import Data.Eq(Eq) import Data.Foldable(Foldable(foldMap)) import Data.Ord(Ord) import Data.Maybe(Maybe(Nothing, Just), isNothing) import Data.String(String) import Data.Geo.Route.Author(Author) import Data.Geo.Route.Copyright(Copyright) import Data.Geo.Route.Description(Description, HasMaybeDescription(mdescription)) import Data.Geo.Route.Gpx(Gpx(gpx)) import Data.Geo.Route.Name(Name, HasMaybeName(mname)) import Data.Geo.Route.Osrm(Osrm(allCoordinates)) import Data.Geo.Route.Track(Track, trackPoints) import Data.Geo.Route.Waypoint(gpxWaypoint) import Text.Printf(printf) data Plan = Plan (Maybe Name) -- name (Maybe Description) -- description (Maybe Author) -- author (Maybe Copyright) -- copyright Track deriving (Eq, Ord, Show) mkPlan :: Track -> Plan mkPlan = Plan Nothing Nothing Nothing Nothing mkPlan' :: Name -> Description -> Author -> Copyright -> Track -> Plan mkPlan' n d a c = Plan (Just n) (Just d) (Just a) (Just c) instance Gpx Plan where gpx (Plan n d a c t) = let gpx' :: (Foldable t, Gpx a) => t a -> String gpx' = foldMap gpx metadata = if isNothing n && isNothing d && isNothing a && isNothing c then "" else printf "%s%s%s%s%s%s" "" (gpx' n) (gpx' d) (gpx' a) (gpx' c) "" wpt = trackPoints t >>= gpx rte :: String rte = printf "%s" (trackPoints t >>= gpxWaypoint "rtept") trk = gpx t in printf "%s%s%s%s%s%s" "" metadata wpt rte trk "" instance Osrm Plan where allCoordinates (Plan _ _ _ _ t) = allCoordinates t instance HasMaybeName Plan where mname = lens (\(Plan n _ _ _ _) -> n) (\(Plan _ d a c t) n -> Plan n d a c t) instance HasMaybeDescription Plan where mdescription = lens (\(Plan _ d _ _ _) -> d) (\(Plan n _ a c t) d -> Plan n d a c t)