workflow-types-0.0.0: Automate keyboard\/mouse\/clipboard\/application interaction.

Safe HaskellNone
LanguageHaskell2010

Workflow.Types

Description

 

Synopsis

Documentation

WorkflowF

data WorkflowF k Source #

platform-agnostic workflows, which can be interpreted by platform-specific bindings.

Naming: WorkflowF for "Workflow Functor".

NOTE: currently, no error codes are returned (only ())). this (1) simplifies bindings and (2) saves the user from explicitly ignoring action results (e.g. _ <- getClipboard). later, they can be supported, alongside wrappers that return () and throw SomeException and provide the same simple API. since the intented usage of workflows are as user-facing (often user-written) scripts, and the monad that satisifes MonadWorkflow will often satisify MonadIO too, convenient partial functions that throw a helpful error message to stdout (the error codes should be converted to their error messages) should suffice. and either way, is strictly better for the user than ignoring, as the exceptions can always be caught, or not displayed.

Constructors

SendKeyChord [Modifier] Key k

press the Key while the Modifiers are held down. sent to the current application. TODO | SendKeyChordTo Application [Modifier] Key k -- ^ TODO | SendKeyChordTo Window [Modifier] Key k -- ^ versus unary: ([Modifier], Key) rn SendChord

SendText String k

a logical grouping for: (1) unicode support (2) efficiency and (3) debugging. sent to the current application.

SendMouseClick [Modifier] Natural MouseButton k

click the button, some number of times, holding down the modifiers derived, make method, not constructor. sent to the current application.

SendMouseScroll [Modifier] MouseScroll Natural k

spin the wheel, some number of units*, holding down the modifiers

GetClipboard (Clipboard -> k) 
SetClipboard Clipboard k 
CurrentApplication (Application -> k)

like getter

OpenApplication Application k

like setter

OpenURL URL k 
Delay MilliSeconds k

interpreted as threadDelay on all platforms; included for convenience

Instances

Functor WorkflowF Source # 

Methods

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

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

data Workflow_ Source #

the non-monadic subset of WorkflowF. i.e. all cases that return (), preserving the previous continuation.

Naming: "unit workflow", like "traverse_".

Instances

Eq Workflow_ Source # 
Data Workflow_ Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Workflow_ -> c Workflow_ #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Workflow_ #

toConstr :: Workflow_ -> Constr #

dataTypeOf :: Workflow_ -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Workflow_) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Workflow_) #

gmapT :: (forall b. Data b => b -> b) -> Workflow_ -> Workflow_ #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Workflow_ -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Workflow_ -> r #

gmapQ :: (forall d. Data d => d -> u) -> Workflow_ -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Workflow_ -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Workflow_ -> m Workflow_ #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Workflow_ -> m Workflow_ #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Workflow_ -> m Workflow_ #

Ord Workflow_ Source # 
Read Workflow_ Source # 
Show Workflow_ Source # 
Generic Workflow_ Source # 

Associated Types

type Rep Workflow_ :: * -> * #

NFData Workflow_ Source # 

Methods

rnf :: Workflow_ -> () #

type Rep Workflow_ Source # 
type Rep Workflow_ = D1 (MetaData "Workflow_" "Workflow.Types" "workflow-types-0.0.0-K0EoQCaTrIdFAFcwhnivNQ" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "SendKeyChord_" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Modifier])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Key)))) (C1 (MetaCons "SendText_" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:+:) (C1 (MetaCons "SendMouseClick_" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Modifier])) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MouseButton))))) (C1 (MetaCons "SendMouseScroll_" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Modifier])) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MouseScroll)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural))))))) ((:+:) ((:+:) (C1 (MetaCons "SetClipboard_" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Clipboard))) (C1 (MetaCons "OpenApplication_" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Application)))) ((:+:) (C1 (MetaCons "OpenURL_" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 URL))) (C1 (MetaCons "Delay_" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MilliSeconds))))))

type MonadWorkflow m = (MonadFree WorkflowF m, MonadThrow m) Source #

abstract interface.

a monad constraint for "workflow effects" (just like MonadState is for "state effects"). Can be used in any monad transformer stack that handles them.

WorkflowF holds the effects.

MonadThrow supports:

  • press, if the user's syntax is wrong
  • error messages from the underlying system calls (TODO e.g. Win32's GetLastError())

type MonadWorkflow_ = MonadFree WorkflowF Source #

(without failability)

type WorkflowT = FreeT WorkflowF Source #

concrete transformer.

type Workflow = Free WorkflowF Source #

concrete monad.

data MouseButton Source #

Operating systems always (?) support at least these mouse events.

Most mice have these three buttons, trackpads have left/right.

Instances

Bounded MouseButton Source # 
Enum MouseButton Source # 
Eq MouseButton Source # 
Data MouseButton Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MouseButton -> c MouseButton #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MouseButton #

toConstr :: MouseButton -> Constr #

dataTypeOf :: MouseButton -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MouseButton) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MouseButton) #

gmapT :: (forall b. Data b => b -> b) -> MouseButton -> MouseButton #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MouseButton -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MouseButton -> r #

gmapQ :: (forall d. Data d => d -> u) -> MouseButton -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MouseButton -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MouseButton -> m MouseButton #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseButton -> m MouseButton #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseButton -> m MouseButton #

Ord MouseButton Source # 
Read MouseButton Source # 
Show MouseButton Source # 
Generic MouseButton Source # 

Associated Types

type Rep MouseButton :: * -> * #

NFData MouseButton Source # 

Methods

rnf :: MouseButton -> () #

type Rep MouseButton Source # 
type Rep MouseButton = D1 (MetaData "MouseButton" "Workflow.Types" "workflow-types-0.0.0-K0EoQCaTrIdFAFcwhnivNQ" False) ((:+:) (C1 (MetaCons "LeftButton" PrefixI False) U1) ((:+:) (C1 (MetaCons "MiddleButton" PrefixI False) U1) (C1 (MetaCons "RightButton" PrefixI False) U1)))

data MouseScroll Source #

Mouse wheel scrolling, vertically and horizontally.

ScrollTowards:

  • scrolls up when "natural scrolling" is disabled
  • scrolls down when "natural scrolling" is enabled

TODO check

Instances

Bounded MouseScroll Source # 
Enum MouseScroll Source # 
Eq MouseScroll Source # 
Data MouseScroll Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MouseScroll -> c MouseScroll #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MouseScroll #

toConstr :: MouseScroll -> Constr #

dataTypeOf :: MouseScroll -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MouseScroll) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MouseScroll) #

gmapT :: (forall b. Data b => b -> b) -> MouseScroll -> MouseScroll #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MouseScroll -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MouseScroll -> r #

gmapQ :: (forall d. Data d => d -> u) -> MouseScroll -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MouseScroll -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MouseScroll -> m MouseScroll #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseScroll -> m MouseScroll #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseScroll -> m MouseScroll #

Ord MouseScroll Source # 
Read MouseScroll Source # 
Show MouseScroll Source # 
Generic MouseScroll Source # 

Associated Types

type Rep MouseScroll :: * -> * #

NFData MouseScroll Source # 

Methods

rnf :: MouseScroll -> () #

type Rep MouseScroll Source # 
type Rep MouseScroll = D1 (MetaData "MouseScroll" "Workflow.Types" "workflow-types-0.0.0-K0EoQCaTrIdFAFcwhnivNQ" False) ((:+:) ((:+:) (C1 (MetaCons "ScrollTowards" PrefixI False) U1) (C1 (MetaCons "ScrollAway" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ScrollLeft" PrefixI False) U1) (C1 (MetaCons "ScrollRight" PrefixI False) U1)))

type KeySequence = [KeyChord] Source #

a sequence of key chords make up a keyboard shortcut

Naming: https://www.emacswiki.org/emacs/KeySequence

type KeyChord = ([Modifier], Key) Source #

represents joitly holding down all the modifiers while individually press each key down and back up.

Naming: https://www.emacswiki.org/emacs/Chord

pattern KeyChord :: [Modifier] -> Key -> KeyChord Source #

pattern KeyChord ms k = (ms,k)

data Modifier Source #

modifier keys are keys that can be "held".

NOTE the escape key tends to be "pressed", not "held", it seems. (possibly explains its behavior in your terminal emulator?)

alt is OptionModifier.

Constructors

MetaModifier

fake modifier: Alt on Linux/Windows, Command on OSX

HyperModifier

fake modifier: Control on Linux/Windows, Command on OSX

ControlModifier 
OptionModifier 
ShiftModifier 
FunctionModifier 

Instances

Bounded Modifier Source # 
Enum Modifier Source # 
Eq Modifier Source # 
Data Modifier Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Modifier -> c Modifier #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Modifier #

toConstr :: Modifier -> Constr #

dataTypeOf :: Modifier -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Modifier) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Modifier) #

gmapT :: (forall b. Data b => b -> b) -> Modifier -> Modifier #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Modifier -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Modifier -> r #

gmapQ :: (forall d. Data d => d -> u) -> Modifier -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Modifier -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Modifier -> m Modifier #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Modifier -> m Modifier #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Modifier -> m Modifier #

Ord Modifier Source # 
Read Modifier Source # 
Show Modifier Source # 
Generic Modifier Source # 

Associated Types

type Rep Modifier :: * -> * #

Methods

from :: Modifier -> Rep Modifier x #

to :: Rep Modifier x -> Modifier #

NFData Modifier Source # 

Methods

rnf :: Modifier -> () #

type Rep Modifier Source # 
type Rep Modifier = D1 (MetaData "Modifier" "Workflow.Types" "workflow-types-0.0.0-K0EoQCaTrIdFAFcwhnivNQ" False) ((:+:) ((:+:) (C1 (MetaCons "MetaModifier" PrefixI False) U1) ((:+:) (C1 (MetaCons "HyperModifier" PrefixI False) U1) (C1 (MetaCons "ControlModifier" PrefixI False) U1))) ((:+:) (C1 (MetaCons "OptionModifier" PrefixI False) U1) ((:+:) (C1 (MetaCons "ShiftModifier" PrefixI False) U1) (C1 (MetaCons "FunctionModifier" PrefixI False) U1))))

data Key Source #

a "cross-platform" keyboard, that has:

  • all keys that exist on standard keyboards.
  • plus, MetaKey and HyperKey: virtual modifiers to abstract over common keyboard shortcuts.

(let me know if you want a type to support cross-platform international keyboards, i haven't looked into it. you can still use the platform-specific virtual-key-codes in the dependent packages: workflow-linux, workflow-osx, and workflow-windows)

Instances

Bounded Key Source # 

Methods

minBound :: Key #

maxBound :: Key #

Enum Key Source # 

Methods

succ :: Key -> Key #

pred :: Key -> Key #

toEnum :: Int -> Key #

fromEnum :: Key -> Int #

enumFrom :: Key -> [Key] #

enumFromThen :: Key -> Key -> [Key] #

enumFromTo :: Key -> Key -> [Key] #

enumFromThenTo :: Key -> Key -> Key -> [Key] #

Eq Key Source # 

Methods

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

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

Data Key Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Key -> c Key #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Key #

toConstr :: Key -> Constr #

dataTypeOf :: Key -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Key) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Key) #

gmapT :: (forall b. Data b => b -> b) -> Key -> Key #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r #

gmapQ :: (forall d. Data d => d -> u) -> Key -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Key -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Key -> m Key #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Key -> m Key #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Key -> m Key #

Ord Key Source # 

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 Source # 
Show Key Source # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

NFData Key Source # 

Methods

rnf :: Key -> () #

type Rep Key Source # 
type Rep Key = D1 (MetaData "Key" "Workflow.Types" "workflow-types-0.0.0-K0EoQCaTrIdFAFcwhnivNQ" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "MetaKey" PrefixI False) U1) (C1 (MetaCons "HyperKey" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ControlKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "CapsLockKey" PrefixI False) U1) (C1 (MetaCons "ShiftKey" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "OptionKey" PrefixI False) U1) (C1 (MetaCons "FunctionKey" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GraveKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "MinusKey" PrefixI False) U1) (C1 (MetaCons "EqualKey" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DeleteKey" PrefixI False) U1) (C1 (MetaCons "ForwardDeleteKey" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LeftBracketKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "RightBracketKey" PrefixI False) U1) (C1 (MetaCons "BackslashKey" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "SemicolonKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "QuoteKey" PrefixI False) U1) (C1 (MetaCons "CommaKey" PrefixI False) U1))) ((:+:) (C1 (MetaCons "PeriodKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "SlashKey" PrefixI False) U1) (C1 (MetaCons "TabKey" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "SpaceKey" PrefixI False) U1) (C1 (MetaCons "ReturnKey" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LeftArrowKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "RightArrowKey" PrefixI False) U1) (C1 (MetaCons "DownArrowKey" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "UpArrowKey" PrefixI False) U1) (C1 (MetaCons "AKey" PrefixI False) U1)) ((:+:) (C1 (MetaCons "BKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "CKey" PrefixI False) U1) (C1 (MetaCons "DKey" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "EKey" PrefixI False) U1) (C1 (MetaCons "FKey" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "HKey" PrefixI False) U1) (C1 (MetaCons "IKey" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "JKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "KKey" PrefixI False) U1) (C1 (MetaCons "LKey" PrefixI False) U1))) ((:+:) (C1 (MetaCons "MKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "NKey" PrefixI False) U1) (C1 (MetaCons "OKey" PrefixI False) U1))))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "PKey" PrefixI False) U1) (C1 (MetaCons "QKey" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "SKey" PrefixI False) U1) (C1 (MetaCons "TKey" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "UKey" PrefixI False) U1) (C1 (MetaCons "VKey" PrefixI False) U1)) ((:+:) (C1 (MetaCons "WKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "XKey" PrefixI False) U1) (C1 (MetaCons "YKey" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ZKey" PrefixI False) U1) (C1 (MetaCons "ZeroKey" PrefixI False) U1)) ((:+:) (C1 (MetaCons "OneKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "TwoKey" PrefixI False) U1) (C1 (MetaCons "ThreeKey" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "FourKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "FiveKey" PrefixI False) U1) (C1 (MetaCons "SixKey" PrefixI False) U1))) ((:+:) (C1 (MetaCons "SevenKey" PrefixI False) U1) ((:+:) (C1 (MetaCons "EightKey" PrefixI False) U1) (C1 (MetaCons "NineKey" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "EscapeKey" PrefixI False) U1) (C1 (MetaCons "F1Key" PrefixI False) U1)) ((:+:) (C1 (MetaCons "F2Key" PrefixI False) U1) ((:+:) (C1 (MetaCons "F3Key" PrefixI False) U1) (C1 (MetaCons "F4Key" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "F5Key" PrefixI False) U1) (C1 (MetaCons "F6Key" PrefixI False) U1)) ((:+:) (C1 (MetaCons "F7Key" PrefixI False) U1) ((:+:) (C1 (MetaCons "F8Key" PrefixI False) U1) (C1 (MetaCons "F9Key" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "F10Key" PrefixI False) U1) (C1 (MetaCons "F11Key" PrefixI False) U1)) ((:+:) (C1 (MetaCons "F12Key" PrefixI False) U1) ((:+:) (C1 (MetaCons "F13Key" PrefixI False) U1) (C1 (MetaCons "F14Key" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "F15Key" PrefixI False) U1) ((:+:) (C1 (MetaCons "F16Key" PrefixI False) U1) (C1 (MetaCons "F17Key" PrefixI False) U1))) ((:+:) (C1 (MetaCons "F18Key" PrefixI False) U1) ((:+:) (C1 (MetaCons "F19Key" PrefixI False) U1) (C1 (MetaCons "F20Key" PrefixI False) U1))))))))

modifier2key :: Modifier -> Key Source #

All modifiers are keys.

delay :: forall m. MonadFree WorkflowF m => MilliSeconds -> m () Source #

openURL :: forall m. MonadFree WorkflowF m => URL -> m () Source #

setClipboard :: forall m. MonadFree WorkflowF m => Clipboard -> m () Source #

sendText :: forall m. MonadFree WorkflowF m => String -> m () Source #

sendKeyChord :: forall m. MonadFree WorkflowF m => [Modifier] -> Key -> m () Source #

CoWorkflowF

provides generic helper functions for defining interpreters.

data CoWorkflowF k Source #

Naming: induces a CoMonad, see http://dlaing.org/cofun/posts/free_and_cofree.html

WorkflowF, CoWorkflowF, and runWorkflowWithT are analogous to:

  • Either (a -> c) (b,c), "get an a, or set a b"
  • ((a,c), (b -> c)), "a handler for the getting of an a, and a handler for the setting of a b"
  • @ handle :: ((a,c), (b -> c))
  • > (Either (a -> c) (b,c))
  • > c handle (aHasBeenGotten, bHasBeenSet) = either TODO @

background: see http://dlaing.org/cofun/posts/free_and_cofree.html

Instances

Functor CoWorkflowF Source # 

Methods

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

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

type CoWorkflowT = CofreeT CoWorkflowF Source #

e.g.

@

expansion:

CoWorkflowT w a ~ CofreeT CoWorkflowF w a ~ w (CofreeF CoWorkflowF a (CofreeT CoWorkflowF w a)) ~ w (a, CoWorkflowF (CofreeT CoWorkflowF w a)) @

since:

data CofreeT f w a = w (CofreeF f a (CofreeT f w a))

type CoWorkflow = Cofree CoWorkflowF Source #

expansion:

CoWorkflow a
~
Cofree CoWorkflowF a
~
(a, CoWorkflow (Cofree CoWorkflowF a))

since:

data Cofree f a = a :< f (Cofree f a)