tinytools-vty-0.1.0.1: a terminal based unicode diagram editing tool
Safe HaskellSafe-Inferred
LanguageHaskell2010

Reflex.Vty.Test.Monad.Host

Synopsis

Documentation

runReflexTestT #

Arguments

:: forall intref inev out t m a. TestGuestConstraints t m 
=> (inev, intref)

make sure intref match inev, i.e. return values of newEventWithTriggerRef

-> (inev -> TestGuestT t m out)

network to test

-> ReflexTestT t intref out m a

test monad to run

-> m () 

type TestGuestT t (m :: Type -> Type) = TriggerEventT t (PostBuildT t (PerformEventT t m)) #

type ReflexTriggerRef t (m :: Type -> Type) a = Ref m (Maybe (EventTrigger t a)) #

since we work with this type directly a lot, it helps to wrap it around a type synonym

type family InnerMonad (m :: Type -> Type) :: Type -> Type #

the inner monad that reflex is running in likely 'SpiderHost Global'

Instances

Instances details
type InnerMonad (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

type InnerMonad (ReflexTestT t intref out m) = m

type family OutputEvents (m :: Type -> Type) #

in practice, this will likely be a record containing events and behaviors for the monad user to build a ReadPhase that is passed into fireQueuedEventsAndRead

Instances

Instances details
type OutputEvents (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

type OutputEvents (ReflexTestT t intref out m) = out

type family InputTriggerRefs (m :: Type -> Type) #

since event subscriptions also happen within the monad, input triggers created via newEventWithTriggerRef may be stuck in the Nothing state as there are no listeners yet therefore it's necessary to pass in IORefs to the EventTriggers, thus the name of this type in practice, this will likely be a record containing many trigger refs and the monad user must deref them all

Instances

Instances details
type InputTriggerRefs (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

type InputTriggerRefs (ReflexTestT t intref out m) = intref

class MonadReflexTest t (m :: Type -> Type) | m -> t where #

 

Associated Types

type InputTriggerRefs (m :: Type -> Type) #

since event subscriptions also happen within the monad, input triggers created via newEventWithTriggerRef may be stuck in the Nothing state as there are no listeners yet therefore it's necessary to pass in IORefs to the EventTriggers, thus the name of this type in practice, this will likely be a record containing many trigger refs and the monad user must deref them all

type OutputEvents (m :: Type -> Type) #

in practice, this will likely be a record containing events and behaviors for the monad user to build a ReadPhase that is passed into fireQueuedEventsAndRead

type InnerMonad (m :: Type -> Type) :: Type -> Type #

the inner monad that reflex is running in likely 'SpiderHost Global'

Methods

inputTriggerRefs :: m (InputTriggerRefs m) #

see comments for InputTriggerRefs

queueEventTrigger :: DSum (EventTrigger t) Identity -> m () #

all queued triggers will fire simultaneous on the next execution of fireQueuedEventsAndRead

queueEventTriggerRef :: Ref (InnerMonad m) (Maybe (EventTrigger t a)) -> a -> m () #

same as queueEventTrigger except works with trigger refs if the trigger ref derefs to Nothing, the event does not get queued

outputs :: m (OutputEvents m) #

see comments for OutputEvents

fireQueuedEventsAndRead :: ReadPhase (InnerMonad m) a -> m [a] #

fire all queued events and run a ReadPhase to produce results from the execution frames readphase takes place in the inner monad

fireQueuedEvents :: m [()] #

same as above with no ReadPhase

Instances

Instances details
MonadRef m => MonadReflexTest t (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

Associated Types

type InputTriggerRefs (ReflexTestT t intref out m) #

type OutputEvents (ReflexTestT t intref out m) #

type InnerMonad (ReflexTestT t intref out m) :: Type -> Type #

Methods

inputTriggerRefs :: ReflexTestT t intref out m (InputTriggerRefs (ReflexTestT t intref out m)) #

queueEventTrigger :: DSum (EventTrigger t) Identity -> ReflexTestT t intref out m () #

queueEventTriggerRef :: Ref (InnerMonad (ReflexTestT t intref out m)) (Maybe (EventTrigger t a)) -> a -> ReflexTestT t intref out m () #

outputs :: ReflexTestT t intref out m (OutputEvents (ReflexTestT t intref out m)) #

fireQueuedEventsAndRead :: ReadPhase (InnerMonad (ReflexTestT t intref out m)) a -> ReflexTestT t intref out m [a] #

fireQueuedEvents :: ReflexTestT t intref out m [()] #

data ReflexTestT t intref out (m :: Type -> Type) a #

implementation of MonadReflexTest

Instances

Instances details
MonadHold t m => MonadHold (t :: Type) (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

Methods

hold :: a -> Event t a -> ReflexTestT t intref out m (Behavior t a) #

holdDyn :: a -> Event t a -> ReflexTestT t intref out m (Dynamic t a) #

holdIncremental :: Patch p => PatchTarget p -> Event t p -> ReflexTestT t intref out m (Incremental t p) #

buildDynamic :: PushM t a -> Event t a -> ReflexTestT t intref out m (Dynamic t a) #

headE :: Event t a -> ReflexTestT t intref out m (Event t a) #

now :: ReflexTestT t intref out m (Event t ()) #

MonadSample t m => MonadSample (t :: Type) (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

Methods

sample :: Behavior t a -> ReflexTestT t intref out m a #

MonadReflexCreateTrigger t m => MonadReflexCreateTrigger t (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

Methods

newEventWithTrigger :: (EventTrigger t a -> IO (IO ())) -> ReflexTestT t intref out m (Event t a) #

newFanEventWithTrigger :: GCompare k => (forall a. k a -> EventTrigger t a -> IO (IO ())) -> ReflexTestT t intref out m (EventSelector t k) #

MonadSubscribeEvent t m => MonadSubscribeEvent t (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

Methods

subscribeEvent :: Event t a -> ReflexTestT t intref out m (EventHandle t a) #

MonadRef m => MonadReflexTest t (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

Associated Types

type InputTriggerRefs (ReflexTestT t intref out m) #

type OutputEvents (ReflexTestT t intref out m) #

type InnerMonad (ReflexTestT t intref out m) :: Type -> Type #

Methods

inputTriggerRefs :: ReflexTestT t intref out m (InputTriggerRefs (ReflexTestT t intref out m)) #

queueEventTrigger :: DSum (EventTrigger t) Identity -> ReflexTestT t intref out m () #

queueEventTriggerRef :: Ref (InnerMonad (ReflexTestT t intref out m)) (Maybe (EventTrigger t a)) -> a -> ReflexTestT t intref out m () #

outputs :: ReflexTestT t intref out m (OutputEvents (ReflexTestT t intref out m)) #

fireQueuedEventsAndRead :: ReadPhase (InnerMonad (ReflexTestT t intref out m)) a -> ReflexTestT t intref out m [a] #

fireQueuedEvents :: ReflexTestT t intref out m [()] #

Monad m => MonadReader (intref, out) (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

Methods

ask :: ReflexTestT t intref out m (intref, out) #

local :: ((intref, out) -> (intref, out)) -> ReflexTestT t intref out m a -> ReflexTestT t intref out m a #

reader :: ((intref, out) -> a) -> ReflexTestT t intref out m a #

Monad m => MonadState (AppState t m) (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

Methods

get :: ReflexTestT t intref out m (AppState t m) #

put :: AppState t m -> ReflexTestT t intref out m () #

state :: (AppState t m -> (a, AppState t m)) -> ReflexTestT t intref out m a #

MonadTrans (ReflexTestT t intref out) 
Instance details

Defined in Reflex.Test.Monad.Host

Methods

lift :: Monad m => m a -> ReflexTestT t intref out m a #

MonadFix m => MonadFix (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

Methods

mfix :: (a -> ReflexTestT t intref out m a) -> ReflexTestT t intref out m a #

MonadIO m => MonadIO (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

Methods

liftIO :: IO a -> ReflexTestT t intref out m a #

Monad m => Applicative (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

Methods

pure :: a -> ReflexTestT t intref out m a #

(<*>) :: ReflexTestT t intref out m (a -> b) -> ReflexTestT t intref out m a -> ReflexTestT t intref out m b #

liftA2 :: (a -> b -> c) -> ReflexTestT t intref out m a -> ReflexTestT t intref out m b -> ReflexTestT t intref out m c #

(*>) :: ReflexTestT t intref out m a -> ReflexTestT t intref out m b -> ReflexTestT t intref out m b #

(<*) :: ReflexTestT t intref out m a -> ReflexTestT t intref out m b -> ReflexTestT t intref out m a #

Functor m => Functor (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

Methods

fmap :: (a -> b) -> ReflexTestT t intref out m a -> ReflexTestT t intref out m b #

(<$) :: a -> ReflexTestT t intref out m b -> ReflexTestT t intref out m a #

Monad m => Monad (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

Methods

(>>=) :: ReflexTestT t intref out m a -> (a -> ReflexTestT t intref out m b) -> ReflexTestT t intref out m b #

(>>) :: ReflexTestT t intref out m a -> ReflexTestT t intref out m b -> ReflexTestT t intref out m b #

return :: a -> ReflexTestT t intref out m a #

type InnerMonad (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

type InnerMonad (ReflexTestT t intref out m) = m
type InputTriggerRefs (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

type InputTriggerRefs (ReflexTestT t intref out m) = intref
type OutputEvents (ReflexTestT t intref out m) 
Instance details

Defined in Reflex.Test.Monad.Host

type OutputEvents (ReflexTestT t intref out m) = out

type ReflexVtyTestT t uintref uout m = ReflexTestT t (uintref, ReflexTriggerRef t m VtyEvent) (uout, Behavior t [Image]) m Source #

reflex-vty variant of ReflexTestT which packages an VtyEvent into the input and 'Behavior t [V.Image]' into the output uintref and uout allow user to add their own inputs and outputs uintref will often just be some singleton type (e.g. ()) as the app being tested still has access to the input 'Event t VtyEvent' through the VtyWidget monad

queueVtyEvent :: MonadRef m => VtyEvent -> ReflexVtyTestT t uintref uout m () Source #

queue a VtyEvent

vtyInputTriggerRefs :: MonadRef m => ReflexVtyTestT t uintref uout m (ReflexTriggerRef t m VtyEvent) Source #

obtain vty inputs

userInputTriggerRefs :: MonadRef m => ReflexVtyTestT t uintref uout m uintref Source #

obtain user defined inputs

userOutputs :: MonadRef m => ReflexVtyTestT t uintref uout m uout Source #

obtain user defined outputs

vtyOutputs :: MonadRef m => ReflexVtyTestT t uintref uout m (Behavior t [Image]) Source #

obtain vty outputs

queueMouseEvent Source #

Arguments

:: MonadRef m 
=> Either MouseDown MouseUp

mouse coordinates are LOCAL to the input region

-> ReflexVtyTestT t uintref uout m () 

queue mouse event

queueMouseEventInRegion Source #

Arguments

:: (Reflex t, MonadSample t m, MonadRef m) 
=> Dynamic t Region 
-> Either MouseDown MouseUp

mouse coordinates are LOCAL to the input region

-> ReflexVtyTestT t uintref uout m () 

queue mouse event in a DynRegion

queueMouseEventInRegionGated Source #

Arguments

:: (Reflex t, MonadSample t m, MonadRef m) 
=> Dynamic t Region 
-> Either MouseDown MouseUp

mouse coordinates are LOCAL to the input region

-> ReflexVtyTestT t uintref uout m Bool 

queue mouse event in a DynRegion if (local) mouse coordinates are outside of the (absolute) region, returns False and does not queue any event

queueMouseDrag Source #

Arguments

:: (Reflex t, MonadSample t m, MonadRef m) 
=> Button

button to press

-> [Modifier]

modifier held during drag

-> NonEmpty (Int, Int)

list of drag positions TODO add something like DragState to this

-> ((Int, Int) -> ReadPhase m a)

ReadPhase to run after each normal drag

-> ReflexVtyTestT t uintref uout m (NonEmpty [a])

collected outputs

queue and fire a series of mouse events representing a mouse drag returns collected outputs

queueMouseDragInRegion Source #

Arguments

:: (Reflex t, MonadSample t m, MonadRef m) 
=> Dynamic t Region 
-> Button

button to press

-> [Modifier]

modifier held during drag

-> NonEmpty (Int, Int)

list of drag positions TODO add something like DragState to this

-> ((Int, Int) -> ReadPhase m a)

ReadPhase to run after each normal drag

-> ReflexVtyTestT t uintref uout m (NonEmpty [a])

collected outputs

same as queueMouseDrag but coordinates are translated to a region

runReflexVtyTestT Source #

Arguments

:: forall uintref uinev uout t m a. (MonadVtyApp t (TestGuestT t m), TestGuestConstraints t m) 
=> (Int, Int)

initial screen size

-> (uinev, uintref)

make sure uintref match uinev, i.e. return values of newEventWithTriggerRef

-> (forall widget. InnerWidgetConstraints t widget => uinev -> widget uout)

VtyWidget to test

-> ReflexVtyTestT t uintref uout m a

test monad to run

-> m () 

run a ReflexVtyTestT analogous to runReflexTestT

class ReflexVtyTestApp app t m | app -> t m where Source #

class to help bind network and types to a ReflexVtyTestT analogous to ReflexTestApp

Associated Types

data VtyAppInputTriggerRefs app :: Type Source #

data VtyAppInputEvents app :: Type Source #

data VtyAppOutput app :: Type Source #

Methods

getApp :: InnerWidgetConstraints t widget => VtyAppInputEvents app -> widget (VtyAppOutput app) Source #

makeInputs :: m (VtyAppInputEvents app, VtyAppInputTriggerRefs app) Source #

runReflexVtyTestApp Source #

Arguments

:: (ReflexVtyTestApp app t m, MonadVtyApp t (TestGuestT t m), TestGuestConstraints t m) 
=> (Int, Int)

initial screen size

-> ReflexVtyTestT t (VtyAppInputTriggerRefs app) (VtyAppOutput app) m () 
-> m ()