{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
module Brick.Types.Common
  ( Location(..)
  , locL
  , origin
  , Edges(..)
  , eTopL, eBottomL, eRightL, eLeftL
  ) where

import Brick.Types.TH (suffixLenses)
import qualified Data.Semigroup as Sem
import GHC.Generics
import Control.DeepSeq
import Lens.Micro (_1, _2)
import Lens.Micro.Internal (Field1, Field2)

-- | A terminal screen location.
data Location = Location { Location -> (Int, Int)
loc :: (Int, Int)
                         -- ^ (Column, Row)
                         }
                deriving (Int -> Location -> ShowS
[Location] -> ShowS
Location -> String
(Int -> Location -> ShowS)
-> (Location -> String) -> ([Location] -> ShowS) -> Show Location
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Location] -> ShowS
$cshowList :: [Location] -> ShowS
show :: Location -> String
$cshow :: Location -> String
showsPrec :: Int -> Location -> ShowS
$cshowsPrec :: Int -> Location -> ShowS
Show, Location -> Location -> Bool
(Location -> Location -> Bool)
-> (Location -> Location -> Bool) -> Eq Location
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Location -> Location -> Bool
$c/= :: Location -> Location -> Bool
== :: Location -> Location -> Bool
$c== :: Location -> Location -> Bool
Eq, Eq Location
Eq Location
-> (Location -> Location -> Ordering)
-> (Location -> Location -> Bool)
-> (Location -> Location -> Bool)
-> (Location -> Location -> Bool)
-> (Location -> Location -> Bool)
-> (Location -> Location -> Location)
-> (Location -> Location -> Location)
-> Ord Location
Location -> Location -> Bool
Location -> Location -> Ordering
Location -> Location -> Location
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
min :: Location -> Location -> Location
$cmin :: Location -> Location -> Location
max :: Location -> Location -> Location
$cmax :: Location -> Location -> Location
>= :: Location -> Location -> Bool
$c>= :: Location -> Location -> Bool
> :: Location -> Location -> Bool
$c> :: Location -> Location -> Bool
<= :: Location -> Location -> Bool
$c<= :: Location -> Location -> Bool
< :: Location -> Location -> Bool
$c< :: Location -> Location -> Bool
compare :: Location -> Location -> Ordering
$ccompare :: Location -> Location -> Ordering
$cp1Ord :: Eq Location
Ord, ReadPrec [Location]
ReadPrec Location
Int -> ReadS Location
ReadS [Location]
(Int -> ReadS Location)
-> ReadS [Location]
-> ReadPrec Location
-> ReadPrec [Location]
-> Read Location
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Location]
$creadListPrec :: ReadPrec [Location]
readPrec :: ReadPrec Location
$creadPrec :: ReadPrec Location
readList :: ReadS [Location]
$creadList :: ReadS [Location]
readsPrec :: Int -> ReadS Location
$creadsPrec :: Int -> ReadS Location
Read, (forall x. Location -> Rep Location x)
-> (forall x. Rep Location x -> Location) -> Generic Location
forall x. Rep Location x -> Location
forall x. Location -> Rep Location x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Location x -> Location
$cfrom :: forall x. Location -> Rep Location x
Generic, Location -> ()
(Location -> ()) -> NFData Location
forall a. (a -> ()) -> NFData a
rnf :: Location -> ()
$crnf :: Location -> ()
NFData)

suffixLenses ''Location

instance Field1 Location Location Int Int where
    _1 :: (Int -> f Int) -> Location -> f Location
_1 = ((Int, Int) -> f (Int, Int)) -> Location -> f Location
Lens' Location (Int, Int)
locL(((Int, Int) -> f (Int, Int)) -> Location -> f Location)
-> ((Int -> f Int) -> (Int, Int) -> f (Int, Int))
-> (Int -> f Int)
-> Location
-> f Location
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Int -> f Int) -> (Int, Int) -> f (Int, Int)
forall s t a b. Field1 s t a b => Lens s t a b
_1

instance Field2 Location Location Int Int where
    _2 :: (Int -> f Int) -> Location -> f Location
_2 = ((Int, Int) -> f (Int, Int)) -> Location -> f Location
Lens' Location (Int, Int)
locL(((Int, Int) -> f (Int, Int)) -> Location -> f Location)
-> ((Int -> f Int) -> (Int, Int) -> f (Int, Int))
-> (Int -> f Int)
-> Location
-> f Location
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Int -> f Int) -> (Int, Int) -> f (Int, Int)
forall s t a b. Field2 s t a b => Lens s t a b
_2

-- | The origin (upper-left corner).
origin :: Location
origin :: Location
origin = (Int, Int) -> Location
Location (Int
0, Int
0)

instance Sem.Semigroup Location where
    (Location (Int
w1, Int
h1)) <> :: Location -> Location -> Location
<> (Location (Int
w2, Int
h2)) = (Int, Int) -> Location
Location (Int
w1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
w2, Int
h1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
h2)

instance Monoid Location where
    mempty :: Location
mempty = Location
origin
    mappend :: Location -> Location -> Location
mappend = Location -> Location -> Location
forall a. Semigroup a => a -> a -> a
(Sem.<>)

data Edges a = Edges { Edges a -> a
eTop, Edges a -> a
eBottom, Edges a -> a
eLeft, Edges a -> a
eRight :: a }
    deriving (Edges a -> Edges a -> Bool
(Edges a -> Edges a -> Bool)
-> (Edges a -> Edges a -> Bool) -> Eq (Edges a)
forall a. Eq a => Edges a -> Edges a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Edges a -> Edges a -> Bool
$c/= :: forall a. Eq a => Edges a -> Edges a -> Bool
== :: Edges a -> Edges a -> Bool
$c== :: forall a. Eq a => Edges a -> Edges a -> Bool
Eq, Eq (Edges a)
Eq (Edges a)
-> (Edges a -> Edges a -> Ordering)
-> (Edges a -> Edges a -> Bool)
-> (Edges a -> Edges a -> Bool)
-> (Edges a -> Edges a -> Bool)
-> (Edges a -> Edges a -> Bool)
-> (Edges a -> Edges a -> Edges a)
-> (Edges a -> Edges a -> Edges a)
-> Ord (Edges a)
Edges a -> Edges a -> Bool
Edges a -> Edges a -> Ordering
Edges a -> Edges a -> Edges a
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
forall a. Ord a => Eq (Edges a)
forall a. Ord a => Edges a -> Edges a -> Bool
forall a. Ord a => Edges a -> Edges a -> Ordering
forall a. Ord a => Edges a -> Edges a -> Edges a
min :: Edges a -> Edges a -> Edges a
$cmin :: forall a. Ord a => Edges a -> Edges a -> Edges a
max :: Edges a -> Edges a -> Edges a
$cmax :: forall a. Ord a => Edges a -> Edges a -> Edges a
>= :: Edges a -> Edges a -> Bool
$c>= :: forall a. Ord a => Edges a -> Edges a -> Bool
> :: Edges a -> Edges a -> Bool
$c> :: forall a. Ord a => Edges a -> Edges a -> Bool
<= :: Edges a -> Edges a -> Bool
$c<= :: forall a. Ord a => Edges a -> Edges a -> Bool
< :: Edges a -> Edges a -> Bool
$c< :: forall a. Ord a => Edges a -> Edges a -> Bool
compare :: Edges a -> Edges a -> Ordering
$ccompare :: forall a. Ord a => Edges a -> Edges a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (Edges a)
Ord, ReadPrec [Edges a]
ReadPrec (Edges a)
Int -> ReadS (Edges a)
ReadS [Edges a]
(Int -> ReadS (Edges a))
-> ReadS [Edges a]
-> ReadPrec (Edges a)
-> ReadPrec [Edges a]
-> Read (Edges a)
forall a. Read a => ReadPrec [Edges a]
forall a. Read a => ReadPrec (Edges a)
forall a. Read a => Int -> ReadS (Edges a)
forall a. Read a => ReadS [Edges a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Edges a]
$creadListPrec :: forall a. Read a => ReadPrec [Edges a]
readPrec :: ReadPrec (Edges a)
$creadPrec :: forall a. Read a => ReadPrec (Edges a)
readList :: ReadS [Edges a]
$creadList :: forall a. Read a => ReadS [Edges a]
readsPrec :: Int -> ReadS (Edges a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Edges a)
Read, Int -> Edges a -> ShowS
[Edges a] -> ShowS
Edges a -> String
(Int -> Edges a -> ShowS)
-> (Edges a -> String) -> ([Edges a] -> ShowS) -> Show (Edges a)
forall a. Show a => Int -> Edges a -> ShowS
forall a. Show a => [Edges a] -> ShowS
forall a. Show a => Edges a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Edges a] -> ShowS
$cshowList :: forall a. Show a => [Edges a] -> ShowS
show :: Edges a -> String
$cshow :: forall a. Show a => Edges a -> String
showsPrec :: Int -> Edges a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Edges a -> ShowS
Show, a -> Edges b -> Edges a
(a -> b) -> Edges a -> Edges b
(forall a b. (a -> b) -> Edges a -> Edges b)
-> (forall a b. a -> Edges b -> Edges a) -> Functor Edges
forall a b. a -> Edges b -> Edges a
forall a b. (a -> b) -> Edges a -> Edges b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Edges b -> Edges a
$c<$ :: forall a b. a -> Edges b -> Edges a
fmap :: (a -> b) -> Edges a -> Edges b
$cfmap :: forall a b. (a -> b) -> Edges a -> Edges b
Functor, (forall x. Edges a -> Rep (Edges a) x)
-> (forall x. Rep (Edges a) x -> Edges a) -> Generic (Edges a)
forall x. Rep (Edges a) x -> Edges a
forall x. Edges a -> Rep (Edges a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Edges a) x -> Edges a
forall a x. Edges a -> Rep (Edges a) x
$cto :: forall a x. Rep (Edges a) x -> Edges a
$cfrom :: forall a x. Edges a -> Rep (Edges a) x
Generic, Edges a -> ()
(Edges a -> ()) -> NFData (Edges a)
forall a. NFData a => Edges a -> ()
forall a. (a -> ()) -> NFData a
rnf :: Edges a -> ()
$crnf :: forall a. NFData a => Edges a -> ()
NFData)

suffixLenses ''Edges

instance Applicative Edges where
    pure :: a -> Edges a
pure a
a = a -> a -> a -> a -> Edges a
forall a. a -> a -> a -> a -> Edges a
Edges a
a a
a a
a a
a
    Edges a -> b
ft a -> b
fb a -> b
fl a -> b
fr <*> :: Edges (a -> b) -> Edges a -> Edges b
<*> Edges a
vt a
vb a
vl a
vr =
        b -> b -> b -> b -> Edges b
forall a. a -> a -> a -> a -> Edges a
Edges (a -> b
ft a
vt) (a -> b
fb a
vb) (a -> b
fl a
vl) (a -> b
fr a
vr)

instance Monad Edges where
    Edges a
vt a
vb a
vl a
vr >>= :: Edges a -> (a -> Edges b) -> Edges b
>>= a -> Edges b
f = b -> b -> b -> b -> Edges b
forall a. a -> a -> a -> a -> Edges a
Edges
        (Edges b -> b
forall a. Edges a -> a
eTop    (a -> Edges b
f a
vt))
        (Edges b -> b
forall a. Edges a -> a
eBottom (a -> Edges b
f a
vb))
        (Edges b -> b
forall a. Edges a -> a
eLeft   (a -> Edges b
f a
vl))
        (Edges b -> b
forall a. Edges a -> a
eRight  (a -> Edges b
f a
vr))