{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE NoImplicitPrelude #-} module Data.Aviation.Navigation.WindComponent( WindComponent(..) , HasWindComponent(..) , calculateWindComponent ) where import Control.Category ( Category(id, (.)) ) import Control.Lens ( view, Lens' ) import Data.Aviation.Navigation.Vector ( HasVector(magnitude, angle) ) import Data.Aviation.Navigation.WindParameters ( HasWindParameters(windParameters, trackTAS, windSpeedDirection) ) import Data.Eq ( Eq ) import Data.Functor ( Functor(fmap) ) import Data.Ord ( Ord ) import GHC.Show(Show) import Prelude(Double, Num((*), (-)), sin, cos) data WindComponent = WindComponent Double Double deriving (Eq, Ord, Show) class HasWindComponent a where windComponent :: Lens' a WindComponent {-# INLINE crosswind #-} crosswind :: Lens' a Double crosswind = windComponent . crosswind {-# INLINE headwind #-} headwind :: Lens' a Double headwind = windComponent . headwind instance HasWindComponent WindComponent where windComponent = id {-# INLINE crosswind #-} crosswind f (WindComponent c h) = fmap (\c' -> WindComponent c' h) (f c) {-# INLINE headwind #-} headwind f (WindComponent c h) = fmap (\h' -> WindComponent c h') (f h) calculateWindComponent :: HasWindParameters s => s -> WindComponent calculateWindComponent wp = let t = view (windParameters . trackTAS) wp w = view (windParameters . windSpeedDirection) wp diff = view angle w - view angle t wm = view magnitude w cw = wm * sin diff hw = wm * cos diff in WindComponent cw hw