-- | Compass bearings.
module Data.CG.Minus.Bearing where

import Data.CG.Minus

-- | Enumeration of compass bearings
data Bearing = N | NNE | NE | ENE
             | E | ESE | SE | SSE
             | S | SSW | SW | WSW
             | W | WNW | NW | NNW
               deriving (Eq,Enum,Bounded,Show)

-- | Bearing from 'Pt' /p/ to /q/.
--
-- > let f (x,y) = bearing (Pt 0 0) (Pt x y)
-- > map f [(0,1),(1,1),(1,0),(1,-1)] == [N,NE,E,SE]
-- > map f [(0,-1),(-1,-1),(-1,0),(-1,1)] == [S,SW,W,NW]
-- > map f [(1/4,1),(1,1/4),(1,-1/4),(1/4,-1)] == [NNE,ENE,ESE,SSE]
-- > map f [(-1/4,-1),(-1,-1/4),(-1,1.4),(-1/4,1)] == [SSW,WSW,NW,NNW]
bearing :: Pt R -> Pt R -> Bearing
bearing p q =
    let a = negate (pt_angle p q) + pi
        c = round ((a * (8 / pi)) - 4) `mod` 16
    in toEnum c

-- | Bearing to nearest eight point compass bearing
--
-- > let f (x,y) = bearing_8 (Pt 0 0) (Pt x y)
-- > map f [(1/4,1),(1,1/4),(1,-1/4),(1/4,-1)] == [N,E,E,S]
bearing_8 :: Pt R -> Pt R -> Bearing
bearing_8 p q =
    let a = negate (pt_angle p q) + pi
        c = round ((a * (4 / pi)) - 2) `mod` 8
    in toEnum (c * 2)

-- | Predicate that is 'True' if bearings are opposite.
--
-- > bearing_opposite (NW,SE) == True
-- > map bearing_opposite (zip [N,E,S,W] [S,W,N,E]) == [True,True,True,True]
bearing_opposite :: (Bearing,Bearing) -> Bool
bearing_opposite (p, q) =
    let n = (fromEnum p - fromEnum q) `mod` 16
    in n == 8