{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} module Data.Aviation.WB.Volume( Volume , HasVolume(..) , HasVolumes(..) , SetVolume(..) , HasVolume0(..) , usgallonsV , litresV , imperialgallonsV ) where import Control.Category((.)) import Control.Lens(makeClassy, Traversal', Setter', Lens', Iso', iso) import Data.Aviation.Units.ImperialGallons(ImperialGallons(imperialgallons)) import Data.Aviation.Units.USGallons(USGallons(usgallons)) import Data.Aviation.Units.Litres(Litres(litres)) import Data.Eq(Eq) import Data.Maybe(Maybe) import Data.Monoid(Monoid(mempty, mappend)) import Data.Ord(Ord) import Data.Ratio((%)) import Data.Semigroup(Semigroup((<>))) import Numeric.Lens(multiplying, dividing) import Prelude(Show, Rational, (+), (*)) newtype Volume = Volume Rational deriving (Volume -> Volume -> Bool (Volume -> Volume -> Bool) -> (Volume -> Volume -> Bool) -> Eq Volume forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Volume -> Volume -> Bool $c/= :: Volume -> Volume -> Bool == :: Volume -> Volume -> Bool $c== :: Volume -> Volume -> Bool Eq, Eq Volume Eq Volume -> (Volume -> Volume -> Ordering) -> (Volume -> Volume -> Bool) -> (Volume -> Volume -> Bool) -> (Volume -> Volume -> Bool) -> (Volume -> Volume -> Bool) -> (Volume -> Volume -> Volume) -> (Volume -> Volume -> Volume) -> Ord Volume Volume -> Volume -> Bool Volume -> Volume -> Ordering Volume -> Volume -> Volume forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Volume -> Volume -> Volume $cmin :: Volume -> Volume -> Volume max :: Volume -> Volume -> Volume $cmax :: Volume -> Volume -> Volume >= :: Volume -> Volume -> Bool $c>= :: Volume -> Volume -> Bool > :: Volume -> Volume -> Bool $c> :: Volume -> Volume -> Bool <= :: Volume -> Volume -> Bool $c<= :: Volume -> Volume -> Bool < :: Volume -> Volume -> Bool $c< :: Volume -> Volume -> Bool compare :: Volume -> Volume -> Ordering $ccompare :: Volume -> Volume -> Ordering $cp1Ord :: Eq Volume Ord, Int -> Volume -> ShowS [Volume] -> ShowS Volume -> String (Int -> Volume -> ShowS) -> (Volume -> String) -> ([Volume] -> ShowS) -> Show Volume forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Volume] -> ShowS $cshowList :: [Volume] -> ShowS show :: Volume -> String $cshow :: Volume -> String showsPrec :: Int -> Volume -> ShowS $cshowsPrec :: Int -> Volume -> ShowS Show) makeClassy ''Volume class HasVolumes a where volumes :: Traversal' a Volume instance HasVolumes Volume where volumes :: (Volume -> f Volume) -> Volume -> f Volume volumes = (Volume -> f Volume) -> Volume -> f Volume forall c. HasVolume c => Lens' c Volume volume class SetVolume a where setVolume :: Setter' a Volume instance SetVolume Volume where setVolume :: (Volume -> f Volume) -> Volume -> f Volume setVolume = (Volume -> f Volume) -> Volume -> f Volume forall c. HasVolume c => Lens' c Volume volume class HasVolume0 a where volume0 :: Lens' a (Maybe Volume) instance Semigroup Volume where <> :: Volume -> Volume -> Volume (<>) = Volume -> Volume -> Volume forall a. Monoid a => a -> a -> a mappend instance Monoid Volume where mempty :: Volume mempty = Rational -> Volume Volume Rational 0 Volume Rational w1 mappend :: Volume -> Volume -> Volume `mappend` Volume Rational w2 = Rational -> Volume Volume (Rational w1 Rational -> Rational -> Rational forall a. Num a => a -> a -> a + Rational w2) instance USGallons Volume where usgallons :: p Volume (f Volume) -> p Rational (f Rational) usgallons = (Rational -> Volume) -> (Volume -> Rational) -> Iso' Rational Volume forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso Rational -> Volume Volume (\(Volume Rational x) -> Rational x) instance Litres Volume where litres :: p Volume (f Volume) -> p Rational (f Rational) litres = Rational -> Iso' Rational Rational forall a. (Fractional a, Eq a) => a -> Iso' a a dividing ((Integer 254 Integer -> Integer -> Integer forall a. Num a => a -> a -> a * Integer 254 Integer -> Integer -> Integer forall a. Num a => a -> a -> a * Integer 254 Integer -> Integer -> Integer forall a. Num a => a -> a -> a * Integer 231) Integer -> Integer -> Rational forall a. Integral a => a -> a -> Ratio a % Integer 1000000000) (p Rational (f Rational) -> p Rational (f Rational)) -> (p Volume (f Volume) -> p Rational (f Rational)) -> p Volume (f Volume) -> 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 Volume (f Volume) -> p Rational (f Rational) forall a. USGallons a => Iso' Rational a usgallons instance ImperialGallons Volume where imperialgallons :: p Volume (f Volume) -> p Rational (f Rational) imperialgallons = Rational -> Iso' Rational Rational forall a. (Fractional a, Eq a) => a -> Iso' a a multiplying (Integer 454609 Integer -> Integer -> Rational forall a. Integral a => a -> a -> Ratio a % Integer 100000) (p Rational (f Rational) -> p Rational (f Rational)) -> (p Volume (f Volume) -> p Rational (f Rational)) -> p Volume (f Volume) -> 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 Volume (f Volume) -> p Rational (f Rational) forall a. Litres a => Iso' Rational a litres usgallonsV :: Iso' Rational Volume usgallonsV :: p Volume (f Volume) -> p Rational (f Rational) usgallonsV = p Volume (f Volume) -> p Rational (f Rational) forall a. USGallons a => Iso' Rational a usgallons litresV :: Iso' Rational Volume litresV :: p Volume (f Volume) -> p Rational (f Rational) litresV = p Volume (f Volume) -> p Rational (f Rational) forall a. Litres a => Iso' Rational a litres imperialgallonsV :: Iso' Rational Volume imperialgallonsV :: p Volume (f Volume) -> p Rational (f Rational) imperialgallonsV = p Volume (f Volume) -> p Rational (f Rational) forall a. ImperialGallons a => Iso' Rational a imperialgallons