[Haskell-cafe] How to insert character key self in sourceView?

Andy Stewart lazycat.manatee at gmail.com
Wed Mar 11 15:42:09 EDT 2009


Hi all,

I use gtk2hs develop editor.

I use below function handle key press event.

keyPressHandler :: Event -> IO Bool
keyPressHandler (Key {eventKeyName = keyName}) = do
  case keyName of
    "Escape" -> do
      mainQuit >> return True    
    _ -> do 
      -- How to insert character self?
      return True

I need handle key press event, and insert itself if key is character
(like: 'a' 'b' 'c').

How to insert character self in sourceView buffer?

Below are complete source code:
------------------------------> source code start <------------------------------
import Graphics.UI.Gtk
import Graphics.UI.Gtk.SourceView
import Graphics.UI.Gtk.Abstract.Widget
import Graphics.UI.Gtk.Gdk.Events
import Text.Printf
import Control.Monad

main :: IO ()
main = do
  -- Init.
  initGUI

  -- Root frame.
  rootFrame <- windowNew
  onDestroy rootFrame mainQuit  -- quit main loop when root frame close

  -- Root frame status.
  -- windowFullscreen rootFrame   -- fullscreen
  windowSetPosition rootFrame WinPosCenter -- set init position
  windowSetDefaultSize rootFrame 400 300   -- set init size

  -- Main box.
  mainBox <- vBoxNew False 0
  containerAdd rootFrame mainBox

  -- Source view box.
  sourceViewBox <- vBoxNew False 0
  containerAdd mainBox sourceViewBox

  -- Source view.
  sourceView <- sourceViewNew
  boxPackStart sourceViewBox sourceView PackNatural 0

  -- Echo area box.
  echoAreaBox <- vBoxNew False 0
  echoAreaAlign <- alignmentNew 0 1 1 1
  containerAdd echoAreaBox echoAreaAlign
  containerAdd mainBox echoAreaBox

  -- Echo area.
  echoArea <- statusbarNew
  boxPackStart echoAreaBox echoArea PackNatural 0
  
  -- Display.
  widgetShowAll rootFrame

  -- Handle keystroke.
  onKeyPress rootFrame $ keyPressHandler

  -- Update echo area.
  updateEchoArea sourceView echoArea

  -- Loop
  mainGUI

keyPressHandler :: Event -> IO Bool
keyPressHandler (Key {eventKeyName = keyName}) = do
  case keyName of
    "Escape" -> do
      mainQuit >> return True    
    _ -> do 
      return True

updateEchoArea :: SourceView -> Statusbar -> IO ()
updateEchoArea sv sb = do
    buf  <- textViewGetBuffer sv
    mark <- textBufferGetInsert buf
    iter <- textBufferGetIterAtMark buf mark
    line <- textIterGetLine iter
    col  <- textIterGetLineOffset iter
    statusbarPop sb 1
    statusbarPush sb 1 $ printf "Line %4d, Column %3d" (line + 1) (col + 1)
    return ()
------------------------------> source code end   <------------------------------

Any help?

Thanks!

  -- Andy




More information about the Haskell-Cafe mailing list