{-# LANGUAGE TemplateHaskell #-}
module Data.PlanarGraph.Dart where
import Control.DeepSeq
import Control.Lens hiding ((.=))
import GHC.Generics (Generic)
import Test.QuickCheck (Arbitrary(..),suchThat)
newtype Arc s = Arc { _unArc :: Int } deriving (Eq,Ord,Enum,Bounded,Generic,NFData)
instance Show (Arc s) where
  show (Arc i) = "Arc " ++ show i
instance Arbitrary (Arc s) where
  arbitrary = Arc <$> (arbitrary `suchThat` (>= 0))
data Direction = Negative | Positive deriving (Eq,Ord,Bounded,Enum,Generic)
instance NFData Direction
instance Show Direction where
  show Positive = "+1"
  show Negative = "-1"
instance Read Direction where
  readsPrec _ "-1" = [(Negative,"")]
  readsPrec _ "+1" = [(Positive,"")]
  readsPrec _ _    = []
instance Arbitrary Direction where
  arbitrary = (\b -> if b then Positive else Negative) <$> arbitrary
rev          :: Direction -> Direction
rev Negative = Positive
rev Positive = Negative
data Dart s = Dart { _arc       :: !(Arc s)
                   , _direction :: !Direction
                   } deriving (Eq,Ord,Generic)
makeLenses ''Dart
instance NFData (Dart s)
instance Show (Dart s) where
  show (Dart a d) = "Dart (" ++ show a ++ ") " ++ show d
instance Arbitrary (Dart s) where
  arbitrary = Dart <$> arbitrary <*> arbitrary
twin            :: Dart s -> Dart s
twin (Dart a d) = Dart a (rev d)
isPositive   :: Dart s -> Bool
isPositive d = d^.direction == Positive
instance Enum (Dart s) where
  toEnum x
    | even x    = Dart (Arc $ x `div` 2) Positive
    | otherwise = Dart (Arc $ x `div` 2) Negative
  
  fromEnum (Dart (Arc i) d) = case d of
                                Positive -> 2*i
                                Negative -> 2*i + 1
allDarts :: [Dart s]
allDarts = concatMap (\a -> [Dart a Positive, Dart a Negative]) [Arc 0..]