Add documentation to Brick.Main

This commit is contained in:
Jonathan Daugherty 2015-06-30 23:40:52 -07:00
parent 618f6f4e4e
commit c4c80492f4

View File

@ -5,12 +5,14 @@ module Brick.Main
, simpleMain , simpleMain
, resizeOrQuit , resizeOrQuit
-- * Event handler functions
, EventM , EventM
, Next , Next
, continue , continue
, halt , halt
, suspendAndResume , suspendAndResume
-- ** Viewport scrolling
, viewportScroll , viewportScroll
, ViewportScroll , ViewportScroll
, scrollBy , scrollBy
@ -18,6 +20,7 @@ module Brick.Main
, scrollToBeginning , scrollToBeginning
, scrollToEnd , scrollToEnd
-- * Cursor management functions
, neverShowCursor , neverShowCursor
, showFirstCursor , showFirstCursor
) )
@ -49,29 +52,69 @@ import Brick.Widgets.Internal (renderFinal, RenderState(..), ScrollRequest(..),
import Brick.Core (row, column, CursorLocation(..), Name(..)) import Brick.Core (row, column, CursorLocation(..), Name(..))
import Brick.AttrMap import Brick.AttrMap
-- | The type of actions to take in an event handler.
data Next a = Continue a data Next a = Continue a
| SuspendAndResume (IO a) | SuspendAndResume (IO a)
| Halt a | Halt a
-- | The library application abstraction. Your application's operations
-- are represented here and passed to one of the various main functions
-- in this module. An application is in terms of an application state
-- type 'a' and an application event type 'e'. In the simplest case 'e' is
-- vty's 'Event' type, but you may define your own event type, permitted
-- that it has a constructor for wrapping Vty events, so that Vty events
-- can be handled by your event loop.
data App a e = data App a e =
App { appDraw :: a -> [Widget] App { appDraw :: a -> [Widget]
-- ^ This function turns your application state into a list of
-- widget layers. The layers are listed topmost first.
, appChooseCursor :: a -> [CursorLocation] -> Maybe CursorLocation , appChooseCursor :: a -> [CursorLocation] -> Maybe CursorLocation
-- ^ This function chooses which of the zero or more cursor
-- locations reported by the rendering process should be
-- selected as the one to use to place the cursor. If this
-- returns 'Nothing', no cursor is placed. The rationale here
-- is that many widgets may request a cursor placement but your
-- application state is what you probably want to use to decide
-- which one wins.
, appHandleEvent :: e -> a -> EventM (Next a) , appHandleEvent :: e -> a -> EventM (Next a)
-- ^ This function takes an event and your application state
-- and returns an action to be taken. Possible options are
-- 'continue', 'suspendAndResume', and 'halt'.
, appStartEvent :: a -> EventM a , appStartEvent :: a -> EventM a
-- ^ This function gets called once just prior to the first
-- drawing of your application. Here is where you can make
-- initial scrolling requests, for example.
, appAttrMap :: a -> AttrMap , appAttrMap :: a -> AttrMap
-- ^ The attribute map that should be used during rendering.
, appMakeVtyEvent :: Event -> e , appMakeVtyEvent :: Event -> e
-- ^ The event constructor to use to wrap Vty events in your own
-- event type. For example, if the application's event type is
-- 'Event', this is just 'id'.
} }
-- | The monad in which event handlers run.
type EventM a = StateT EventState IO a type EventM a = StateT EventState IO a
type EventState = [(Name, ScrollRequest)] type EventState = [(Name, ScrollRequest)]
defaultMain :: App a Event -> a -> IO a -- | The default main entry point which takes an application and an
-- initial state and returns the final state returned by a 'halt'
-- operation.
defaultMain :: App a Event
-- ^ The application.
-> a
-- ^ The initial application state.
-> IO a
defaultMain app st = do defaultMain app st = do
chan <- newChan chan <- newChan
customMain (mkVty def) chan app st customMain (mkVty def) chan app st
simpleMain :: Widget -> IO () -- | A simple main entry point which takes a widget and renders it. This
-- event loop terminates when the user presses any key, but terminal
-- resize events cause redraws.
simpleMain :: Widget
-- ^ The widget to draw.
-> IO ()
simpleMain w = simpleMain w =
let app = App { appDraw = const [w] let app = App { appDraw = const [w]
, appHandleEvent = resizeOrQuit , appHandleEvent = resizeOrQuit
@ -82,6 +125,11 @@ simpleMain w =
} }
in defaultMain app () in defaultMain app ()
-- | An event-handling function which continues execution of the event
-- loop only when resize events occur; all other types of events trigger
-- a halt. This is a convenience function useful as an 'appHandleEvent'
-- value for simple applications using the 'Event' type that do not need
-- to get more sophisticated user input.
resizeOrQuit :: Event -> a -> EventM (Next a) resizeOrQuit :: Event -> a -> EventM (Next a)
resizeOrQuit e a = resizeOrQuit e a =
case e of case e of
@ -107,7 +155,21 @@ runWithNewVty buildVty chan app initialRS initialSt = do
Continue s -> runInner newRS s Continue s -> runInner newRS s
runInner initialRS initialSt runInner initialRS initialSt
customMain :: IO Vty -> Chan e -> App a e -> a -> IO a -- | The custom event loop entry point to use when the simpler ones
-- don't permit enough control.
customMain :: IO Vty
-- ^ An IO action to build a Vty handle. This is used to
-- build a Vty handle whenever the event loop begins or is
-- resumed after suspension.
-> Chan e
-- ^ An event channel for sending custom events to the event
-- loop (you write to this channel, the event loop reads from
-- it).
-> App a e
-- ^ The application.
-> a
-- ^ The initial application state.
-> IO a
customMain buildVty chan app initialAppState = do customMain buildVty chan app initialAppState = do
let run rs st = do let run rs st = do
result <- runWithNewVty buildVty chan app rs st result <- runWithNewVty buildVty chan app rs st
@ -155,12 +217,22 @@ renderApp vty app appState rs = do
return newRS return newRS
-- | Ignore all requested cursor positions returned by the rendering
-- process. This is a convenience function useful as an
-- 'appChooseCursor' value when a simple application has no need to
-- position the cursor.
neverShowCursor :: a -> [CursorLocation] -> Maybe CursorLocation neverShowCursor :: a -> [CursorLocation] -> Maybe CursorLocation
neverShowCursor = const $ const Nothing neverShowCursor = const $ const Nothing
-- | Always show the first cursor, if any, returned by the rendering
-- process. This is a convenience function useful as an
-- 'appChooseCursor' value when a simple program has zero or more
-- widgets that advertise a cursor position.
showFirstCursor :: a -> [CursorLocation] -> Maybe CursorLocation showFirstCursor :: a -> [CursorLocation] -> Maybe CursorLocation
showFirstCursor = const $ listToMaybe showFirstCursor = const $ listToMaybe
-- | A viewport scrolling handle for managing the scroll state of
-- viewports.
data ViewportScroll = data ViewportScroll =
ViewportScroll { viewportName :: Name ViewportScroll { viewportName :: Name
, scrollPage :: Direction -> EventM () , scrollPage :: Direction -> EventM ()
@ -169,6 +241,7 @@ data ViewportScroll =
, scrollToEnd :: EventM () , scrollToEnd :: EventM ()
} }
-- | Build a viewport scroller for the viewport with the specified name.
viewportScroll :: Name -> ViewportScroll viewportScroll :: Name -> ViewportScroll
viewportScroll n = viewportScroll n =
ViewportScroll { viewportName = n ViewportScroll { viewportName = n
@ -178,11 +251,19 @@ viewportScroll n =
, scrollToEnd = modify ((n, ScrollToEnd) :) , scrollToEnd = modify ((n, ScrollToEnd) :)
} }
-- | Continue running the event loop with the specified application
-- state.
continue :: a -> EventM (Next a) continue :: a -> EventM (Next a)
continue = return . Continue continue = return . Continue
-- | Halt the event loop and return the specified application state as
-- the final state value.
halt :: a -> EventM (Next a) halt :: a -> EventM (Next a)
halt = return . Halt halt = return . Halt
-- | Suspend the event loop, save the terminal state, and run the
-- specified action. When it returns an application state value, restore
-- the terminal state, and resume the event loop with the returned
-- application state.
suspendAndResume :: IO a -> EventM (Next a) suspendAndResume :: IO a -> EventM (Next a)
suspendAndResume = return . SuspendAndResume suspendAndResume = return . SuspendAndResume