Skip to content

Commit

Permalink
Add "wide cursors" to the Pango frontend.
Browse files Browse the repository at this point in the history
  • Loading branch information
reinerp committed Jul 18, 2011
1 parent aad07f7 commit 1c76da3
Show file tree
Hide file tree
Showing 4 changed files with 65 additions and 8 deletions.
7 changes: 7 additions & 0 deletions yi/src/library/Yi/Config.hs
Expand Up @@ -27,12 +27,19 @@ data UIConfig = UIConfig {
configAutoHideScrollBar :: Bool, -- ^ Hide scrollbar automatically if text fits on one page.
configAutoHideTabBar :: Bool, -- ^ Hide the tabbar automatically if only one tab is present
configLineWrap :: Bool, -- ^ Wrap lines at the edge of the window if too long to display.
configCursorStyle :: CursorStyle,
configWindowFill :: Char,
-- ^ The char with which to fill empty window space. Usually '~' for vi-like
-- editors, ' ' for everything else.
configTheme :: Theme -- ^ UI colours
}

-- | When should we use a \"fat\" cursor (i.e. 2 pixels wide, rather than 1)? Fat cursors have only been implemented for the Pango frontend.
data CursorStyle = AlwaysFat
| NeverFat
| FatWhenFocused
| FatWhenFocusedAndInserting

configStyle :: UIConfig -> UIStyle
configStyle = extractValue . configTheme

Expand Down
1 change: 1 addition & 0 deletions yi/src/library/Yi/Config/Default.hs
Expand Up @@ -135,6 +135,7 @@ defaultConfig =
{ configFontSize = Nothing
, configFontName = Nothing
, configScrollStyle = Nothing
, configCursorStyle = FatWhenFocusedAndInserting
, configLineWrap = True
, configLeftSideScrollBar = True
, configAutoHideScrollBar = False
Expand Down
10 changes: 9 additions & 1 deletion yi/src/library/Yi/Config/Simple.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE Rank2Types, CPP, GeneralizedNewtypeDeriving #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-} -- for good documentation, we want control over our export list, which occasionally gives us duplicate exports

{- | A simplified configuration interface for Yi. -}
module Yi.Config.Simple (
Expand Down Expand Up @@ -28,6 +29,9 @@ module Yi.Config.Simple (
fontName,
fontSize,
scrollStyle,
ScrollStyle(..),
cursorStyle,
CursorStyle(..),
Side(..),
scrollBarSide,
autoHideScrollBar,
Expand Down Expand Up @@ -61,7 +65,6 @@ module Yi.Config.Simple (
module Yi.File,
module Yi.Config,
module Yi.Config.Default,
module Yi.Config.Misc,
module Yi.Layout,
module Yi.Search,
module Yi.Style,
Expand Down Expand Up @@ -102,6 +105,7 @@ import Yi.Config(Config, UIConfig,
configInputPreprocessA, modeTableA, debugModeA,
configRegionStyleA, configKillringAccumulateA, bufferUpdateHandlerA,
configVtyEscDelayA, configFontNameA, configFontSizeA, configScrollStyleA,
configCursorStyleA, CursorStyle(..),
configLeftSideScrollBarA, configAutoHideScrollBarA, configAutoHideTabBarA,
configLineWrapA, configWindowFillA, configThemeA, layoutManagersA, configVarsA,
)
Expand Down Expand Up @@ -207,6 +211,10 @@ fontSize = configFontSizeA . configUIA
scrollStyle :: Field (Maybe ScrollStyle)
scrollStyle = configScrollStyleA . configUIA

-- | See 'CursorStyle' for documentation.
cursorStyle :: Field CursorStyle
cursorStyle = configCursorStyleA . configUIA

data Side = LeftSide | RightSide

-- | Which side to display the scroll bar on.
Expand Down
55 changes: 48 additions & 7 deletions yi/src/library/Yi/UI/Pango.hs
@@ -1,4 +1,4 @@
{-# LANGUAGE CPP, ExistentialQuantification, DoRec, TupleSections, NamedFieldPuns #-}
{-# LANGUAGE CPP, ExistentialQuantification, DoRec, TupleSections, NamedFieldPuns, ViewPatterns #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}

-- Copyright (c) 2007, 2008 Jean-Philippe Bernardy
Expand Down Expand Up @@ -87,6 +87,7 @@ data WinInfo = WinInfo
, shownTos :: IORef Point
, lButtonPressed :: IORef Bool
, insertingMode :: IORef Bool
, inFocus :: IORef Bool
, winLayoutInfo :: MVar WinLayoutInfo
, winMetrics :: FontMetrics
, textview :: DrawingArea
Expand Down Expand Up @@ -259,6 +260,7 @@ updateTabInfo e ui tab tabInfo = do

updateWindow :: Editor -> UI -> Window -> WinInfo -> IO ()
updateWindow e _ui win wInfo = do
writeIORef (inFocus wInfo) False -- see also 'setWindowFocus'
writeIORef (coreWin wInfo) win
writeIORef (insertingMode wInfo) (askBuffer win (findBufferWith (bufkey win) e) $ getA insertingA)

Expand All @@ -269,6 +271,7 @@ setWindowFocus e ui t w = do
ml = askBuffer win (findBufferWith (bufkey win) e) $ getModeLine (commonNamePrefix e)
im = uiInput ui

writeIORef (inFocus w) True -- see also 'updateWindow'
update (textview w) widgetIsFocus True
update (modeline w) labelText ml
writeIORef (fullTitle t) bufferName
Expand Down Expand Up @@ -362,6 +365,7 @@ newWindow e ui w = do
metrics <- contextGetMetrics context f language
ifLButton <- newIORef False
imode <- newIORef False
focused <- newIORef False
winRef <- newIORef w

layoutSetFontDescription layout (Just f)
Expand All @@ -378,6 +382,7 @@ newWindow e ui w = do
, shownTos = tosRef
, lButtonPressed = ifLButton
, insertingMode = imode
, inFocus = focused
}
updateWindow e ui w win

Expand All @@ -387,6 +392,11 @@ newWindow e ui w = do
v `on` configureEvent $ handleConfigure ui -- todo: allocate event rather than configure?
v `on` motionNotifyEvent $ handleMove ui win
discard $ v `onExpose` render ui win
-- also redraw when the window receives/loses focus
(uiWindow ui) `on` focusInEvent $ io (widgetQueueDraw v) >> return False
(uiWindow ui) `on` focusOutEvent $ io (widgetQueueDraw v) >> return False
-- todo: consider adding an 'isDirty' flag to WinLayoutInfo,
-- so that we don't have to recompute the Attributes when focus changes.
return win

refresh :: UI -> Editor -> IO ()
Expand Down Expand Up @@ -440,22 +450,37 @@ render ui w _event = withMVar (winLayoutInfo w) $ \WinLayoutInfo{winLayout=layou
drawWindow <- widgetGetDrawWindow $ textview w
gc <- gcNew drawWindow

-- see Note [PangoLayout width]
-- draw the layout
drawLayout drawWindow gc 0 0 layout
drawLayout drawWindow gc 1 0 layout

-- calculate the cursor position
im <- readIORef (insertingMode w)
(PangoRectangle curX curY curW curH, _) <- layoutGetCursorPos layout (rel cur)

-- check focus, and decide whether we want a wide cursor
bufferFocused <- readIORef (inFocus w)
uiFocused <- Gtk.windowHasToplevelFocus (uiWindow ui)
let focused = bufferFocused && uiFocused
wideCursor =
case configCursorStyle (uiConfig ui) of
AlwaysFat -> True
NeverFat -> False
FatWhenFocused -> focused
FatWhenFocusedAndInserting -> focused && im


(PangoRectangle (succ -> curX) curY curW curH, _) <- layoutGetCursorPos layout (rel cur)
-- tell the input method
imContextSetCursorLocation (uiInput ui) (Rectangle (round curX) (round curY) (round curW) (round curH))
-- paint the cursor
gcSetValues gc (newGCValues { Gtk.foreground = mkCol True $ Yi.Style.foreground $ baseAttributes $ configStyle $ uiConfig ui })
gcSetValues gc (newGCValues { Gtk.foreground = mkCol True $ Yi.Style.foreground $ baseAttributes $ configStyle $ uiConfig ui,
Gtk.lineWidth = if wideCursor then 2 else 1 })
-- tell the renderer
if im
then -- if we are inserting, we just want a line
drawLine drawWindow gc (round curX, round curY) (round $ curX + curW, round $ curY + curH)
else do -- if we aren't inserting, we want a rectangle around the current character
PangoRectangle chx chy chw chh <- layoutIndexToPos layout (rel cur)
PangoRectangle (succ -> chx) chy chw chh <- layoutIndexToPos layout (rel cur)
drawRectangle drawWindow gc False (round chx) (round chy) (if chw > 0 then round chw else 8) (round chh)

return True
Expand Down Expand Up @@ -495,12 +520,28 @@ shownRegion ui f w b = modifyMVar (winLayoutInfo w) $ \wli -> do
where clampTo lo hi x = max lo (min hi x)
-- during scrolling, cur might not lie between tos and bos, so we clamp it to avoid Pango errors

{-
Note [PangoLayout width]
~~~~~~~~~~~~~~~~~~~~~~~~
We start rendering the PangoLayout one pixel from the left of the rendering area, which means a few +/-1 offsets in Pango rendering and point lookup code.
The reason for this is to support the "wide cursor", which is 2 pixels wide. If we started rendering the PangoLayout
directly from the left of the rendering area instead of at a 1-pixel offset, then the "wide cursor" would only be half-displayed
when the cursor is at the beginning of the line, and would then be a "thin cursor".
An alternative would be to special-case the wide cursor rendering at the beginning of the line, and draw it one pixel to
the right of where it "should" be. I haven't tried this out to see how it looks.
Reiner
-}

-- we update the regex and the buffer to avoid holding on to potential garbage.
-- These will be overwritten with correct values soon, in
-- updateWinInfoForRendering.
updatePango :: UI -> FontDescription -> WinInfo -> FBuffer -> PangoLayout -> IO (Point, Point, Point, Point)
updatePango ui font w b layout = do
(width', height') <- widgetGetSize $ textview w
(width_', height') <- widgetGetSize $ textview w
let width' = max 0 (width_' - 1) -- see Note [PangoLayout width]

oldFont <- layoutGetFontDescription layout
oldFontStr <- maybe (return Nothing) (fmap Just . fontDescriptionToString) oldFont
Expand Down Expand Up @@ -686,7 +727,7 @@ handleDividerMove actionCh ref pos = actionCh (makeAction (setDividerPosE ref po
pointToOffset :: (Double, Double) -> WinInfo -> IO Point
pointToOffset (x,y) w = withMVar (winLayoutInfo w) $ \WinLayoutInfo{winLayout,tos,bufEnd} -> do
im <- readIORef (insertingMode w)
(_, charOffsetX, extra) <- layoutXYToIndex winLayout x y
(_, charOffsetX, extra) <- layoutXYToIndex winLayout (max 0 (x-1)) y -- see Note [PangoLayout width]
return $ min bufEnd (tos + fromIntegral (charOffsetX + if im then extra else 0))

selectArea :: UI -> WinInfo -> (Double, Double) -> IO ()
Expand Down

0 comments on commit 1c76da3

Please sign in to comment.