Copyright | Travis Whitaker 2023 |
---|---|
License | MIT |
Maintainer | pi.boy.travis@gmail.com |
Stability | Provisional |
Portability | Portable (Windows, POSIX) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Types for dealing with different representations of angles in the plane.
Synopsis
- class PlaneAngle ang where
- newtype Radians a = Radians a
- newtype Degrees a = Degrees a
- data DMS a = DMS {}
- dmsToDegrees :: Fractional a => DMS a -> Degrees a
- degreesToDMS :: (Real a, Fractional a) => Degrees a -> DMS a
- data DM a = DM {}
- dmToDegrees :: Fractional a => DM a -> Degrees a
- degreesToDM :: (Fractional a, Real a) => Degrees a -> DM a
Documentation
class PlaneAngle ang where Source #
Plane angles.
normalizeAngle :: (Floating a, Real a) => ang a -> ang a Source #
toRadians :: (Floating a, Real a) => ang a -> Radians a Source #
Convert the angle to radians.
fromRadians :: (Floating a, Real a) => Radians a -> ang a Source #
Convert the angle from radians.
Instances
A quantity representing a plane angle that satisfies the equation
S = r * a
where r
is the radius of a circle, a
is the measure of some
angle subtending the circle, and S
is the length of the subtended arc.
Radians a |
Instances
One degree is pi / 180
radians.
Degrees a |
Instances
An angle represented as degrees, minutes, and seconds of arc.
Instances
MonadFix DMS Source # | |
Defined in Linear.Geo.PlaneAngle | |
MonadZip DMS Source # | |
Foldable DMS Source # | |
Defined in Linear.Geo.PlaneAngle fold :: Monoid m => DMS m -> m # foldMap :: Monoid m => (a -> m) -> DMS a -> m # foldMap' :: Monoid m => (a -> m) -> DMS a -> m # foldr :: (a -> b -> b) -> b -> DMS a -> b # foldr' :: (a -> b -> b) -> b -> DMS a -> b # foldl :: (b -> a -> b) -> b -> DMS a -> b # foldl' :: (b -> a -> b) -> b -> DMS a -> b # foldr1 :: (a -> a -> a) -> DMS a -> a # foldl1 :: (a -> a -> a) -> DMS a -> a # elem :: Eq a => a -> DMS a -> Bool # maximum :: Ord a => DMS a -> a # | |
Traversable DMS Source # | |
Applicative DMS Source # | |
Functor DMS Source # | |
Monad DMS Source # | |
Distributive DMS Source # | |
PlaneAngle DMS Source # | |
Data a => Data (DMS a) Source # | |
Defined in Linear.Geo.PlaneAngle gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DMS a -> c (DMS a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DMS a) # dataTypeOf :: DMS a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DMS a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DMS a)) # gmapT :: (forall b. Data b => b -> b) -> DMS a -> DMS a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DMS a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DMS a -> r # gmapQ :: (forall d. Data d => d -> u) -> DMS a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DMS a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DMS a -> m (DMS a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DMS a -> m (DMS a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DMS a -> m (DMS a) # | |
Bounded a => Bounded (DMS a) Source # | |
Generic (DMS a) Source # | |
Show a => Show (DMS a) Source # | |
NFData a => NFData (DMS a) Source # | |
Defined in Linear.Geo.PlaneAngle | |
Eq a => Eq (DMS a) Source # | |
Ord a => Ord (DMS a) Source # | |
type Rep (DMS a) Source # | |
Defined in Linear.Geo.PlaneAngle type Rep (DMS a) = D1 ('MetaData "DMS" "Linear.Geo.PlaneAngle" "linear-geo-0.1.0.0-LxCVplq22GGCkRzZB0XgZk" 'False) (C1 ('MetaCons "DMS" 'PrefixI 'True) (S1 ('MetaSel ('Just "dmsDeg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Just "dmsMin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "dmsSec") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))) |
dmsToDegrees :: Fractional a => DMS a -> Degrees a Source #
Convert DMS to Degrees. This does not normalize the angle.
degreesToDMS :: (Real a, Fractional a) => Degrees a -> DMS a Source #
Convert degrees to DMS. This does not normalize the angle.
An angle represented as degrees and minutes of arc.
Instances
MonadFix DM Source # | |
Defined in Linear.Geo.PlaneAngle | |
MonadZip DM Source # | |
Foldable DM Source # | |
Defined in Linear.Geo.PlaneAngle fold :: Monoid m => DM m -> m # foldMap :: Monoid m => (a -> m) -> DM a -> m # foldMap' :: Monoid m => (a -> m) -> DM a -> m # foldr :: (a -> b -> b) -> b -> DM a -> b # foldr' :: (a -> b -> b) -> b -> DM a -> b # foldl :: (b -> a -> b) -> b -> DM a -> b # foldl' :: (b -> a -> b) -> b -> DM a -> b # foldr1 :: (a -> a -> a) -> DM a -> a # foldl1 :: (a -> a -> a) -> DM a -> a # elem :: Eq a => a -> DM a -> Bool # maximum :: Ord a => DM a -> a # | |
Traversable DM Source # | |
Applicative DM Source # | |
Functor DM Source # | |
Monad DM Source # | |
Distributive DM Source # | |
PlaneAngle DM Source # | |
Data a => Data (DM a) Source # | |
Defined in Linear.Geo.PlaneAngle gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DM a -> c (DM a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DM a) # dataTypeOf :: DM a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DM a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DM a)) # gmapT :: (forall b. Data b => b -> b) -> DM a -> DM a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DM a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DM a -> r # gmapQ :: (forall d. Data d => d -> u) -> DM a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DM a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DM a -> m (DM a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DM a -> m (DM a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DM a -> m (DM a) # | |
Bounded a => Bounded (DM a) Source # | |
Generic (DM a) Source # | |
Show a => Show (DM a) Source # | |
NFData a => NFData (DM a) Source # | |
Defined in Linear.Geo.PlaneAngle | |
Eq a => Eq (DM a) Source # | |
Ord a => Ord (DM a) Source # | |
type Rep (DM a) Source # | |
Defined in Linear.Geo.PlaneAngle type Rep (DM a) = D1 ('MetaData "DM" "Linear.Geo.PlaneAngle" "linear-geo-0.1.0.0-LxCVplq22GGCkRzZB0XgZk" 'False) (C1 ('MetaCons "DM" 'PrefixI 'True) (S1 ('MetaSel ('Just "dmDeg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "dmMin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))) |
dmToDegrees :: Fractional a => DM a -> Degrees a Source #
Convert DM to degrees. This does not normalize the angle.
degreesToDM :: (Fractional a, Real a) => Degrees a -> DM a Source #
Convert degrees to DM. This does not normalize the angle.