dyna-brick-0.1.0.0: FRP for brick Terminal user interface library
Safe HaskellNone
LanguageHaskell2010

Dyna.Brick.Run

Description

IO of thebrick application

Synopsis

Documentation

data Spec Source #

Instances

Instances details
Default Spec Source # 
Instance details

Defined in Dyna.Brick.Run

Methods

def :: Spec #

Run application

data Run a Source #

Instances

Instances details
Monad Run Source # 
Instance details

Defined in Dyna.Brick.Types

Methods

(>>=) :: Run a -> (a -> Run b) -> Run b #

(>>) :: Run a -> Run b -> Run b #

return :: a -> Run a #

Functor Run Source # 
Instance details

Defined in Dyna.Brick.Types

Methods

fmap :: (a -> b) -> Run a -> Run b #

(<$) :: a -> Run b -> Run a #

Applicative Run Source # 
Instance details

Defined in Dyna.Brick.Types

Methods

pure :: a -> Run a #

(<*>) :: Run (a -> b) -> Run a -> Run b #

liftA2 :: (a -> b -> c) -> Run a -> Run b -> Run c #

(*>) :: Run a -> Run b -> Run b #

(<*) :: Run a -> Run b -> Run a #

MonadIO Run Source # 
Instance details

Defined in Dyna.Brick.Types

Methods

liftIO :: IO a -> Run a #

MonadRandom Run Source # 
Instance details

Defined in Dyna.Brick.Types

Methods

getRandomR :: Random a => (a, a) -> Run a #

getRandom :: Random a => Run a #

getRandomRs :: Random a => (a, a) -> Run [a] #

getRandoms :: Random a => Run [a] #

Frp Run Source # 
Instance details

Defined in Dyna.Brick.Types

Associated Types

type Ref Run :: Type -> Type #

MonadReader Env Run Source # 
Instance details

Defined in Dyna.Brick.Types

Methods

ask :: Run Env #

local :: (Env -> Env) -> Run a -> Run a #

reader :: (Env -> a) -> Run a #

MonadBase IO Run Source # 
Instance details

Defined in Dyna.Brick.Types

Methods

liftBase :: IO α -> Run α #

MonadBaseControl IO Run Source # 
Instance details

Defined in Dyna.Brick.Types

Associated Types

type StM Run a #

Methods

liftBaseWith :: (RunInBase Run IO -> IO a) -> Run a #

restoreM :: StM Run a -> Run a #

type Ref Run Source # 
Instance details

Defined in Dyna.Brick.Types

type Ref Run = IORef
type StM Run a Source # 
Instance details

Defined in Dyna.Brick.Types

type StM Run a

runApp :: Spec -> Run Win -> IO () Source #

Run application

Sensors

module Brick

data Key #

Representations of non-modifier keys.

  • KFun is indexed from 0 to 63. Range of supported FKeys varies by terminal and keyboard.
  • KUpLeft, KUpRight, KDownLeft, KDownRight, KCenter support varies by terminal and keyboard.
  • Actually, support for most of these but KEsc, KChar, KBS, and KEnter vary by terminal and keyboard.

Instances

Instances details
Eq Key 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Ord Key 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

(>=) :: Key -> Key -> Bool #

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Read Key 
Instance details

Defined in Graphics.Vty.Input.Events

Show Key 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key 
Instance details

Defined in Graphics.Vty.Input.Events

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

NFData Key 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

rnf :: Key -> () #

Parse Key 
Instance details

Defined in Graphics.Vty.Config

Methods

parseValue :: Parser Key

type Rep Key 
Instance details

Defined in Graphics.Vty.Input.Events

type Rep Key = D1 ('MetaData "Key" "Graphics.Vty.Input.Events" "vty-5.35.1-KZM7sNe0OABAUeGlQIWLj" 'False) ((((C1 ('MetaCons "KEsc" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Char)) :+: C1 ('MetaCons "KBS" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KEnter" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KRight" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KDown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KUpLeft" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KUpRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KDownLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KDownRight" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "KCenter" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KFun" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "KBackTab" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KPrtScr" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KPause" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KIns" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KHome" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KPageUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KDel" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "KEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KPageDown" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KBegin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KMenu" 'PrefixI 'False) (U1 :: Type -> Type))))))

data Modifier #

Modifier keys. Key codes are interpreted such that users are more likely to have Meta than Alt; for instance on the PC Linux console, MMeta will generally correspond to the physical Alt key.

Constructors

MShift 
MCtrl 
MMeta 
MAlt 

Instances

Instances details
Eq Modifier 
Instance details

Defined in Graphics.Vty.Input.Events

Ord Modifier 
Instance details

Defined in Graphics.Vty.Input.Events

Read Modifier 
Instance details

Defined in Graphics.Vty.Input.Events

Show Modifier 
Instance details

Defined in Graphics.Vty.Input.Events

Generic Modifier 
Instance details

Defined in Graphics.Vty.Input.Events

Associated Types

type Rep Modifier :: Type -> Type #

Methods

from :: Modifier -> Rep Modifier x #

to :: Rep Modifier x -> Modifier #

NFData Modifier 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

rnf :: Modifier -> () #

Parse Modifier 
Instance details

Defined in Graphics.Vty.Config

Methods

parseValue :: Parser Modifier

type Rep Modifier 
Instance details

Defined in Graphics.Vty.Input.Events

type Rep Modifier = D1 ('MetaData "Modifier" "Graphics.Vty.Input.Events" "vty-5.35.1-KZM7sNe0OABAUeGlQIWLj" 'False) ((C1 ('MetaCons "MShift" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MCtrl" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MMeta" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MAlt" 'PrefixI 'False) (U1 :: Type -> Type)))