{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}

-- | A bearing in a degrees between 0 and 360.
module Data.Geo.Bearing(
                         Bearing,
                         bearing
                       ) where

import Data.Geo.Accessor.Value
import Data.Fixed

newtype Bearing = Bearing Double
  deriving (Eq, Ord, Enum, Show, Num, Fractional, Floating)

-- | Construct a bearing with the number of degrees.
bearing :: Double -> Bearing
bearing x = Bearing (x `mod'` 360)

instance Value Bearing Double where
  value (Bearing x) = x