{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE UndecidableInstances #-}
module Reflex.Vty.Test.Monad.Host (
module Reflex.Test.Monad.Host
, ReflexVtyTestT
, queueVtyEvent
, vtyInputTriggerRefs
, userInputTriggerRefs
, userOutputs
, vtyOutputs
, queueMouseEvent
, queueMouseEventInRegion
, queueMouseEventInRegionGated
, queueMouseDrag
, queueMouseDragInRegion
, runReflexVtyTestT
, ReflexVtyTestApp(..)
, runReflexVtyTestApp
) where
import Relude hiding (getFirst)
import Control.Monad.Ref
import qualified Data.Map as Map
import qualified Graphics.Vty as V
import Potato.Reflex.Vty.Widget
import Reflex
import Reflex.Host.Class
import Reflex.Test.Monad.Host (MonadReflexTest (..), ReflexTestT,
ReflexTriggerRef,
TestGuestConstraints, TestGuestT,
runReflexTestT)
import Reflex.Vty
import Control.Monad.Fix
import Data.Bimap (Bimap)
import qualified Data.Bimap as Bimap
import Data.Semigroup
type ReflexVtyTestT t uintref uout m = ReflexTestT t (uintref, ReflexTriggerRef t m VtyEvent) (uout, Behavior t [V.Image]) m
queueVtyEvent :: (MonadRef m) => VtyEvent -> ReflexVtyTestT t uintref uout m ()
queueVtyEvent :: forall (m :: * -> *) t uintref uout.
MonadRef m =>
VtyEvent -> ReflexVtyTestT t uintref uout m ()
queueVtyEvent VtyEvent
vtyev = do
(uintref
_, Ref m (Maybe (EventTrigger t VtyEvent))
vtytref) <- forall t (m :: * -> *).
MonadReflexTest t m =>
m (InputTriggerRefs m)
inputTriggerRefs
forall t (m :: * -> *) a.
MonadReflexTest t m =>
Ref (InnerMonad m) (Maybe (EventTrigger t a)) -> a -> m ()
queueEventTriggerRef Ref m (Maybe (EventTrigger t VtyEvent))
vtytref VtyEvent
vtyev
vtyInputTriggerRefs :: (MonadRef m) => ReflexVtyTestT t uintref uout m (ReflexTriggerRef t m VtyEvent)
vtyInputTriggerRefs :: forall (m :: * -> *) t uintref uout.
MonadRef m =>
ReflexVtyTestT t uintref uout m (ReflexTriggerRef t m VtyEvent)
vtyInputTriggerRefs = do
(uintref
_, Ref m (Maybe (EventTrigger t VtyEvent))
vtytrefs) <- forall t (m :: * -> *).
MonadReflexTest t m =>
m (InputTriggerRefs m)
inputTriggerRefs
forall (m :: * -> *) a. Monad m => a -> m a
return Ref m (Maybe (EventTrigger t VtyEvent))
vtytrefs
userInputTriggerRefs :: (MonadRef m) => ReflexVtyTestT t uintref uout m uintref
userInputTriggerRefs :: forall (m :: * -> *) t uintref uout.
MonadRef m =>
ReflexVtyTestT t uintref uout m uintref
userInputTriggerRefs = do
(uintref
usertrefs, Ref m (Maybe (EventTrigger t VtyEvent))
_) <- forall t (m :: * -> *).
MonadReflexTest t m =>
m (InputTriggerRefs m)
inputTriggerRefs
forall (m :: * -> *) a. Monad m => a -> m a
return uintref
usertrefs
userOutputs :: (MonadRef m) => ReflexVtyTestT t uintref uout m uout
userOutputs :: forall (m :: * -> *) t uintref uout.
MonadRef m =>
ReflexVtyTestT t uintref uout m uout
userOutputs = do
(uout
useroutputs, Behavior t [Image]
_) <- forall t (m :: * -> *). MonadReflexTest t m => m (OutputEvents m)
outputs
forall (m :: * -> *) a. Monad m => a -> m a
return uout
useroutputs
vtyOutputs :: (MonadRef m) => ReflexVtyTestT t uintref uout m (Behavior t [V.Image])
vtyOutputs :: forall (m :: * -> *) t uintref uout.
MonadRef m =>
ReflexVtyTestT t uintref uout m (Behavior t [Image])
vtyOutputs = do
(uout
_, Behavior t [Image]
vtyoutputs) <- forall t (m :: * -> *). MonadReflexTest t m => m (OutputEvents m)
outputs
forall (m :: * -> *) a. Monad m => a -> m a
return Behavior t [Image]
vtyoutputs
queueMouseEvent :: (MonadRef m)
=> Either MouseDown MouseUp
-> ReflexVtyTestT t uintref uout m ()
queueMouseEvent :: forall (m :: * -> *) t uintref uout.
MonadRef m =>
Either MouseDown MouseUp -> ReflexVtyTestT t uintref uout m ()
queueMouseEvent Either MouseDown MouseUp
mouse = case Either MouseDown MouseUp
mouse of
Left (MouseDown Button
b (Int, Int)
c [Modifier]
mods) -> forall (m :: * -> *) t uintref uout.
MonadRef m =>
VtyEvent -> ReflexVtyTestT t uintref uout m ()
queueVtyEvent forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Int -> Button -> [Modifier] -> VtyEvent
V.EvMouseDown (Int, Int)
c Button
b [Modifier]
mods
Right (MouseUp Maybe Button
b (Int, Int)
c) -> forall (m :: * -> *) t uintref uout.
MonadRef m =>
VtyEvent -> ReflexVtyTestT t uintref uout m ()
queueVtyEvent forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Int -> Maybe Button -> VtyEvent
V.EvMouseUp (Int, Int)
c Maybe Button
b
queueMouseEventInRegion :: (Reflex t, MonadSample t m, MonadRef m)
=> Dynamic t Region
-> Either MouseDown MouseUp
-> ReflexVtyTestT t uintref uout m ()
queueMouseEventInRegion :: forall t (m :: * -> *) uintref uout.
(Reflex t, MonadSample t m, MonadRef m) =>
Dynamic t Region
-> Either MouseDown MouseUp -> ReflexVtyTestT t uintref uout m ()
queueMouseEventInRegion Dynamic t Region
dr Either MouseDown MouseUp
mouse = do
let
absCoords :: Region -> (Int, Int) -> (Int, Int)
absCoords (Region Int
l Int
t Int
_ Int
_) (Int
x,Int
y) = (Int
xforall a. Num a => a -> a -> a
+Int
l, Int
yforall a. Num a => a -> a -> a
+Int
t)
Region
region <- forall {k} (t :: k) (m :: * -> *) a.
MonadSample t m =>
Behavior t a -> m a
sample forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (t :: k) a. Reflex t => Dynamic t a -> Behavior t a
current forall a b. (a -> b) -> a -> b
$ Dynamic t Region
dr
case Either MouseDown MouseUp
mouse of
Left (MouseDown Button
b (Int, Int)
c [Modifier]
mods) -> forall (m :: * -> *) t uintref uout.
MonadRef m =>
VtyEvent -> ReflexVtyTestT t uintref uout m ()
queueVtyEvent forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Int -> Button -> [Modifier] -> VtyEvent
V.EvMouseDown (Region -> (Int, Int) -> (Int, Int)
absCoords Region
region (Int, Int)
c) Button
b [Modifier]
mods
Right (MouseUp Maybe Button
b (Int, Int)
c) -> forall (m :: * -> *) t uintref uout.
MonadRef m =>
VtyEvent -> ReflexVtyTestT t uintref uout m ()
queueVtyEvent forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Int -> Maybe Button -> VtyEvent
V.EvMouseUp (Region -> (Int, Int) -> (Int, Int)
absCoords Region
region (Int, Int)
c) Maybe Button
b
queueMouseEventInRegionGated :: (Reflex t, MonadSample t m, MonadRef m)
=> Dynamic t Region
-> Either MouseDown MouseUp
-> ReflexVtyTestT t uintref uout m Bool
queueMouseEventInRegionGated :: forall t (m :: * -> *) uintref uout.
(Reflex t, MonadSample t m, MonadRef m) =>
Dynamic t Region
-> Either MouseDown MouseUp -> ReflexVtyTestT t uintref uout m Bool
queueMouseEventInRegionGated Dynamic t Region
dr Either MouseDown MouseUp
mouse = do
Region
region <- forall {k} (t :: k) (m :: * -> *) a.
MonadSample t m =>
Behavior t a -> m a
sample forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (t :: k) a. Reflex t => Dynamic t a -> Behavior t a
current forall a b. (a -> b) -> a -> b
$ Dynamic t Region
dr
let
absCoords :: Region -> (Int, Int) -> (Int, Int)
absCoords (Region Int
l Int
t Int
_ Int
_) (Int
x,Int
y) = (Int
xforall a. Num a => a -> a -> a
+Int
l, Int
yforall a. Num a => a -> a -> a
+Int
t)
coordinates :: (Int, Int)
coordinates = case Either MouseDown MouseUp
mouse of
Left (MouseDown Button
_ (Int, Int)
c [Modifier]
_) -> (Int, Int)
c
Right (MouseUp Maybe Button
_ (Int, Int)
c) -> (Int, Int)
c
withinRegion :: Region -> (Int, Int) -> Bool
withinRegion (Region Int
_ Int
_ Int
w Int
h) (Int
x,Int
y) = Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *). Foldable t => t Bool -> Bool
or [ Int
x forall a. Ord a => a -> a -> Bool
< Int
0, Int
y forall a. Ord a => a -> a -> Bool
< Int
0, Int
x forall a. Ord a => a -> a -> Bool
>= Int
w, Int
y forall a. Ord a => a -> a -> Bool
>= Int
h ]
if Region -> (Int, Int) -> Bool
withinRegion Region
region (Int, Int)
coordinates
then do
case Either MouseDown MouseUp
mouse of
Left (MouseDown Button
b (Int, Int)
c [Modifier]
mods) -> forall (m :: * -> *) t uintref uout.
MonadRef m =>
VtyEvent -> ReflexVtyTestT t uintref uout m ()
queueVtyEvent forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Int -> Button -> [Modifier] -> VtyEvent
V.EvMouseDown (Region -> (Int, Int) -> (Int, Int)
absCoords Region
region (Int, Int)
c) Button
b [Modifier]
mods
Right (MouseUp Maybe Button
b (Int, Int)
c) -> forall (m :: * -> *) t uintref uout.
MonadRef m =>
VtyEvent -> ReflexVtyTestT t uintref uout m ()
queueVtyEvent forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Int -> Maybe Button -> VtyEvent
V.EvMouseUp (Region -> (Int, Int) -> (Int, Int)
absCoords Region
region (Int, Int)
c) Maybe Button
b
return Bool
True
else forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
queueMouseDrag :: (Reflex t, MonadSample t m, MonadRef m)
=> V.Button
-> [V.Modifier]
-> NonEmpty (Int,Int)
-> ((Int,Int) -> ReadPhase m a)
-> ReflexVtyTestT t uintref uout m (NonEmpty [a])
queueMouseDrag :: forall t (m :: * -> *) a uintref uout.
(Reflex t, MonadSample t m, MonadRef m) =>
Button
-> [Modifier]
-> NonEmpty (Int, Int)
-> ((Int, Int) -> ReadPhase m a)
-> ReflexVtyTestT t uintref uout m (NonEmpty [a])
queueMouseDrag = forall t (m :: * -> *) a uintref uout.
(Reflex t, MonadSample t m, MonadRef m) =>
Dynamic t Region
-> Button
-> [Modifier]
-> NonEmpty (Int, Int)
-> ((Int, Int) -> ReadPhase m a)
-> ReflexVtyTestT t uintref uout m (NonEmpty [a])
queueMouseDragInRegion (forall {k} (t :: k) a. Reflex t => a -> Dynamic t a
constDyn forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> Int -> Region
Region Int
0 Int
0 Int
0 Int
0)
queueMouseDragInRegion :: (Reflex t, MonadSample t m, MonadRef m)
=> Dynamic t Region
-> V.Button
-> [V.Modifier]
-> NonEmpty (Int,Int)
-> ((Int,Int) -> ReadPhase m a)
-> ReflexVtyTestT t uintref uout m (NonEmpty [a])
queueMouseDragInRegion :: forall t (m :: * -> *) a uintref uout.
(Reflex t, MonadSample t m, MonadRef m) =>
Dynamic t Region
-> Button
-> [Modifier]
-> NonEmpty (Int, Int)
-> ((Int, Int) -> ReadPhase m a)
-> ReflexVtyTestT t uintref uout m (NonEmpty [a])
queueMouseDragInRegion Dynamic t Region
region Button
b [Modifier]
mods NonEmpty (Int, Int)
ps (Int, Int) -> ReadPhase m a
rps = do
let
dragPs' :: [(Int, Int)]
dragPs' = forall (f :: * -> *) a. IsNonEmpty f a [a] "init" => f a -> [a]
init NonEmpty (Int, Int)
ps
dragPs :: NonEmpty (Int, Int)
dragPs = forall a. a -> Maybe a -> a
fromMaybe (forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall (f :: * -> *) a. IsNonEmpty f a a "head" => f a -> a
head NonEmpty (Int, Int)
ps)) forall a b. (a -> b) -> a -> b
$ forall a b. (NonEmpty a -> b) -> [a] -> Maybe b
viaNonEmpty forall a. a -> a
id [(Int, Int)]
dragPs'
endP :: (Int, Int)
endP = forall (f :: * -> *) a. IsNonEmpty f a a "last" => f a -> a
last NonEmpty (Int, Int)
ps
NonEmpty [a]
initas <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM NonEmpty (Int, Int)
dragPs forall a b. (a -> b) -> a -> b
$ \(Int, Int)
p -> do
forall t (m :: * -> *) uintref uout.
(Reflex t, MonadSample t m, MonadRef m) =>
Dynamic t Region
-> Either MouseDown MouseUp -> ReflexVtyTestT t uintref uout m ()
queueMouseEventInRegion Dynamic t Region
region forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left (Button -> (Int, Int) -> [Modifier] -> MouseDown
MouseDown Button
b (Int, Int)
p [Modifier]
mods)
forall t (m :: * -> *) a.
MonadReflexTest t m =>
ReadPhase (InnerMonad m) a -> m [a]
fireQueuedEventsAndRead ((Int, Int) -> ReadPhase m a
rps (Int, Int)
p)
forall t (m :: * -> *) uintref uout.
(Reflex t, MonadSample t m, MonadRef m) =>
Dynamic t Region
-> Either MouseDown MouseUp -> ReflexVtyTestT t uintref uout m ()
queueMouseEventInRegion Dynamic t Region
region forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right (Maybe Button -> (Int, Int) -> MouseUp
MouseUp (forall a. a -> Maybe a
Just Button
b) (Int, Int)
endP)
[a]
lastas <- forall t (m :: * -> *) a.
MonadReflexTest t m =>
ReadPhase (InnerMonad m) a -> m [a]
fireQueuedEventsAndRead ((Int, Int) -> ReadPhase m a
rps (Int, Int)
endP)
return $ NonEmpty [a]
initas forall a. Semigroup a => a -> a -> a
<> ([a]
lastas forall a. a -> [a] -> NonEmpty a
:| [])
type InnerWidgetConstraints t widget = (
MonadVtyApp t widget
, HasImageWriter t widget
, MonadNodeId widget
, HasDisplayRegion t widget
, HasFocusReader t widget
, HasInput t widget
, HasTheme t widget
)
runReflexVtyTestT :: forall uintref uinev uout t m a. (MonadVtyApp t (TestGuestT t m), TestGuestConstraints t m)
=> (Int, Int)
-> (uinev, uintref)
-> (forall widget. (InnerWidgetConstraints t widget) => uinev -> widget uout)
-> ReflexVtyTestT t uintref uout m a
-> m ()
runReflexVtyTestT :: forall uintref uinev uout t (m :: * -> *) a.
(MonadVtyApp t (TestGuestT t m), TestGuestConstraints t m) =>
(Int, Int)
-> (uinev, uintref)
-> (forall (widget :: * -> *).
InnerWidgetConstraints t widget =>
uinev -> widget uout)
-> ReflexVtyTestT t uintref uout m a
-> m ()
runReflexVtyTestT (Int, Int)
r0 (uinev
uinput, uintref
uinputtrefs) forall (widget :: * -> *).
InnerWidgetConstraints t widget =>
uinev -> widget uout
app ReflexVtyTestT t uintref uout m a
rtm = do
(Event t VtyEvent
vinev, IORef (Maybe (EventTrigger t VtyEvent))
vintref) <- forall t (m :: * -> *) a.
(MonadReflexCreateTrigger t m, MonadRef m, Ref m ~ Ref IO) =>
m (Event t a, Ref m (Maybe (EventTrigger t a)))
newEventWithTriggerRef
Dynamic t (Int, Int)
size <- forall {k} (t :: k) (m :: * -> *) a.
MonadHold t m =>
a -> Event t a -> m (Dynamic t a)
holdDyn (Int, Int)
r0 forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b.
Filterable f =>
f a -> (a -> Maybe b) -> f b
fforMaybe Event t VtyEvent
vinev forall a b. (a -> b) -> a -> b
$ \case
V.EvResize Int
w Int
h -> forall a. a -> Maybe a
Just (Int
w, Int
h)
VtyEvent
_ -> forall a. Maybe a
Nothing
forall intref inev out t (m :: * -> *) a.
TestGuestConstraints t m =>
(inev, intref)
-> (inev -> TestGuestT t m out)
-> ReflexTestT t intref out m a
-> m ()
runReflexTestT
((uinev
uinput, Event t VtyEvent
vinev), (uintref
uinputtrefs, IORef (Maybe (EventTrigger t VtyEvent))
vintref))
(\(uinev
uinput',Event t VtyEvent
_) -> forall {k} (t :: k) (m :: * -> *) a.
(Reflex t, Monad m) =>
Behavior t Attr -> ThemeReader t m a -> m a
runThemeReader (forall {k} (t :: k) a. Reflex t => a -> Behavior t a
constant Attr
V.defAttr) forall a b. (a -> b) -> a -> b
$
forall {k} (t :: k) (m :: * -> *) a.
(Reflex t, Monad m) =>
Dynamic t Bool -> FocusReader t m a -> m a
runFocusReader (forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True) forall a b. (a -> b) -> a -> b
$
forall {k} (t :: k) (m :: * -> *) a.
(Reflex t, Monad m) =>
Dynamic t Region -> DisplayRegion t m a -> m a
runDisplayRegion (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Int
w, Int
h) -> Int -> Int -> Int -> Int -> Region
Region Int
0 Int
0 Int
w Int
h) Dynamic t (Int, Int)
size) forall a b. (a -> b) -> a -> b
$
forall t (m :: * -> *) a.
(Reflex t, Monad m) =>
ImageWriter t m a -> m (a, Behavior t [Image])
runImageWriter forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. MonadIO m => NodeIdT m a -> m a
runNodeIdT forall a b. (a -> b) -> a -> b
$
forall {k} (t :: k) (m :: * -> *) a.
Reflex t =>
Event t VtyEvent -> Input t m a -> m a
runInput Event t VtyEvent
vinev forall a b. (a -> b) -> a -> b
$ do
forall {k} (t :: k) (m :: * -> *).
HasImageWriter t m =>
Behavior t [Image] -> m ()
tellImages forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
ffor (forall {k} (t :: k) a. Reflex t => Dynamic t a -> Behavior t a
current Dynamic t (Int, Int)
size) forall a b. (a -> b) -> a -> b
$ \(Int
w, Int
h) -> [forall d. Integral d => Attr -> Char -> d -> d -> Image
V.charFill Attr
V.defAttr Char
' ' Int
w Int
h]
(forall (widget :: * -> *).
InnerWidgetConstraints t widget =>
uinev -> widget uout
app uinev
uinput'))
ReflexVtyTestT t uintref uout m a
rtm
class ReflexVtyTestApp app t m | app -> t m where
data VtyAppInputTriggerRefs app :: Type
data VtyAppInputEvents app :: Type
data VtyAppOutput app :: Type
getApp :: (InnerWidgetConstraints t widget)
=> VtyAppInputEvents app -> widget (VtyAppOutput app)
makeInputs :: m (VtyAppInputEvents app, VtyAppInputTriggerRefs app)
runReflexVtyTestApp :: (ReflexVtyTestApp app t m, MonadVtyApp t (TestGuestT t m), TestGuestConstraints t m)
=> (Int, Int)
-> ReflexVtyTestT t (VtyAppInputTriggerRefs app) (VtyAppOutput app) m ()
-> m ()
runReflexVtyTestApp :: forall app t (m :: * -> *).
(ReflexVtyTestApp app t m, MonadVtyApp t (TestGuestT t m),
TestGuestConstraints t m) =>
(Int, Int)
-> ReflexVtyTestT
t (VtyAppInputTriggerRefs app) (VtyAppOutput app) m ()
-> m ()
runReflexVtyTestApp (Int, Int)
r0 ReflexVtyTestT
t (VtyAppInputTriggerRefs app) (VtyAppOutput app) m ()
rtm = do
(VtyAppInputEvents app, VtyAppInputTriggerRefs app)
inp <- forall app t (m :: * -> *).
ReflexVtyTestApp app t m =>
m (VtyAppInputEvents app, VtyAppInputTriggerRefs app)
makeInputs
forall uintref uinev uout t (m :: * -> *) a.
(MonadVtyApp t (TestGuestT t m), TestGuestConstraints t m) =>
(Int, Int)
-> (uinev, uintref)
-> (forall (widget :: * -> *).
InnerWidgetConstraints t widget =>
uinev -> widget uout)
-> ReflexVtyTestT t uintref uout m a
-> m ()
runReflexVtyTestT (Int, Int)
r0 (VtyAppInputEvents app, VtyAppInputTriggerRefs app)
inp forall app t (m :: * -> *) (widget :: * -> *).
(ReflexVtyTestApp app t m, InnerWidgetConstraints t widget) =>
VtyAppInputEvents app -> widget (VtyAppOutput app)
getApp ReflexVtyTestT
t (VtyAppInputTriggerRefs app) (VtyAppOutput app) m ()
rtm
integralFractionalDivide :: (Integral a, Fractional b) => a -> a -> b
integralFractionalDivide :: forall a b. (Integral a, Fractional b) => a -> a -> b
integralFractionalDivide a
n a
d = forall a b. (Integral a, Num b) => a -> b
fromIntegral a
n forall a. Fractional a => a -> a -> a
/ forall a b. (Integral a, Num b) => a -> b
fromIntegral a
d