tinytools-vty-0.1.0.4: tinytools-vty is a terminal based monospace unicode diagram editing tool
Safe HaskellSafe-Inferred
LanguageHaskell2010

Potato.Flow.Vty.PotatoReader

Synopsis

Documentation

class (Reflex t, Monad m) => HasPotato t m | m -> t where Source #

A class for things that can dynamically gain and lose focus

Methods

askPotato :: m (PotatoConfig t) Source #

Instances

Instances details
HasPotato t m => HasPotato t (NodeIdT m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

HasPotato t m => HasPotato t (ImageWriter t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

HasPotato t m => HasPotato t (Focus t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

askPotato :: Focus t m (PotatoConfig t) Source #

HasPotato t m => HasPotato t (Layout t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

(Monad m, Reflex t) => HasPotato t (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

HasPotato t m => HasPotato t (ReaderT x m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

HasPotato t m => HasPotato t (BehaviorWriterT t x m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

HasPotato t m => HasPotato t (DynamicWriterT t x m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

HasPotato t m => HasPotato t (EventWriterT t x m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

HasPotato t m => HasPotato t (DisplayRegion t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

HasPotato t m => HasPotato t (FocusReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

HasPotato t m => HasPotato t (Input t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

askPotato :: Input t m (PotatoConfig t) Source #

newtype PotatoReader t m a Source #

A widget that has access to information about whether it is focused

Constructors

PotatoReader 

Instances

Instances details
MonadHold t m => MonadHold (t :: Type) (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

hold :: a -> Event t a -> PotatoReader t m (Behavior t a) #

holdDyn :: a -> Event t a -> PotatoReader t m (Dynamic t a) #

holdIncremental :: Patch p => PatchTarget p -> Event t p -> PotatoReader t m (Incremental t p) #

buildDynamic :: PushM t a -> Event t a -> PotatoReader t m (Dynamic t a) #

headE :: Event t a -> PotatoReader t m (Event t a) #

now :: PotatoReader t m (Event t ()) #

MonadSample t m => MonadSample (t :: Type) (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

sample :: Behavior t a -> PotatoReader t m a #

HasDisplayRegion t m => HasDisplayRegion (t :: Type) (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

HasFocusReader t m => HasFocusReader (t :: Type) (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

focus :: PotatoReader t m (Dynamic t Bool) #

localFocus :: (Dynamic t Bool -> Dynamic t Bool) -> PotatoReader t m a -> PotatoReader t m a #

HasImageWriter t m => HasImageWriter (t :: Type) (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

tellImages :: Behavior t [Image] -> PotatoReader t m () #

mapImages :: (Behavior t [Image] -> Behavior t [Image]) -> PotatoReader t m a -> PotatoReader t m a #

(HasInput t m, Monad m) => HasInput (t :: Type) (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

HasTheme t m => HasTheme (t :: Type) (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

HasFocus t m => HasFocus (t :: Type) (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

(Reflex t, HasLayout t m) => HasLayout (t :: Type) (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

(Adjustable t m, MonadFix m, MonadHold t m) => Adjustable t (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

runWithReplace :: PotatoReader t m a -> Event t (PotatoReader t m b) -> PotatoReader t m (a, Event t b) #

traverseIntMapWithKeyWithAdjust :: (Key -> v -> PotatoReader t m v') -> IntMap v -> Event t (PatchIntMap v) -> PotatoReader t m (IntMap v', Event t (PatchIntMap v')) #

traverseDMapWithKeyWithAdjust :: GCompare k => (forall a. k a -> v a -> PotatoReader t m (v' a)) -> DMap k v -> Event t (PatchDMap k v) -> PotatoReader t m (DMap k v', Event t (PatchDMap k v')) #

traverseDMapWithKeyWithAdjustWithMove :: GCompare k => (forall a. k a -> v a -> PotatoReader t m (v' a)) -> DMap k v -> Event t (PatchDMapWithMove k v) -> PotatoReader t m (DMap k v', Event t (PatchDMapWithMove k v')) #

MonadReflexCreateTrigger t m => MonadReflexCreateTrigger t (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

newEventWithTrigger :: (EventTrigger t a -> IO (IO ())) -> PotatoReader t m (Event t a) #

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

NotReady t m => NotReady t (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

notReadyUntil :: Event t a -> PotatoReader t m () #

notReady :: PotatoReader t m () #

PerformEvent t m => PerformEvent t (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Associated Types

type Performable (PotatoReader t m) :: Type -> Type #

PostBuild t m => PostBuild t (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

getPostBuild :: PotatoReader t m (Event t ()) #

TriggerEvent t m => TriggerEvent t (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

newTriggerEvent :: PotatoReader t m (Event t a, a -> IO ()) #

newTriggerEventWithOnComplete :: PotatoReader t m (Event t a, a -> IO () -> IO ()) #

newEventWithLazyTriggerWithOnComplete :: ((a -> IO () -> IO ()) -> IO (IO ())) -> PotatoReader t m (Event t a) #

(Monad m, Reflex t) => HasPotato t (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

MonadTrans (PotatoReader t) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

lift :: Monad m => m a -> PotatoReader t m a #

MonadFix m => MonadFix (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

mfix :: (a -> PotatoReader t m a) -> PotatoReader t m a #

MonadIO m => MonadIO (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

liftIO :: IO a -> PotatoReader t m a #

Applicative m => Applicative (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

pure :: a -> PotatoReader t m a #

(<*>) :: PotatoReader t m (a -> b) -> PotatoReader t m a -> PotatoReader t m b #

liftA2 :: (a -> b -> c) -> PotatoReader t m a -> PotatoReader t m b -> PotatoReader t m c #

(*>) :: PotatoReader t m a -> PotatoReader t m b -> PotatoReader t m b #

(<*) :: PotatoReader t m a -> PotatoReader t m b -> PotatoReader t m a #

Functor m => Functor (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

fmap :: (a -> b) -> PotatoReader t m a -> PotatoReader t m b #

(<$) :: a -> PotatoReader t m b -> PotatoReader t m a #

Monad m => Monad (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Methods

(>>=) :: PotatoReader t m a -> (a -> PotatoReader t m b) -> PotatoReader t m b #

(>>) :: PotatoReader t m a -> PotatoReader t m b -> PotatoReader t m b #

return :: a -> PotatoReader t m a #

MonadRef m => MonadRef (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

Associated Types

type Ref (PotatoReader t m) :: Type -> Type #

Methods

newRef :: a -> PotatoReader t m (Ref (PotatoReader t m) a) #

readRef :: Ref (PotatoReader t m) a -> PotatoReader t m a #

writeRef :: Ref (PotatoReader t m) a -> a -> PotatoReader t m () #

modifyRef :: Ref (PotatoReader t m) a -> (a -> a) -> PotatoReader t m () #

modifyRef' :: Ref (PotatoReader t m) a -> (a -> a) -> PotatoReader t m () #

MonadNodeId m => MonadNodeId (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

type Ref (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

type Ref (PotatoReader t m) = Ref (ReaderT (PotatoConfig t) m)
type Performable (PotatoReader t m) Source # 
Instance details

Defined in Potato.Flow.Vty.PotatoReader

runPotatoReader :: (Reflex t, Monad m) => PotatoReader t m a -> PotatoConfig t -> m a Source #

Run a FocusReader action with the given focus value TODO flip arg order to match ReaderT oops...

Orphan instances

(HasInput t m, Monad m) => HasInput (t :: Type) (ReaderT r m) Source # 
Instance details

Methods

input :: ReaderT r m (Event t VtyEvent) #

localInput :: (Event t VtyEvent -> Event t VtyEvent) -> ReaderT r m a -> ReaderT r m a #

(Reflex t, HasFocus t m, Monad m) => HasFocus (t :: Type) (ReaderT r m) Source # 
Instance details