{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} module Data.Aviation.WB.Avgas100LL( Avgas100LL(..) ) where import Control.Category((.)) import Control.Lens(Iso', from) import Data.Aviation.Units.USGallons(usgallons) import Data.Aviation.Units.Pounds(pounds) import Data.Aviation.WB.Weight(Weight) import Data.Aviation.WB.Volume(Volume) import Numeric.Lens(multiplying) class Avgas100LL a b | a -> b, b -> a where avgas100LL :: Iso' a b instance Avgas100LL Volume Weight where avgas100LL :: p Weight (f Weight) -> p Volume (f Volume) avgas100LL = AnIso Rational Rational Volume Volume -> Iso Volume Volume Rational Rational forall s t a b. AnIso s t a b -> Iso b a t s from AnIso Rational Rational Volume Volume forall a. USGallons a => Iso' Rational a usgallons (p Rational (f Rational) -> p Volume (f Volume)) -> (p Weight (f Weight) -> p Rational (f Rational)) -> p Weight (f Weight) -> p Volume (f Volume) forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Rational -> Iso' Rational Rational forall a. (Fractional a, Eq a) => a -> Iso' a a multiplying Rational 6 (p Rational (f Rational) -> p Rational (f Rational)) -> (p Weight (f Weight) -> p Rational (f Rational)) -> p Weight (f Weight) -> p Rational (f Rational) forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . p Weight (f Weight) -> p Rational (f Rational) forall a. Pounds a => Iso' Rational a pounds instance Avgas100LL Weight Volume where avgas100LL :: p Volume (f Volume) -> p Weight (f Weight) avgas100LL = AnIso Volume Volume Weight Weight -> Iso' Weight Volume forall s t a b. AnIso s t a b -> Iso b a t s from AnIso Volume Volume Weight Weight forall a b. Avgas100LL a b => Iso' a b avgas100LL