{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
module Swarm.Language.Syntax.Direction (
Direction (..),
CoordinateOrientation (..),
AbsoluteDir (..),
RelativeDir (..),
PlanarRelativeDir (..),
directionSyntax,
isCardinal,
allDirs,
directionJsonModifier,
getCoordinateOrientation,
) where
import Data.Aeson.Types hiding (Key)
import Data.Char qualified as C (toLower)
import Data.Data (Data)
import Data.Hashable (Hashable)
import Data.List qualified as L (drop)
import Data.List.Extra (enumerate)
import Data.Text (Text)
import Data.Text qualified as T
import GHC.Generics (Generic)
import Prettyprinter (pretty)
import Swarm.Pretty (PrettyPrec (..))
import Swarm.Util.JSON (optionsMinimize)
data AbsoluteDir = DEast | DNorth | DWest | DSouth
deriving (AbsoluteDir -> AbsoluteDir -> Bool
(AbsoluteDir -> AbsoluteDir -> Bool)
-> (AbsoluteDir -> AbsoluteDir -> Bool) -> Eq AbsoluteDir
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AbsoluteDir -> AbsoluteDir -> Bool
== :: AbsoluteDir -> AbsoluteDir -> Bool
$c/= :: AbsoluteDir -> AbsoluteDir -> Bool
/= :: AbsoluteDir -> AbsoluteDir -> Bool
Eq, Eq AbsoluteDir
Eq AbsoluteDir =>
(AbsoluteDir -> AbsoluteDir -> Ordering)
-> (AbsoluteDir -> AbsoluteDir -> Bool)
-> (AbsoluteDir -> AbsoluteDir -> Bool)
-> (AbsoluteDir -> AbsoluteDir -> Bool)
-> (AbsoluteDir -> AbsoluteDir -> Bool)
-> (AbsoluteDir -> AbsoluteDir -> AbsoluteDir)
-> (AbsoluteDir -> AbsoluteDir -> AbsoluteDir)
-> Ord AbsoluteDir
AbsoluteDir -> AbsoluteDir -> Bool
AbsoluteDir -> AbsoluteDir -> Ordering
AbsoluteDir -> AbsoluteDir -> AbsoluteDir
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
$ccompare :: AbsoluteDir -> AbsoluteDir -> Ordering
compare :: AbsoluteDir -> AbsoluteDir -> Ordering
$c< :: AbsoluteDir -> AbsoluteDir -> Bool
< :: AbsoluteDir -> AbsoluteDir -> Bool
$c<= :: AbsoluteDir -> AbsoluteDir -> Bool
<= :: AbsoluteDir -> AbsoluteDir -> Bool
$c> :: AbsoluteDir -> AbsoluteDir -> Bool
> :: AbsoluteDir -> AbsoluteDir -> Bool
$c>= :: AbsoluteDir -> AbsoluteDir -> Bool
>= :: AbsoluteDir -> AbsoluteDir -> Bool
$cmax :: AbsoluteDir -> AbsoluteDir -> AbsoluteDir
max :: AbsoluteDir -> AbsoluteDir -> AbsoluteDir
$cmin :: AbsoluteDir -> AbsoluteDir -> AbsoluteDir
min :: AbsoluteDir -> AbsoluteDir -> AbsoluteDir
Ord, Int -> AbsoluteDir -> ShowS
[AbsoluteDir] -> ShowS
AbsoluteDir -> String
(Int -> AbsoluteDir -> ShowS)
-> (AbsoluteDir -> String)
-> ([AbsoluteDir] -> ShowS)
-> Show AbsoluteDir
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AbsoluteDir -> ShowS
showsPrec :: Int -> AbsoluteDir -> ShowS
$cshow :: AbsoluteDir -> String
show :: AbsoluteDir -> String
$cshowList :: [AbsoluteDir] -> ShowS
showList :: [AbsoluteDir] -> ShowS
Show, ReadPrec [AbsoluteDir]
ReadPrec AbsoluteDir
Int -> ReadS AbsoluteDir
ReadS [AbsoluteDir]
(Int -> ReadS AbsoluteDir)
-> ReadS [AbsoluteDir]
-> ReadPrec AbsoluteDir
-> ReadPrec [AbsoluteDir]
-> Read AbsoluteDir
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AbsoluteDir
readsPrec :: Int -> ReadS AbsoluteDir
$creadList :: ReadS [AbsoluteDir]
readList :: ReadS [AbsoluteDir]
$creadPrec :: ReadPrec AbsoluteDir
readPrec :: ReadPrec AbsoluteDir
$creadListPrec :: ReadPrec [AbsoluteDir]
readListPrec :: ReadPrec [AbsoluteDir]
Read, (forall x. AbsoluteDir -> Rep AbsoluteDir x)
-> (forall x. Rep AbsoluteDir x -> AbsoluteDir)
-> Generic AbsoluteDir
forall x. Rep AbsoluteDir x -> AbsoluteDir
forall x. AbsoluteDir -> Rep AbsoluteDir x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AbsoluteDir -> Rep AbsoluteDir x
from :: forall x. AbsoluteDir -> Rep AbsoluteDir x
$cto :: forall x. Rep AbsoluteDir x -> AbsoluteDir
to :: forall x. Rep AbsoluteDir x -> AbsoluteDir
Generic, Typeable AbsoluteDir
Typeable AbsoluteDir =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AbsoluteDir -> c AbsoluteDir)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AbsoluteDir)
-> (AbsoluteDir -> Constr)
-> (AbsoluteDir -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AbsoluteDir))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AbsoluteDir))
-> ((forall b. Data b => b -> b) -> AbsoluteDir -> AbsoluteDir)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AbsoluteDir -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AbsoluteDir -> r)
-> (forall u. (forall d. Data d => d -> u) -> AbsoluteDir -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> AbsoluteDir -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AbsoluteDir -> m AbsoluteDir)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AbsoluteDir -> m AbsoluteDir)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AbsoluteDir -> m AbsoluteDir)
-> Data AbsoluteDir
AbsoluteDir -> Constr
AbsoluteDir -> DataType
(forall b. Data b => b -> b) -> AbsoluteDir -> AbsoluteDir
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> AbsoluteDir -> u
forall u. (forall d. Data d => d -> u) -> AbsoluteDir -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AbsoluteDir -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AbsoluteDir -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AbsoluteDir -> m AbsoluteDir
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AbsoluteDir -> m AbsoluteDir
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AbsoluteDir
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AbsoluteDir -> c AbsoluteDir
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AbsoluteDir)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AbsoluteDir)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AbsoluteDir -> c AbsoluteDir
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AbsoluteDir -> c AbsoluteDir
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AbsoluteDir
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AbsoluteDir
$ctoConstr :: AbsoluteDir -> Constr
toConstr :: AbsoluteDir -> Constr
$cdataTypeOf :: AbsoluteDir -> DataType
dataTypeOf :: AbsoluteDir -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AbsoluteDir)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AbsoluteDir)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AbsoluteDir)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AbsoluteDir)
$cgmapT :: (forall b. Data b => b -> b) -> AbsoluteDir -> AbsoluteDir
gmapT :: (forall b. Data b => b -> b) -> AbsoluteDir -> AbsoluteDir
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AbsoluteDir -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AbsoluteDir -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AbsoluteDir -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AbsoluteDir -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> AbsoluteDir -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> AbsoluteDir -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> AbsoluteDir -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> AbsoluteDir -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AbsoluteDir -> m AbsoluteDir
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AbsoluteDir -> m AbsoluteDir
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AbsoluteDir -> m AbsoluteDir
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AbsoluteDir -> m AbsoluteDir
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AbsoluteDir -> m AbsoluteDir
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AbsoluteDir -> m AbsoluteDir
Data, Eq AbsoluteDir
Eq AbsoluteDir =>
(Int -> AbsoluteDir -> Int)
-> (AbsoluteDir -> Int) -> Hashable AbsoluteDir
Int -> AbsoluteDir -> Int
AbsoluteDir -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> AbsoluteDir -> Int
hashWithSalt :: Int -> AbsoluteDir -> Int
$chash :: AbsoluteDir -> Int
hash :: AbsoluteDir -> Int
Hashable, Int -> AbsoluteDir
AbsoluteDir -> Int
AbsoluteDir -> [AbsoluteDir]
AbsoluteDir -> AbsoluteDir
AbsoluteDir -> AbsoluteDir -> [AbsoluteDir]
AbsoluteDir -> AbsoluteDir -> AbsoluteDir -> [AbsoluteDir]
(AbsoluteDir -> AbsoluteDir)
-> (AbsoluteDir -> AbsoluteDir)
-> (Int -> AbsoluteDir)
-> (AbsoluteDir -> Int)
-> (AbsoluteDir -> [AbsoluteDir])
-> (AbsoluteDir -> AbsoluteDir -> [AbsoluteDir])
-> (AbsoluteDir -> AbsoluteDir -> [AbsoluteDir])
-> (AbsoluteDir -> AbsoluteDir -> AbsoluteDir -> [AbsoluteDir])
-> Enum AbsoluteDir
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: AbsoluteDir -> AbsoluteDir
succ :: AbsoluteDir -> AbsoluteDir
$cpred :: AbsoluteDir -> AbsoluteDir
pred :: AbsoluteDir -> AbsoluteDir
$ctoEnum :: Int -> AbsoluteDir
toEnum :: Int -> AbsoluteDir
$cfromEnum :: AbsoluteDir -> Int
fromEnum :: AbsoluteDir -> Int
$cenumFrom :: AbsoluteDir -> [AbsoluteDir]
enumFrom :: AbsoluteDir -> [AbsoluteDir]
$cenumFromThen :: AbsoluteDir -> AbsoluteDir -> [AbsoluteDir]
enumFromThen :: AbsoluteDir -> AbsoluteDir -> [AbsoluteDir]
$cenumFromTo :: AbsoluteDir -> AbsoluteDir -> [AbsoluteDir]
enumFromTo :: AbsoluteDir -> AbsoluteDir -> [AbsoluteDir]
$cenumFromThenTo :: AbsoluteDir -> AbsoluteDir -> AbsoluteDir -> [AbsoluteDir]
enumFromThenTo :: AbsoluteDir -> AbsoluteDir -> AbsoluteDir -> [AbsoluteDir]
Enum, AbsoluteDir
AbsoluteDir -> AbsoluteDir -> Bounded AbsoluteDir
forall a. a -> a -> Bounded a
$cminBound :: AbsoluteDir
minBound :: AbsoluteDir
$cmaxBound :: AbsoluteDir
maxBound :: AbsoluteDir
Bounded)
directionJsonModifier :: String -> String
directionJsonModifier :: ShowS
directionJsonModifier = (Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
C.toLower ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Int -> [a] -> [a]
L.drop Int
1
data CoordinateOrientation
= Latitudinal
| Longitudinal
deriving (Int -> CoordinateOrientation -> ShowS
[CoordinateOrientation] -> ShowS
CoordinateOrientation -> String
(Int -> CoordinateOrientation -> ShowS)
-> (CoordinateOrientation -> String)
-> ([CoordinateOrientation] -> ShowS)
-> Show CoordinateOrientation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CoordinateOrientation -> ShowS
showsPrec :: Int -> CoordinateOrientation -> ShowS
$cshow :: CoordinateOrientation -> String
show :: CoordinateOrientation -> String
$cshowList :: [CoordinateOrientation] -> ShowS
showList :: [CoordinateOrientation] -> ShowS
Show, CoordinateOrientation -> CoordinateOrientation -> Bool
(CoordinateOrientation -> CoordinateOrientation -> Bool)
-> (CoordinateOrientation -> CoordinateOrientation -> Bool)
-> Eq CoordinateOrientation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CoordinateOrientation -> CoordinateOrientation -> Bool
== :: CoordinateOrientation -> CoordinateOrientation -> Bool
$c/= :: CoordinateOrientation -> CoordinateOrientation -> Bool
/= :: CoordinateOrientation -> CoordinateOrientation -> Bool
Eq, Eq CoordinateOrientation
Eq CoordinateOrientation =>
(CoordinateOrientation -> CoordinateOrientation -> Ordering)
-> (CoordinateOrientation -> CoordinateOrientation -> Bool)
-> (CoordinateOrientation -> CoordinateOrientation -> Bool)
-> (CoordinateOrientation -> CoordinateOrientation -> Bool)
-> (CoordinateOrientation -> CoordinateOrientation -> Bool)
-> (CoordinateOrientation
-> CoordinateOrientation -> CoordinateOrientation)
-> (CoordinateOrientation
-> CoordinateOrientation -> CoordinateOrientation)
-> Ord CoordinateOrientation
CoordinateOrientation -> CoordinateOrientation -> Bool
CoordinateOrientation -> CoordinateOrientation -> Ordering
CoordinateOrientation
-> CoordinateOrientation -> CoordinateOrientation
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
$ccompare :: CoordinateOrientation -> CoordinateOrientation -> Ordering
compare :: CoordinateOrientation -> CoordinateOrientation -> Ordering
$c< :: CoordinateOrientation -> CoordinateOrientation -> Bool
< :: CoordinateOrientation -> CoordinateOrientation -> Bool
$c<= :: CoordinateOrientation -> CoordinateOrientation -> Bool
<= :: CoordinateOrientation -> CoordinateOrientation -> Bool
$c> :: CoordinateOrientation -> CoordinateOrientation -> Bool
> :: CoordinateOrientation -> CoordinateOrientation -> Bool
$c>= :: CoordinateOrientation -> CoordinateOrientation -> Bool
>= :: CoordinateOrientation -> CoordinateOrientation -> Bool
$cmax :: CoordinateOrientation
-> CoordinateOrientation -> CoordinateOrientation
max :: CoordinateOrientation
-> CoordinateOrientation -> CoordinateOrientation
$cmin :: CoordinateOrientation
-> CoordinateOrientation -> CoordinateOrientation
min :: CoordinateOrientation
-> CoordinateOrientation -> CoordinateOrientation
Ord)
getCoordinateOrientation :: AbsoluteDir -> CoordinateOrientation
getCoordinateOrientation :: AbsoluteDir -> CoordinateOrientation
getCoordinateOrientation = \case
AbsoluteDir
DEast -> CoordinateOrientation
Longitudinal
AbsoluteDir
DWest -> CoordinateOrientation
Longitudinal
AbsoluteDir
DNorth -> CoordinateOrientation
Latitudinal
AbsoluteDir
DSouth -> CoordinateOrientation
Latitudinal
directionJsonOptions :: Options
directionJsonOptions :: Options
directionJsonOptions =
Options
defaultOptions
{ constructorTagModifier = directionJsonModifier
}
instance FromJSON AbsoluteDir where
parseJSON :: Value -> Parser AbsoluteDir
parseJSON = Options -> Value -> Parser AbsoluteDir
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
directionJsonOptions
instance ToJSON AbsoluteDir where
toJSON :: AbsoluteDir -> Value
toJSON = Options -> AbsoluteDir -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
directionJsonOptions
cardinalDirectionKeyOptions :: JSONKeyOptions
cardinalDirectionKeyOptions :: JSONKeyOptions
cardinalDirectionKeyOptions =
JSONKeyOptions
defaultJSONKeyOptions
{ keyModifier = directionJsonModifier
}
instance ToJSONKey AbsoluteDir where
toJSONKey :: ToJSONKeyFunction AbsoluteDir
toJSONKey = JSONKeyOptions -> ToJSONKeyFunction AbsoluteDir
forall a.
(Generic a, GToJSONKey (Rep a)) =>
JSONKeyOptions -> ToJSONKeyFunction a
genericToJSONKey JSONKeyOptions
cardinalDirectionKeyOptions
instance FromJSONKey AbsoluteDir where
fromJSONKey :: FromJSONKeyFunction AbsoluteDir
fromJSONKey = JSONKeyOptions -> FromJSONKeyFunction AbsoluteDir
forall a.
(Generic a, GFromJSONKey (Rep a)) =>
JSONKeyOptions -> FromJSONKeyFunction a
genericFromJSONKey JSONKeyOptions
cardinalDirectionKeyOptions
data RelativeDir = DPlanar PlanarRelativeDir | DDown
deriving (RelativeDir -> RelativeDir -> Bool
(RelativeDir -> RelativeDir -> Bool)
-> (RelativeDir -> RelativeDir -> Bool) -> Eq RelativeDir
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RelativeDir -> RelativeDir -> Bool
== :: RelativeDir -> RelativeDir -> Bool
$c/= :: RelativeDir -> RelativeDir -> Bool
/= :: RelativeDir -> RelativeDir -> Bool
Eq, Eq RelativeDir
Eq RelativeDir =>
(RelativeDir -> RelativeDir -> Ordering)
-> (RelativeDir -> RelativeDir -> Bool)
-> (RelativeDir -> RelativeDir -> Bool)
-> (RelativeDir -> RelativeDir -> Bool)
-> (RelativeDir -> RelativeDir -> Bool)
-> (RelativeDir -> RelativeDir -> RelativeDir)
-> (RelativeDir -> RelativeDir -> RelativeDir)
-> Ord RelativeDir
RelativeDir -> RelativeDir -> Bool
RelativeDir -> RelativeDir -> Ordering
RelativeDir -> RelativeDir -> RelativeDir
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
$ccompare :: RelativeDir -> RelativeDir -> Ordering
compare :: RelativeDir -> RelativeDir -> Ordering
$c< :: RelativeDir -> RelativeDir -> Bool
< :: RelativeDir -> RelativeDir -> Bool
$c<= :: RelativeDir -> RelativeDir -> Bool
<= :: RelativeDir -> RelativeDir -> Bool
$c> :: RelativeDir -> RelativeDir -> Bool
> :: RelativeDir -> RelativeDir -> Bool
$c>= :: RelativeDir -> RelativeDir -> Bool
>= :: RelativeDir -> RelativeDir -> Bool
$cmax :: RelativeDir -> RelativeDir -> RelativeDir
max :: RelativeDir -> RelativeDir -> RelativeDir
$cmin :: RelativeDir -> RelativeDir -> RelativeDir
min :: RelativeDir -> RelativeDir -> RelativeDir
Ord, Int -> RelativeDir -> ShowS
[RelativeDir] -> ShowS
RelativeDir -> String
(Int -> RelativeDir -> ShowS)
-> (RelativeDir -> String)
-> ([RelativeDir] -> ShowS)
-> Show RelativeDir
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RelativeDir -> ShowS
showsPrec :: Int -> RelativeDir -> ShowS
$cshow :: RelativeDir -> String
show :: RelativeDir -> String
$cshowList :: [RelativeDir] -> ShowS
showList :: [RelativeDir] -> ShowS
Show, ReadPrec [RelativeDir]
ReadPrec RelativeDir
Int -> ReadS RelativeDir
ReadS [RelativeDir]
(Int -> ReadS RelativeDir)
-> ReadS [RelativeDir]
-> ReadPrec RelativeDir
-> ReadPrec [RelativeDir]
-> Read RelativeDir
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RelativeDir
readsPrec :: Int -> ReadS RelativeDir
$creadList :: ReadS [RelativeDir]
readList :: ReadS [RelativeDir]
$creadPrec :: ReadPrec RelativeDir
readPrec :: ReadPrec RelativeDir
$creadListPrec :: ReadPrec [RelativeDir]
readListPrec :: ReadPrec [RelativeDir]
Read, (forall x. RelativeDir -> Rep RelativeDir x)
-> (forall x. Rep RelativeDir x -> RelativeDir)
-> Generic RelativeDir
forall x. Rep RelativeDir x -> RelativeDir
forall x. RelativeDir -> Rep RelativeDir x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RelativeDir -> Rep RelativeDir x
from :: forall x. RelativeDir -> Rep RelativeDir x
$cto :: forall x. Rep RelativeDir x -> RelativeDir
to :: forall x. Rep RelativeDir x -> RelativeDir
Generic, Typeable RelativeDir
Typeable RelativeDir =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RelativeDir -> c RelativeDir)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RelativeDir)
-> (RelativeDir -> Constr)
-> (RelativeDir -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RelativeDir))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RelativeDir))
-> ((forall b. Data b => b -> b) -> RelativeDir -> RelativeDir)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RelativeDir -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RelativeDir -> r)
-> (forall u. (forall d. Data d => d -> u) -> RelativeDir -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> RelativeDir -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RelativeDir -> m RelativeDir)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RelativeDir -> m RelativeDir)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RelativeDir -> m RelativeDir)
-> Data RelativeDir
RelativeDir -> Constr
RelativeDir -> DataType
(forall b. Data b => b -> b) -> RelativeDir -> RelativeDir
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> RelativeDir -> u
forall u. (forall d. Data d => d -> u) -> RelativeDir -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RelativeDir -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RelativeDir -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RelativeDir -> m RelativeDir
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RelativeDir -> m RelativeDir
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RelativeDir
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RelativeDir -> c RelativeDir
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RelativeDir)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RelativeDir)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RelativeDir -> c RelativeDir
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RelativeDir -> c RelativeDir
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RelativeDir
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RelativeDir
$ctoConstr :: RelativeDir -> Constr
toConstr :: RelativeDir -> Constr
$cdataTypeOf :: RelativeDir -> DataType
dataTypeOf :: RelativeDir -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RelativeDir)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RelativeDir)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RelativeDir)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RelativeDir)
$cgmapT :: (forall b. Data b => b -> b) -> RelativeDir -> RelativeDir
gmapT :: (forall b. Data b => b -> b) -> RelativeDir -> RelativeDir
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RelativeDir -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RelativeDir -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RelativeDir -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RelativeDir -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RelativeDir -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> RelativeDir -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RelativeDir -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RelativeDir -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RelativeDir -> m RelativeDir
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RelativeDir -> m RelativeDir
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RelativeDir -> m RelativeDir
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RelativeDir -> m RelativeDir
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RelativeDir -> m RelativeDir
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RelativeDir -> m RelativeDir
Data, Eq RelativeDir
Eq RelativeDir =>
(Int -> RelativeDir -> Int)
-> (RelativeDir -> Int) -> Hashable RelativeDir
Int -> RelativeDir -> Int
RelativeDir -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> RelativeDir -> Int
hashWithSalt :: Int -> RelativeDir -> Int
$chash :: RelativeDir -> Int
hash :: RelativeDir -> Int
Hashable)
instance ToJSON RelativeDir where
toJSON :: RelativeDir -> Value
toJSON = Options -> RelativeDir -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
optionsMinimize
instance FromJSON RelativeDir where
parseJSON :: Value -> Parser RelativeDir
parseJSON = Options -> Value -> Parser RelativeDir
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
optionsMinimize
data PlanarRelativeDir = DForward | DLeft | DBack | DRight
deriving (PlanarRelativeDir -> PlanarRelativeDir -> Bool
(PlanarRelativeDir -> PlanarRelativeDir -> Bool)
-> (PlanarRelativeDir -> PlanarRelativeDir -> Bool)
-> Eq PlanarRelativeDir
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PlanarRelativeDir -> PlanarRelativeDir -> Bool
== :: PlanarRelativeDir -> PlanarRelativeDir -> Bool
$c/= :: PlanarRelativeDir -> PlanarRelativeDir -> Bool
/= :: PlanarRelativeDir -> PlanarRelativeDir -> Bool
Eq, Eq PlanarRelativeDir
Eq PlanarRelativeDir =>
(PlanarRelativeDir -> PlanarRelativeDir -> Ordering)
-> (PlanarRelativeDir -> PlanarRelativeDir -> Bool)
-> (PlanarRelativeDir -> PlanarRelativeDir -> Bool)
-> (PlanarRelativeDir -> PlanarRelativeDir -> Bool)
-> (PlanarRelativeDir -> PlanarRelativeDir -> Bool)
-> (PlanarRelativeDir -> PlanarRelativeDir -> PlanarRelativeDir)
-> (PlanarRelativeDir -> PlanarRelativeDir -> PlanarRelativeDir)
-> Ord PlanarRelativeDir
PlanarRelativeDir -> PlanarRelativeDir -> Bool
PlanarRelativeDir -> PlanarRelativeDir -> Ordering
PlanarRelativeDir -> PlanarRelativeDir -> PlanarRelativeDir
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
$ccompare :: PlanarRelativeDir -> PlanarRelativeDir -> Ordering
compare :: PlanarRelativeDir -> PlanarRelativeDir -> Ordering
$c< :: PlanarRelativeDir -> PlanarRelativeDir -> Bool
< :: PlanarRelativeDir -> PlanarRelativeDir -> Bool
$c<= :: PlanarRelativeDir -> PlanarRelativeDir -> Bool
<= :: PlanarRelativeDir -> PlanarRelativeDir -> Bool
$c> :: PlanarRelativeDir -> PlanarRelativeDir -> Bool
> :: PlanarRelativeDir -> PlanarRelativeDir -> Bool
$c>= :: PlanarRelativeDir -> PlanarRelativeDir -> Bool
>= :: PlanarRelativeDir -> PlanarRelativeDir -> Bool
$cmax :: PlanarRelativeDir -> PlanarRelativeDir -> PlanarRelativeDir
max :: PlanarRelativeDir -> PlanarRelativeDir -> PlanarRelativeDir
$cmin :: PlanarRelativeDir -> PlanarRelativeDir -> PlanarRelativeDir
min :: PlanarRelativeDir -> PlanarRelativeDir -> PlanarRelativeDir
Ord, Int -> PlanarRelativeDir -> ShowS
[PlanarRelativeDir] -> ShowS
PlanarRelativeDir -> String
(Int -> PlanarRelativeDir -> ShowS)
-> (PlanarRelativeDir -> String)
-> ([PlanarRelativeDir] -> ShowS)
-> Show PlanarRelativeDir
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PlanarRelativeDir -> ShowS
showsPrec :: Int -> PlanarRelativeDir -> ShowS
$cshow :: PlanarRelativeDir -> String
show :: PlanarRelativeDir -> String
$cshowList :: [PlanarRelativeDir] -> ShowS
showList :: [PlanarRelativeDir] -> ShowS
Show, ReadPrec [PlanarRelativeDir]
ReadPrec PlanarRelativeDir
Int -> ReadS PlanarRelativeDir
ReadS [PlanarRelativeDir]
(Int -> ReadS PlanarRelativeDir)
-> ReadS [PlanarRelativeDir]
-> ReadPrec PlanarRelativeDir
-> ReadPrec [PlanarRelativeDir]
-> Read PlanarRelativeDir
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PlanarRelativeDir
readsPrec :: Int -> ReadS PlanarRelativeDir
$creadList :: ReadS [PlanarRelativeDir]
readList :: ReadS [PlanarRelativeDir]
$creadPrec :: ReadPrec PlanarRelativeDir
readPrec :: ReadPrec PlanarRelativeDir
$creadListPrec :: ReadPrec [PlanarRelativeDir]
readListPrec :: ReadPrec [PlanarRelativeDir]
Read, (forall x. PlanarRelativeDir -> Rep PlanarRelativeDir x)
-> (forall x. Rep PlanarRelativeDir x -> PlanarRelativeDir)
-> Generic PlanarRelativeDir
forall x. Rep PlanarRelativeDir x -> PlanarRelativeDir
forall x. PlanarRelativeDir -> Rep PlanarRelativeDir x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PlanarRelativeDir -> Rep PlanarRelativeDir x
from :: forall x. PlanarRelativeDir -> Rep PlanarRelativeDir x
$cto :: forall x. Rep PlanarRelativeDir x -> PlanarRelativeDir
to :: forall x. Rep PlanarRelativeDir x -> PlanarRelativeDir
Generic, Typeable PlanarRelativeDir
Typeable PlanarRelativeDir =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PlanarRelativeDir
-> c PlanarRelativeDir)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PlanarRelativeDir)
-> (PlanarRelativeDir -> Constr)
-> (PlanarRelativeDir -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PlanarRelativeDir))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PlanarRelativeDir))
-> ((forall b. Data b => b -> b)
-> PlanarRelativeDir -> PlanarRelativeDir)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PlanarRelativeDir -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PlanarRelativeDir -> r)
-> (forall u.
(forall d. Data d => d -> u) -> PlanarRelativeDir -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PlanarRelativeDir -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PlanarRelativeDir -> m PlanarRelativeDir)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PlanarRelativeDir -> m PlanarRelativeDir)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PlanarRelativeDir -> m PlanarRelativeDir)
-> Data PlanarRelativeDir
PlanarRelativeDir -> Constr
PlanarRelativeDir -> DataType
(forall b. Data b => b -> b)
-> PlanarRelativeDir -> PlanarRelativeDir
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> PlanarRelativeDir -> u
forall u. (forall d. Data d => d -> u) -> PlanarRelativeDir -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PlanarRelativeDir -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PlanarRelativeDir -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PlanarRelativeDir -> m PlanarRelativeDir
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PlanarRelativeDir -> m PlanarRelativeDir
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PlanarRelativeDir
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PlanarRelativeDir -> c PlanarRelativeDir
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PlanarRelativeDir)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PlanarRelativeDir)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PlanarRelativeDir -> c PlanarRelativeDir
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PlanarRelativeDir -> c PlanarRelativeDir
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PlanarRelativeDir
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PlanarRelativeDir
$ctoConstr :: PlanarRelativeDir -> Constr
toConstr :: PlanarRelativeDir -> Constr
$cdataTypeOf :: PlanarRelativeDir -> DataType
dataTypeOf :: PlanarRelativeDir -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PlanarRelativeDir)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PlanarRelativeDir)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PlanarRelativeDir)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PlanarRelativeDir)
$cgmapT :: (forall b. Data b => b -> b)
-> PlanarRelativeDir -> PlanarRelativeDir
gmapT :: (forall b. Data b => b -> b)
-> PlanarRelativeDir -> PlanarRelativeDir
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PlanarRelativeDir -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PlanarRelativeDir -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PlanarRelativeDir -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PlanarRelativeDir -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PlanarRelativeDir -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> PlanarRelativeDir -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PlanarRelativeDir -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PlanarRelativeDir -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PlanarRelativeDir -> m PlanarRelativeDir
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PlanarRelativeDir -> m PlanarRelativeDir
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PlanarRelativeDir -> m PlanarRelativeDir
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PlanarRelativeDir -> m PlanarRelativeDir
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PlanarRelativeDir -> m PlanarRelativeDir
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PlanarRelativeDir -> m PlanarRelativeDir
Data, Eq PlanarRelativeDir
Eq PlanarRelativeDir =>
(Int -> PlanarRelativeDir -> Int)
-> (PlanarRelativeDir -> Int) -> Hashable PlanarRelativeDir
Int -> PlanarRelativeDir -> Int
PlanarRelativeDir -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> PlanarRelativeDir -> Int
hashWithSalt :: Int -> PlanarRelativeDir -> Int
$chash :: PlanarRelativeDir -> Int
hash :: PlanarRelativeDir -> Int
Hashable, Int -> PlanarRelativeDir
PlanarRelativeDir -> Int
PlanarRelativeDir -> [PlanarRelativeDir]
PlanarRelativeDir -> PlanarRelativeDir
PlanarRelativeDir -> PlanarRelativeDir -> [PlanarRelativeDir]
PlanarRelativeDir
-> PlanarRelativeDir -> PlanarRelativeDir -> [PlanarRelativeDir]
(PlanarRelativeDir -> PlanarRelativeDir)
-> (PlanarRelativeDir -> PlanarRelativeDir)
-> (Int -> PlanarRelativeDir)
-> (PlanarRelativeDir -> Int)
-> (PlanarRelativeDir -> [PlanarRelativeDir])
-> (PlanarRelativeDir -> PlanarRelativeDir -> [PlanarRelativeDir])
-> (PlanarRelativeDir -> PlanarRelativeDir -> [PlanarRelativeDir])
-> (PlanarRelativeDir
-> PlanarRelativeDir -> PlanarRelativeDir -> [PlanarRelativeDir])
-> Enum PlanarRelativeDir
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: PlanarRelativeDir -> PlanarRelativeDir
succ :: PlanarRelativeDir -> PlanarRelativeDir
$cpred :: PlanarRelativeDir -> PlanarRelativeDir
pred :: PlanarRelativeDir -> PlanarRelativeDir
$ctoEnum :: Int -> PlanarRelativeDir
toEnum :: Int -> PlanarRelativeDir
$cfromEnum :: PlanarRelativeDir -> Int
fromEnum :: PlanarRelativeDir -> Int
$cenumFrom :: PlanarRelativeDir -> [PlanarRelativeDir]
enumFrom :: PlanarRelativeDir -> [PlanarRelativeDir]
$cenumFromThen :: PlanarRelativeDir -> PlanarRelativeDir -> [PlanarRelativeDir]
enumFromThen :: PlanarRelativeDir -> PlanarRelativeDir -> [PlanarRelativeDir]
$cenumFromTo :: PlanarRelativeDir -> PlanarRelativeDir -> [PlanarRelativeDir]
enumFromTo :: PlanarRelativeDir -> PlanarRelativeDir -> [PlanarRelativeDir]
$cenumFromThenTo :: PlanarRelativeDir
-> PlanarRelativeDir -> PlanarRelativeDir -> [PlanarRelativeDir]
enumFromThenTo :: PlanarRelativeDir
-> PlanarRelativeDir -> PlanarRelativeDir -> [PlanarRelativeDir]
Enum, PlanarRelativeDir
PlanarRelativeDir -> PlanarRelativeDir -> Bounded PlanarRelativeDir
forall a. a -> a -> Bounded a
$cminBound :: PlanarRelativeDir
minBound :: PlanarRelativeDir
$cmaxBound :: PlanarRelativeDir
maxBound :: PlanarRelativeDir
Bounded)
instance FromJSON PlanarRelativeDir where
parseJSON :: Value -> Parser PlanarRelativeDir
parseJSON = Options -> Value -> Parser PlanarRelativeDir
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
directionJsonOptions
instance ToJSON PlanarRelativeDir where
toJSON :: PlanarRelativeDir -> Value
toJSON = Options -> PlanarRelativeDir -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
directionJsonOptions
data Direction = DAbsolute AbsoluteDir | DRelative RelativeDir
deriving (Direction -> Direction -> Bool
(Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool) -> Eq Direction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Direction -> Direction -> Bool
== :: Direction -> Direction -> Bool
$c/= :: Direction -> Direction -> Bool
/= :: Direction -> Direction -> Bool
Eq, Eq Direction
Eq Direction =>
(Direction -> Direction -> Ordering)
-> (Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool)
-> (Direction -> Direction -> Direction)
-> (Direction -> Direction -> Direction)
-> Ord Direction
Direction -> Direction -> Bool
Direction -> Direction -> Ordering
Direction -> Direction -> Direction
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
$ccompare :: Direction -> Direction -> Ordering
compare :: Direction -> Direction -> Ordering
$c< :: Direction -> Direction -> Bool
< :: Direction -> Direction -> Bool
$c<= :: Direction -> Direction -> Bool
<= :: Direction -> Direction -> Bool
$c> :: Direction -> Direction -> Bool
> :: Direction -> Direction -> Bool
$c>= :: Direction -> Direction -> Bool
>= :: Direction -> Direction -> Bool
$cmax :: Direction -> Direction -> Direction
max :: Direction -> Direction -> Direction
$cmin :: Direction -> Direction -> Direction
min :: Direction -> Direction -> Direction
Ord, Int -> Direction -> ShowS
[Direction] -> ShowS
Direction -> String
(Int -> Direction -> ShowS)
-> (Direction -> String)
-> ([Direction] -> ShowS)
-> Show Direction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Direction -> ShowS
showsPrec :: Int -> Direction -> ShowS
$cshow :: Direction -> String
show :: Direction -> String
$cshowList :: [Direction] -> ShowS
showList :: [Direction] -> ShowS
Show, ReadPrec [Direction]
ReadPrec Direction
Int -> ReadS Direction
ReadS [Direction]
(Int -> ReadS Direction)
-> ReadS [Direction]
-> ReadPrec Direction
-> ReadPrec [Direction]
-> Read Direction
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Direction
readsPrec :: Int -> ReadS Direction
$creadList :: ReadS [Direction]
readList :: ReadS [Direction]
$creadPrec :: ReadPrec Direction
readPrec :: ReadPrec Direction
$creadListPrec :: ReadPrec [Direction]
readListPrec :: ReadPrec [Direction]
Read, (forall x. Direction -> Rep Direction x)
-> (forall x. Rep Direction x -> Direction) -> Generic Direction
forall x. Rep Direction x -> Direction
forall x. Direction -> Rep Direction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Direction -> Rep Direction x
from :: forall x. Direction -> Rep Direction x
$cto :: forall x. Rep Direction x -> Direction
to :: forall x. Rep Direction x -> Direction
Generic, Typeable Direction
Typeable Direction =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Direction -> c Direction)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Direction)
-> (Direction -> Constr)
-> (Direction -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Direction))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Direction))
-> ((forall b. Data b => b -> b) -> Direction -> Direction)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Direction -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Direction -> r)
-> (forall u. (forall d. Data d => d -> u) -> Direction -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Direction -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Direction -> m Direction)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Direction -> m Direction)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Direction -> m Direction)
-> Data Direction
Direction -> Constr
Direction -> DataType
(forall b. Data b => b -> b) -> Direction -> Direction
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Direction -> u
forall u. (forall d. Data d => d -> u) -> Direction -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Direction -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Direction -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Direction -> m Direction
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Direction -> m Direction
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Direction
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Direction -> c Direction
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Direction)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Direction)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Direction -> c Direction
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Direction -> c Direction
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Direction
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Direction
$ctoConstr :: Direction -> Constr
toConstr :: Direction -> Constr
$cdataTypeOf :: Direction -> DataType
dataTypeOf :: Direction -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Direction)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Direction)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Direction)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Direction)
$cgmapT :: (forall b. Data b => b -> b) -> Direction -> Direction
gmapT :: (forall b. Data b => b -> b) -> Direction -> Direction
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Direction -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Direction -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Direction -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Direction -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Direction -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Direction -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Direction -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Direction -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Direction -> m Direction
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Direction -> m Direction
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Direction -> m Direction
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Direction -> m Direction
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Direction -> m Direction
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Direction -> m Direction
Data, Eq Direction
Eq Direction =>
(Int -> Direction -> Int)
-> (Direction -> Int) -> Hashable Direction
Int -> Direction -> Int
Direction -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Direction -> Int
hashWithSalt :: Int -> Direction -> Int
$chash :: Direction -> Int
hash :: Direction -> Int
Hashable)
instance FromJSON Direction where
parseJSON :: Value -> Parser Direction
parseJSON = Options -> Value -> Parser Direction
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
optionsMinimize
instance ToJSON Direction where
toJSON :: Direction -> Value
toJSON = Options -> Direction -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
optionsMinimize
directionSyntax :: Direction -> Text
directionSyntax :: Direction -> Text
directionSyntax Direction
d = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ShowS
directionJsonModifier ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ case Direction
d of
DAbsolute AbsoluteDir
x -> AbsoluteDir -> String
forall a. Show a => a -> String
show AbsoluteDir
x
DRelative RelativeDir
x -> case RelativeDir
x of
DPlanar PlanarRelativeDir
y -> PlanarRelativeDir -> String
forall a. Show a => a -> String
show PlanarRelativeDir
y
RelativeDir
_ -> RelativeDir -> String
forall a. Show a => a -> String
show RelativeDir
x
instance PrettyPrec Direction where
prettyPrec :: forall ann. Int -> Direction -> Doc ann
prettyPrec Int
_ = Text -> Doc ann
forall ann. Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Text -> Doc ann) -> (Direction -> Text) -> Direction -> Doc ann
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Direction -> Text
directionSyntax
isCardinal :: Direction -> Bool
isCardinal :: Direction -> Bool
isCardinal = \case
DAbsolute AbsoluteDir
_ -> Bool
True
Direction
_ -> Bool
False
allDirs :: [Direction]
allDirs :: [Direction]
allDirs = (AbsoluteDir -> Direction) -> [AbsoluteDir] -> [Direction]
forall a b. (a -> b) -> [a] -> [b]
map AbsoluteDir -> Direction
DAbsolute [AbsoluteDir]
forall a. (Enum a, Bounded a) => [a]
enumerate [Direction] -> [Direction] -> [Direction]
forall a. Semigroup a => a -> a -> a
<> (RelativeDir -> Direction) -> [RelativeDir] -> [Direction]
forall a b. (a -> b) -> [a] -> [b]
map RelativeDir -> Direction
DRelative (RelativeDir
DDown RelativeDir -> [RelativeDir] -> [RelativeDir]
forall a. a -> [a] -> [a]
: (PlanarRelativeDir -> RelativeDir)
-> [PlanarRelativeDir] -> [RelativeDir]
forall a b. (a -> b) -> [a] -> [b]
map PlanarRelativeDir -> RelativeDir
DPlanar [PlanarRelativeDir]
forall a. (Enum a, Bounded a) => [a]
enumerate)