{-# LINE 1 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
{-# LANGUAGE CPP, ExistentialQuantification, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, ScopedTypeVariables, UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.UI.FLTK.LowLevel.TextDisplay
(
mkStyleTableEntriesPtr,
toStyleTableEntries,
indexStyleTableEntries,
textDisplayNew,
textDisplayCustom
)
where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp
import C2HS hiding (cFromEnum, cFromBool, cToBool,cToEnum)
import Graphics.UI.FLTK.LowLevel.Widget
import qualified Foreign.Concurrent as FC
import Graphics.UI.FLTK.LowLevel.Fl_Types
import Graphics.UI.FLTK.LowLevel.Fl_Enumerations
import Graphics.UI.FLTK.LowLevel.Utils
import Graphics.UI.FLTK.LowLevel.Hierarchy
import Graphics.UI.FLTK.LowLevel.Dispatch
import qualified Data.Text as T
import qualified Foreign.ForeignPtr.Unsafe as Unsafe
mkStyleTableEntriesPtr :: (Parent a TextDisplay) => Ref a -> [StyleTableEntry] -> IO (ForeignPtr [StyleTableEntry])
mkStyleTableEntriesPtr td stes = do
styleTableEntriesPtr <- mallocBytes ((length stes) * 16)
mapM_
(
\(idx, (StyleTableEntry c f s)) -> do
let currPtr = styleTableEntriesPtr `plusPtr` (idx * 16)
(\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: C2HSImp.CUInt)}) currPtr $ maybe 0 (\(Color c') -> fromIntegral c') c
(\ptr val -> do {C2HSImp.pokeByteOff ptr 4 (val :: C2HSImp.CInt)}) currPtr $ maybe 0 (\(Font f') -> fromIntegral f') f
(\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CInt)}) currPtr $ maybe 0 (\(FontSize s') -> s') s
(\ptr val -> do {C2HSImp.pokeByteOff ptr 12 (val :: C2HSImp.CUInt)}) currPtr 0
)
(zip [0..] stes)
textDisplayAsPtr <- unsafeRefToPtr td
let finalizerF = if (textDisplayAsPtr == nullPtr)
then free styleTableEntriesPtr
else return ()
FC.newForeignPtr
styleTableEntriesPtr
finalizerF
toStyleTableEntries :: Int -> Ptr () -> IO (Maybe [StyleTableEntry])
toStyleTableEntries len ptr = do
entries <- mapM toStyleTableEntry [0 .. (len - 1)]
return (sequence entries)
where
toStyleTableEntry :: Int -> IO (Maybe StyleTableEntry)
toStyleTableEntry idx =
let entryPtr = ptr `plusPtr` (idx * 16) in
if (entryPtr == nullPtr)
then return Nothing
else do
color <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CUInt}) entryPtr
font <- (\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CInt}) entryPtr
fontSize <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) entryPtr
return
(Just
(
StyleTableEntry
(if (color == 0) then Nothing else Just (Color (fromIntegral color)))
(if (font == 0) then Nothing else Just (Font (fromIntegral font)))
(if (fontSize == 0) then Nothing else Just (FontSize (fromIntegral fontSize)))
)
)
indexStyleTableEntries :: [StyleTableEntry] -> [(Char, StyleTableEntry)]
indexStyleTableEntries = zip ['A'..]
overriddenWidgetNewWithLabel' :: (Int) -> (Int) -> (Int) -> (Int) -> (CString) -> (Ptr ()) -> IO ((Ptr ()))
overriddenWidgetNewWithLabel' a1 a2 a3 a4 a5 a6 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
(flip ($)) a5 $ \a5' ->
let {a6' = id a6} in
overriddenWidgetNewWithLabel''_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 81 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
overriddenWidgetNew' :: (Int) -> (Int) -> (Int) -> (Int) -> (Ptr ()) -> IO ((Ptr ()))
overriddenWidgetNew' a1 a2 a3 a4 a5 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
let {a5' = id a5} in
overriddenWidgetNew''_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 82 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
textDisplayCustom ::
Rectangle
-> Maybe T.Text
-> Maybe (Ref TextDisplay -> IO ())
-> Maybe (CustomWidgetFuncs TextDisplay)
-> IO (Ref TextDisplay)
textDisplayCustom rectangle l' draw' funcs' =
widgetMaker
rectangle
l'
draw'
funcs'
overriddenWidgetNew'
overriddenWidgetNewWithLabel'
textDisplayNew' :: (Int) -> (Int) -> (Int) -> (Int) -> IO ((Ptr ()))
textDisplayNew' a1 a2 a3 a4 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
textDisplayNew''_ a1' a2' a3' a4' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 98 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
textDisplayNewWithLabel' :: (Int) -> (Int) -> (Int) -> (Int) -> (CString) -> IO ((Ptr ()))
textDisplayNewWithLabel' a1 a2 a3 a4 a5 =
let {a1' = fromIntegral a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
(flip ($)) a5 $ \a5' ->
textDisplayNewWithLabel''_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 99 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
textDisplayNew :: Rectangle -> Maybe T.Text -> IO (Ref TextDisplay)
textDisplayNew rectangle l' =
let (x_pos, y_pos, width, height) = fromRectangle rectangle
in do
r <- case l' of
Nothing -> textDisplayNew' x_pos y_pos width height >>= toRef
Just l -> copyTextToCString l >>= \l' -> textDisplayNewWithLabel' x_pos y_pos width height l' >>= toRef
setFlag r WidgetFlagCopiedLabel
setFlag r WidgetFlagCopiedTooltip
return r
textDisplayDestroy' :: (Ptr ()) -> IO ((()))
textDisplayDestroy' a1 =
let {a1' = id a1} in
textDisplayDestroy''_ a1' >>= \res ->
let {res' = supressWarningAboutRes res} in
return (res')
{-# LINE 111 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (IO ())) => Op (Destroy ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> textDisplayDestroy' text_displayPtr
setBuffer' :: (Ptr ()) -> (Ptr ()) -> IO ()
setBuffer' a1 a2 =
let {a1' = id a1} in
let {a2' = id a2} in
setBuffer''_ a1' a2' >>
return ()
{-# LINE 114 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (Parent a TextBuffer, impl ~ (Maybe ( Ref a ) -> IO ())) => Op (SetBuffer ()) TextDisplay orig impl where
runOp _ _ text_display buf = withRef text_display $ \text_displayPtr -> withMaybeRef buf $ \bufPtr -> setBuffer' text_displayPtr bufPtr
buffer' :: (Ptr ()) -> IO ((Ptr ()))
buffer' a1 =
let {a1' = id a1} in
buffer''_ a1' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 117 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Maybe (Ref TextBuffer)))) => Op (GetBuffer ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> buffer' text_displayPtr >>= toMaybeRef
redisplayRange' :: (Ptr ()) -> (Int) -> (Int) -> IO ()
redisplayRange' a1 a2 a3 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
redisplayRange''_ a1' a2' a3' >>
return ()
{-# LINE 120 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (IndexRange -> IO ())) => Op (RedisplayRange ()) TextDisplay orig impl where
runOp _ _ text_display (IndexRange (AtIndex start') (AtIndex end')) = withRef text_display $ \text_displayPtr -> redisplayRange' text_displayPtr start' end'
scroll' :: (Ptr ()) -> (Int) -> (Int) -> IO ()
scroll' a1 a2 a3 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
scroll''_ a1' a2' a3' >>
return ()
{-# LINE 123 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (LineNumber -> AtIndex -> IO ())) => Op (Scroll ()) TextDisplay orig impl where
runOp _ _ text_display (LineNumber toplinenum) (AtIndex horizoffset) = withRef text_display $ \text_displayPtr -> scroll' text_displayPtr toplinenum horizoffset
overstrike' :: (Ptr ()) -> (CString) -> IO ()
overstrike' a1 a2 =
let {a1' = id a1} in
(flip ($)) a2 $ \a2' ->
overstrike''_ a1' a2' >>
return ()
{-# LINE 126 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (T.Text -> IO ())) => Op (Overstrike ()) TextDisplay orig impl where
runOp _ _ text_display text = withRef text_display $ \text_displayPtr -> copyTextToCString text >>= overstrike' text_displayPtr
setInsertPosition' :: (Ptr ()) -> (Int) -> IO ()
setInsertPosition' a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
setInsertPosition''_ a1' a2' >>
return ()
{-# LINE 129 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (AtIndex -> IO ())) => Op (SetInsertPosition ()) TextDisplay orig impl where
runOp _ _ text_display (AtIndex newpos) = withRef text_display $ \text_displayPtr -> setInsertPosition' text_displayPtr newpos
insertPosition' :: (Ptr ()) -> IO ((Int))
insertPosition' a1 =
let {a1' = id a1} in
insertPosition''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 132 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO AtIndex)) => Op (GetInsertPosition ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> insertPosition' text_displayPtr >>= return . AtIndex
positionToXy' :: (Ptr ()) -> (Int) -> (Ptr CInt) -> (Ptr CInt) -> IO ((Int))
positionToXy' a1 a2 a3 a4 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = id a3} in
let {a4' = id a4} in
positionToXy''_ a1' a2' a3' a4' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 135 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (AtIndex -> IO (Either OutOfRange Position))) => Op (PositionToXy ()) TextDisplay orig impl where
runOp _ _ text_display (AtIndex pos) =
withRef text_display $ \text_displayPtr ->
alloca $ \xPtr ->
alloca $ \yPtr -> do
status' <- positionToXy' text_displayPtr pos xPtr yPtr
successOrOutOfRange
((xPtr,yPtr))
(status' == 0)
(\(xp',yp') -> do
x' <- peekIntConv xp'
y' <- peekIntConv yp'
return (Position (X x') (Y y'))
)
inSelection' :: (Ptr ()) -> (Int) -> (Int) -> IO ((Bool))
inSelection' a1 a2 a3 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
inSelection''_ a1' a2' a3' >>= \res ->
let {res' = cToBool res} in
return (res')
{-# LINE 150 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Position -> IO (Bool))) => Op (InSelection ()) TextDisplay orig impl where
runOp _ _ text_display (Position (X x_pos') (Y y_pos')) = withRef text_display $ \text_displayPtr -> inSelection' text_displayPtr x_pos' y_pos'
showInsertPosition' :: (Ptr ()) -> IO ()
showInsertPosition' a1 =
let {a1' = id a1} in
showInsertPosition''_ a1' >>
return ()
{-# LINE 153 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO ())) => Op (ShowInsertPosition ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> showInsertPosition' text_displayPtr
moveRight' :: (Ptr ()) -> IO ((Int))
moveRight' a1 =
let {a1' = id a1} in
moveRight''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 156 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Either OutOfRange ()))) => Op (MoveRight ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr ->
moveRight' text_displayPtr >>= \s -> successOrOutOfRange () (s == 0) return
moveLeft' :: (Ptr ()) -> IO ((Int))
moveLeft' a1 =
let {a1' = id a1} in
moveLeft''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 160 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Either OutOfRange ()))) => Op (MoveLeft ()) TextDisplay orig impl where
runOp _ _ text_display =
withRef text_display $ \text_displayPtr ->
moveLeft' text_displayPtr >>= \s -> successOrOutOfRange () (s == 0) return
moveUp' :: (Ptr ()) -> IO ((Int))
moveUp' a1 =
let {a1' = id a1} in
moveUp''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 165 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Either OutOfRange ()))) => Op (MoveUp ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr ->
moveUp' text_displayPtr >>= \s -> successOrOutOfRange () (s == 0) return
moveDown' :: (Ptr ()) -> IO ((Int))
moveDown' a1 =
let {a1' = id a1} in
moveDown''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 169 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Either OutOfRange ()))) => Op (MoveDown ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr ->
moveDown' text_displayPtr >>= \s -> successOrOutOfRange () (s == 0) return
countLines' :: (Ptr ()) -> (Int) -> (Int) -> (Bool) -> IO ((Int))
countLines' a1 a2 a3 a4 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
let {a4' = cFromBool a4} in
countLines''_ a1' a2' a3' a4' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 173 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (IndexRange -> Bool -> IO (Int))) => Op (CountLines ()) TextDisplay orig impl where
runOp _ _ text_display (IndexRange (AtIndex start') (AtIndex end')) start_pos_is_line_start =
withRef text_display $ \text_displayPtr -> countLines' text_displayPtr start' end' start_pos_is_line_start
lineStart' :: (Ptr ()) -> (Int) -> IO ((Int))
lineStart' a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
lineStart''_ a1' a2' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 177 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (AtIndex -> IO (AtIndex))) => Op (LineStart ()) TextDisplay orig impl where
runOp _ _ text_display (AtIndex pos) = withRef text_display $ \text_displayPtr -> lineStart' text_displayPtr pos >>= return . AtIndex
lineEnd' :: (Ptr ()) -> (Int) -> (Bool) -> IO ((Int))
lineEnd' a1 a2 a3 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = cFromBool a3} in
lineEnd''_ a1' a2' a3' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 180 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (AtIndex -> Bool -> IO (AtIndex))) => Op (LineEnd ()) TextDisplay orig impl where
runOp _ _ text_display (AtIndex startpos) startposislinestart = withRef text_display $ \text_displayPtr -> lineEnd' text_displayPtr startpos startposislinestart >>= return . AtIndex
skipLines' :: (Ptr ()) -> (Int) -> (Int) -> (Bool) -> IO ((Int))
skipLines' a1 a2 a3 a4 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
let {a4' = cFromBool a4} in
skipLines''_ a1' a2' a3' a4' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 183 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (AtIndex -> Int -> Bool -> IO (AtIndex))) => Op (SkipLines ()) TextDisplay orig impl where
runOp _ _ text_display (AtIndex startpos) nlines startposislinestart = withRef text_display $ \text_displayPtr -> skipLines' text_displayPtr startpos nlines startposislinestart >>= return . AtIndex
rewindLines' :: (Ptr ()) -> (Int) -> (Int) -> IO ((Int))
rewindLines' a1 a2 a3 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
rewindLines''_ a1' a2' a3' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 186 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (AtIndex -> Int -> IO (AtIndex))) => Op (RewindLines ()) TextDisplay orig impl where
runOp _ _ text_display (AtIndex startpos) nlines = withRef text_display $ \text_displayPtr -> rewindLines' text_displayPtr startpos nlines >>= return . AtIndex
nextWord' :: (Ptr ()) -> IO ()
nextWord' a1 =
let {a1' = id a1} in
nextWord''_ a1' >>
return ()
{-# LINE 189 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO ())) => Op (NextWord ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> nextWord' text_displayPtr
previousWord' :: (Ptr ()) -> IO ()
previousWord' a1 =
let {a1' = id a1} in
previousWord''_ a1' >>
return ()
{-# LINE 192 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO ())) => Op (PreviousWord ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> previousWord' text_displayPtr
showCursorWithB' :: (Ptr ()) -> (Bool) -> IO ()
showCursorWithB' a1 a2 =
let {a1' = id a1} in
let {a2' = cFromBool a2} in
showCursorWithB''_ a1' a2' >>
return ()
{-# LINE 195 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Bool -> IO ())) => Op (ShowCursor ()) TextDisplay orig impl where
runOp _ _ text_display b = withRef text_display $ \text_displayPtr -> showCursorWithB' text_displayPtr b
cursorStyle' :: (Ptr ()) -> (Int) -> IO ()
cursorStyle' a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
cursorStyle''_ a1' a2' >>
return ()
{-# LINE 198 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (CursorType -> IO ())) => Op (SetCursorStyle ()) TextDisplay orig impl where
runOp _ _ text_display ct = withRef text_display $ \text_displayPtr -> cursorStyle' text_displayPtr (fromEnum ct)
cursorColor' :: (Ptr ()) -> IO ((Color))
cursorColor' a1 =
let {a1' = id a1} in
cursorColor''_ a1' >>= \res ->
let {res' = cToColor res} in
return (res')
{-# LINE 201 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Color))) => Op (GetCursorColor ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> cursorColor' text_displayPtr
setCursorColor' :: (Ptr ()) -> (Color) -> IO ()
setCursorColor' a1 a2 =
let {a1' = id a1} in
let {a2' = cFromColor a2} in
setCursorColor''_ a1' a2' >>
return ()
{-# LINE 204 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Color -> IO ())) => Op (SetCursorColor ()) TextDisplay orig impl where
runOp _ _ text_display n = withRef text_display $ \text_displayPtr -> setCursorColor' text_displayPtr n
scrollbarWidth' :: (Ptr ()) -> IO ((Int))
scrollbarWidth' a1 =
let {a1' = id a1} in
scrollbarWidth''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 207 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Width))) => Op (GetScrollbarWidth ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> scrollbarWidth' text_displayPtr >>= return . Width
setScrollbarWidth' :: (Ptr ()) -> (Int) -> IO ()
setScrollbarWidth' a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
setScrollbarWidth''_ a1' a2' >>
return ()
{-# LINE 210 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Width -> IO ())) => Op (SetScrollbarWidth ()) TextDisplay orig impl where
runOp _ _ text_display (Width w) = withRef text_display $ \text_displayPtr -> setScrollbarWidth' text_displayPtr w
scrollbarAlign' :: (Ptr ()) -> IO ((AlignType))
scrollbarAlign' a1 =
let {a1' = id a1} in
scrollbarAlign''_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 213 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (AlignType))) => Op (GetScrollbarAlign ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> scrollbarAlign' text_displayPtr
setScrollbarAlign' :: (Ptr ()) -> (AlignType) -> IO ()
setScrollbarAlign' a1 a2 =
let {a1' = id a1} in
let {a2' = cFromEnum a2} in
setScrollbarAlign''_ a1' a2' >>
return ()
{-# LINE 216 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (AlignType -> IO ())) => Op (SetScrollbarAlign ()) TextDisplay orig impl where
runOp _ _ text_display a = withRef text_display $ \text_displayPtr -> setScrollbarAlign' text_displayPtr a
wordStart' :: (Ptr ()) -> (Int) -> IO ((Int))
wordStart' a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
wordStart''_ a1' a2' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 219 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (AtIndex -> IO (AtIndex))) => Op (WordStart ()) TextDisplay orig impl where
runOp _ _ text_display (AtIndex pos) = withRef text_display $ \text_displayPtr -> wordStart' text_displayPtr pos >>= return . AtIndex
wordEnd' :: (Ptr ()) -> (Int) -> IO ((Int))
wordEnd' a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
wordEnd''_ a1' a2' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 222 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (AtIndex -> IO (AtIndex))) => Op (WordEnd ()) TextDisplay orig impl where
runOp _ _ text_display (AtIndex pos) = withRef text_display $ \text_displayPtr -> wordEnd' text_displayPtr pos >>= return . AtIndex
highlightData' :: (Ptr ()) -> (Ptr ()) -> (Ptr ()) -> (Int) -> (CChar) -> (FunPtr UnfinishedStyleCbPrim) -> (Ptr ()) -> IO ()
highlightData' a1 a2 a3 a4 a5 a6 a7 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = id a3} in
let {a4' = fromIntegral a4} in
let {a5' = id a5} in
let {a6' = id a6} in
let {a7' = id a7} in
highlightData''_ a1' a2' a3' a4' a5' a6' a7' >>
return ()
{-# LINE 225 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (Parent a TextBuffer, impl ~ (Ref a -> [(Char, StyleTableEntry)] -> Maybe(Char,UnfinishedStyleCb) -> IO ())) => Op (HighlightData ()) TextDisplay orig impl where
runOp _ _ text_display style_buffer indexedStyleTable cb =
withRef text_display $ \text_displayPtr ->
withRef style_buffer $ \style_bufferPtr -> do
stesPtr <- mkStyleTableEntriesPtr text_display (map snd indexedStyleTable)
(indexChar, fPtr) <- case cb of
(Just (indexChar', unfinishedhighlightcb)) -> do
fPtr' <- toUnfinishedStyleCbPrim unfinishedhighlightcb
return ((fromEnum indexChar'), fPtr')
Nothing -> return (0, nullFunPtr)
highlightData' text_displayPtr style_bufferPtr (castPtr $ Unsafe.unsafeForeignPtrToPtr $ stesPtr) (length indexedStyleTable) (fromIntegral indexChar) fPtr nullPtr
positionStyle' :: (Ptr ()) -> (Int) -> (Int) -> (Int) -> IO ((Int))
positionStyle' a1 a2 a3 a4 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
positionStyle''_ a1' a2' a3' a4' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 237 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (AtIndex -> Int -> LineNumber -> IO TextDisplayStyle)) => Op (PositionStyle ()) TextDisplay orig impl where
runOp _ _ text_display (AtIndex linestartpos) linelen (LineNumber lineindex) =
withRef text_display $ \text_displayPtr ->
positionStyle' text_displayPtr linestartpos linelen lineindex >>= return . TextDisplayStyle . fromIntegral
shortcut' :: (Ptr ()) -> IO ((CInt))
shortcut' a1 =
let {a1' = id a1} in
shortcut''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 242 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Maybe ShortcutKeySequence))) => Op (GetShortcut ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> shortcut' text_displayPtr >>= return . cIntToKeySequence
setShortcut' :: (Ptr ()) -> (CInt) -> IO ()
setShortcut' a1 a2 =
let {a1' = id a1} in
let {a2' = id a2} in
setShortcut''_ a1' a2' >>
return ()
{-# LINE 245 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (ShortcutKeySequence -> IO ())) => Op (SetShortcut ()) TextDisplay orig impl where
runOp _ _ input (ShortcutKeySequence modifiers char) =
withRef input $ \inputPtr -> setShortcut' inputPtr (keySequenceToCInt modifiers char)
textfont' :: (Ptr ()) -> IO ((Font))
textfont' a1 =
let {a1' = id a1} in
textfont''_ a1' >>= \res ->
let {res' = cToFont res} in
return (res')
{-# LINE 249 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Font))) => Op (GetTextfont ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> textfont' text_displayPtr
setTextfont' :: (Ptr ()) -> (CInt) -> IO ()
setTextfont' a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
setTextfont''_ a1' a2' >>
return ()
{-# LINE 252 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( Font -> IO ())) => Op (SetTextfont ()) TextDisplay orig impl where
runOp _ _ text_display font = withRef text_display $ \text_displayPtr -> setTextfont' text_displayPtr (cFromFont font)
textsize' :: (Ptr ()) -> IO ((CInt))
textsize' a1 =
let {a1' = id a1} in
textsize''_ a1' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 255 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (FontSize))) => Op (GetTextsize ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> textsize' text_displayPtr >>= return . FontSize
setTextsize' :: (Ptr ()) -> (CInt) -> IO ()
setTextsize' a1 a2 =
let {a1' = id a1} in
let {a2' = id a2} in
setTextsize''_ a1' a2' >>
return ()
{-# LINE 258 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (FontSize -> IO ())) => Op (SetTextsize ()) TextDisplay orig impl where
runOp _ _ text_display (FontSize s) = withRef text_display $ \text_displayPtr -> setTextsize' text_displayPtr s
textcolor' :: (Ptr ()) -> IO ((Color))
textcolor' a1 =
let {a1' = id a1} in
textcolor''_ a1' >>= \res ->
let {res' = cToColor res} in
return (res')
{-# LINE 261 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Color))) => Op (GetTextcolor ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> textcolor' text_displayPtr
setTextcolor' :: (Ptr ()) -> (Color) -> IO ()
setTextcolor' a1 a2 =
let {a1' = id a1} in
let {a2' = cFromColor a2} in
setTextcolor''_ a1' a2' >>
return ()
{-# LINE 264 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Color -> IO ())) => Op (SetTextcolor ()) TextDisplay orig impl where
runOp _ _ text_display n = withRef text_display $ \text_displayPtr -> setTextcolor' text_displayPtr n
xToCol' :: (Ptr ()) -> (Double) -> IO ((Double))
xToCol' a1 a2 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
xToCol''_ a1' a2' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 267 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Double -> IO (Double))) => Op (XToCol ()) TextDisplay orig impl where
runOp _ _ text_display pixelPos = withRef text_display $ \text_displayPtr -> xToCol' text_displayPtr pixelPos
colToX' :: (Ptr ()) -> (Double) -> IO ((Double))
colToX' a1 a2 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
colToX''_ a1' a2' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 270 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Double -> IO (Double))) => Op (ColToX ()) TextDisplay orig impl where
runOp _ _ text_display col = withRef text_display $ \text_displayPtr -> colToX' text_displayPtr col
setLinenumberWidth' :: (Ptr ()) -> (Int) -> IO ()
setLinenumberWidth' a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
setLinenumberWidth''_ a1' a2' >>
return ()
{-# LINE 273 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Width -> IO ())) => Op (SetLinenumberWidth ()) TextDisplay orig impl where
runOp _ _ text_display (Width width) = withRef text_display $ \text_displayPtr -> setLinenumberWidth' text_displayPtr width
linenumberWidth' :: (Ptr ()) -> IO ((Int))
linenumberWidth' a1 =
let {a1' = id a1} in
linenumberWidth''_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 276 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Width))) => Op (GetLinenumberWidth ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> linenumberWidth' text_displayPtr >>= return . Width
setLinenumberFont' :: (Ptr ()) -> (Font) -> IO ()
setLinenumberFont' a1 a2 =
let {a1' = id a1} in
let {a2' = cFromFont a2} in
setLinenumberFont''_ a1' a2' >>
return ()
{-# LINE 279 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Font -> IO ())) => Op (SetLinenumberFont ()) TextDisplay orig impl where
runOp _ _ text_display val = withRef text_display $ \text_displayPtr -> setLinenumberFont' text_displayPtr val
linenumberFont' :: (Ptr ()) -> IO ((Font))
linenumberFont' a1 =
let {a1' = id a1} in
linenumberFont''_ a1' >>= \res ->
let {res' = cToFont res} in
return (res')
{-# LINE 282 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Font))) => Op (GetLinenumberFont ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> linenumberFont' text_displayPtr
setLinenumberSize' :: (Ptr ()) -> (CInt) -> IO ()
setLinenumberSize' a1 a2 =
let {a1' = id a1} in
let {a2' = id a2} in
setLinenumberSize''_ a1' a2' >>
return ()
{-# LINE 285 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (FontSize -> IO ())) => Op (SetLinenumberSize ()) TextDisplay orig impl where
runOp _ _ text_display (FontSize val) = withRef text_display $ \text_displayPtr -> setLinenumberSize' text_displayPtr val
linenumberSize' :: (Ptr ()) -> IO ((CInt))
linenumberSize' a1 =
let {a1' = id a1} in
linenumberSize''_ a1' >>= \res ->
let {res' = id res} in
return (res')
{-# LINE 288 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (FontSize))) => Op (GetLinenumberSize ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> linenumberSize' text_displayPtr >>= return . FontSize
setLinenumberFgcolor' :: (Ptr ()) -> (Color) -> IO ()
setLinenumberFgcolor' a1 a2 =
let {a1' = id a1} in
let {a2' = cFromColor a2} in
setLinenumberFgcolor''_ a1' a2' >>
return ()
{-# LINE 291 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Color -> IO ())) => Op (SetLinenumberFgcolor ()) TextDisplay orig impl where
runOp _ _ text_display val = withRef text_display $ \text_displayPtr -> setLinenumberFgcolor' text_displayPtr val
linenumberFgcolor' :: (Ptr ()) -> IO ((Color))
linenumberFgcolor' a1 =
let {a1' = id a1} in
linenumberFgcolor''_ a1' >>= \res ->
let {res' = cToColor res} in
return (res')
{-# LINE 294 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Color))) => Op (GetLinenumberFgcolor ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> linenumberFgcolor' text_displayPtr
setLinenumberBgcolor' :: (Ptr ()) -> (Color) -> IO ()
setLinenumberBgcolor' a1 a2 =
let {a1' = id a1} in
let {a2' = cFromColor a2} in
setLinenumberBgcolor''_ a1' a2' >>
return ()
{-# LINE 297 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Color -> IO ())) => Op (SetLinenumberBgcolor ()) TextDisplay orig impl where
runOp _ _ text_display val = withRef text_display $ \text_displayPtr -> setLinenumberBgcolor' text_displayPtr val
linenumberBgcolor' :: (Ptr ()) -> IO ((Color))
linenumberBgcolor' a1 =
let {a1' = id a1} in
linenumberBgcolor''_ a1' >>= \res ->
let {res' = cToColor res} in
return (res')
{-# LINE 300 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (Color))) => Op (GetLinenumberBgcolor ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> linenumberBgcolor' text_displayPtr
setLinenumberAlign' :: (Ptr ()) -> (AlignType) -> IO ()
setLinenumberAlign' a1 a2 =
let {a1' = id a1} in
let {a2' = cFromEnum a2} in
setLinenumberAlign''_ a1' a2' >>
return ()
{-# LINE 303 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (AlignType -> IO ())) => Op (SetLinenumberAlign ()) TextDisplay orig impl where
runOp _ _ text_display val = withRef text_display $ \text_displayPtr -> setLinenumberAlign' text_displayPtr val
linenumberAlign' :: (Ptr ()) -> IO ((AlignType))
linenumberAlign' a1 =
let {a1' = id a1} in
linenumberAlign''_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 306 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO (AlignType))) => Op (GetLinenumberAlign ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> linenumberAlign' text_displayPtr
setLinenumberFormat' :: (Ptr ()) -> (CString) -> IO ()
setLinenumberFormat' a1 a2 =
let {a1' = id a1} in
(flip ($)) a2 $ \a2' ->
setLinenumberFormat''_ a1' a2' >>
return ()
{-# LINE 309 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (T.Text -> IO ())) => Op (SetLinenumberFormat ()) TextDisplay orig impl where
runOp _ _ text_display val = withRef text_display $ \text_displayPtr -> copyTextToCString val >>= setLinenumberFormat' text_displayPtr
linenumberFormat' :: (Ptr ()) -> IO ((CString))
linenumberFormat' a1 =
let {a1' = id a1} in
linenumberFormat''_ a1' >>= \res ->
return res >>= \res' ->
return (res')
{-# LINE 312 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO T.Text)) => Op (GetLinenumberFormat ()) TextDisplay orig impl where
runOp _ _ text_display = withRef text_display $ \text_displayPtr -> linenumberFormat' text_displayPtr >>= cStringToText
wrapMode' :: (Ptr ()) -> (CInt) -> (CInt) -> IO ()
wrapMode' a1 a2 a3 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
wrapMode''_ a1' a2' a3' >>
return ()
{-# LINE 315 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (WrapType -> IO ())) => Op (WrapMode ()) TextDisplay orig impl where
runOp _ _ textDisplay wt =
withRef textDisplay $ \textDisplayPtr ->
(case wt of
(WrapAtPixel (PixelPosition p')) -> wrapMode' textDisplayPtr ((fromIntegral . fromEnum) WrapAtPixelFl) (fromIntegral p')
(WrapAtColumn (ColumnNumber c')) -> wrapMode' textDisplayPtr ((fromIntegral . fromEnum) WrapAtColumnFl) (fromIntegral c')
WrapAtBounds -> wrapMode' textDisplayPtr ((fromIntegral . fromEnum) WrapAtBoundsFl) (fromIntegral (0 :: Int))
WrapNone -> wrapMode' textDisplayPtr ((fromIntegral . fromEnum) WrapNoneFl) (fromIntegral (0 :: Int))
)
draw'' :: (Ptr ()) -> IO ()
draw'' a1 =
let {a1' = id a1} in
draw'''_ a1' >>
return ()
{-# LINE 325 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO ())) => Op (Draw ()) TextDisplay orig impl where
runOp _ _ textDisplay = withRef textDisplay $ \textDisplayPtr -> draw'' textDisplayPtr
drawSuper' :: (Ptr ()) -> IO ((()))
drawSuper' a1 =
let {a1' = id a1} in
drawSuper''_ a1' >>= \res ->
let {res' = supressWarningAboutRes res} in
return (res')
{-# LINE 328 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO ())) => Op (DrawSuper ()) TextDisplay orig impl where
runOp _ _ textDisplay = withRef textDisplay $ \textDisplayPtr -> drawSuper' textDisplayPtr
textDisplayHandle' :: (Ptr ()) -> (CInt) -> IO ((Int))
textDisplayHandle' a1 a2 =
let {a1' = id a1} in
let {a2' = id a2} in
textDisplayHandle''_ a1' a2' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 331 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Event -> IO (Either UnknownEvent ()))) => Op (Handle ()) TextDisplay orig impl where
runOp _ _ textDisplay event = withRef textDisplay (\p -> textDisplayHandle' p (fromIntegral . fromEnum $ event)) >>= return . successOrUnknownEvent
handleSuper' :: (Ptr ()) -> (Int) -> IO ((Int))
handleSuper' a1 a2 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
handleSuper''_ a1' a2' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 334 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Event -> IO (Either UnknownEvent ()))) => Op (HandleSuper ()) TextDisplay orig impl where
runOp _ _ textDisplay event = withRef textDisplay $ \textDisplayPtr -> handleSuper' textDisplayPtr (fromIntegral (fromEnum event)) >>= return . successOrUnknownEvent
resize' :: (Ptr ()) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ((()))
resize' a1 a2 a3 a4 a5 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
let {a5' = fromIntegral a5} in
resize''_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = supressWarningAboutRes res} in
return (res')
{-# LINE 337 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Rectangle -> IO ())) => Op (Resize ()) TextDisplay orig impl where
runOp _ _ textDisplay rectangle = withRef textDisplay $ \textDisplayPtr -> do
let (x_pos,y_pos,w_pos,h_pos) = fromRectangle rectangle
resize' textDisplayPtr x_pos y_pos w_pos h_pos
resizeSuper' :: (Ptr ()) -> (Int) -> (Int) -> (Int) -> (Int) -> IO ((()))
resizeSuper' a1 a2 a3 a4 a5 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
let {a5' = fromIntegral a5} in
resizeSuper''_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = supressWarningAboutRes res} in
return (res')
{-# LINE 342 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ (Rectangle -> IO ())) => Op (ResizeSuper ()) TextDisplay orig impl where
runOp _ _ textDisplay rectangle =
let (x_pos, y_pos, width, height) = fromRectangle rectangle
in withRef textDisplay $ \textDisplayPtr -> resizeSuper' textDisplayPtr x_pos y_pos width height
hide' :: (Ptr ()) -> IO ()
hide' a1 =
let {a1' = id a1} in
hide''_ a1' >>
return ()
{-# LINE 347 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO ())) => Op (Hide ()) TextDisplay orig impl where
runOp _ _ textDisplay = withRef textDisplay $ \textDisplayPtr -> hide' textDisplayPtr
hideSuper' :: (Ptr ()) -> IO ((()))
hideSuper' a1 =
let {a1' = id a1} in
hideSuper''_ a1' >>= \res ->
let {res' = supressWarningAboutRes res} in
return (res')
{-# LINE 350 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO ())) => Op (HideSuper ()) TextDisplay orig impl where
runOp _ _ textDisplay = withRef textDisplay $ \textDisplayPtr -> hideSuper' textDisplayPtr
show' :: (Ptr ()) -> IO ()
show' a1 =
let {a1' = id a1} in
show''_ a1' >>
return ()
{-# LINE 353 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO ())) => Op (ShowWidget ()) TextDisplay orig impl where
runOp _ _ textDisplay = withRef textDisplay $ \textDisplayPtr -> show' textDisplayPtr
showSuper' :: (Ptr ()) -> IO ((()))
showSuper' a1 =
let {a1' = id a1} in
showSuper''_ a1' >>= \res ->
let {res' = supressWarningAboutRes res} in
return (res')
{-# LINE 356 "src/Graphics/UI/FLTK/LowLevel/TextDisplay.chs" #-}
instance (impl ~ ( IO ())) => Op (ShowWidgetSuper ()) TextDisplay orig impl where
runOp _ _ textDisplay = withRef textDisplay $ \textDisplayPtr -> showSuper' textDisplayPtr
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_OverriddenText_Display_New_WithLabel"
overriddenWidgetNewWithLabel''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ()))))))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_OverriddenText_Display_New"
overriddenWidgetNew''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_New"
textDisplayNew''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ()))))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_New_WithLabel"
textDisplayNewWithLabel''_ :: (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO (C2HSImp.Ptr ())))))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_Destroy"
textDisplayDestroy''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_set_buffer"
setBuffer''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_buffer"
buffer''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_redisplay_range"
redisplayRange''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_scroll"
scroll''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_overstrike"
overstrike''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_set_insert_position"
setInsertPosition''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_insert_position"
insertPosition''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_position_to_xy"
positionToXy''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CInt) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_in_selection"
inSelection''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_show_insert_position"
showInsertPosition''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_move_right"
moveRight''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_move_left"
moveLeft''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_move_up"
moveUp''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_move_down"
moveDown''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_count_lines"
countLines''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_line_start"
lineStart''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_line_end"
lineEnd''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_skip_lines"
skipLines''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_rewind_lines"
rewindLines''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_next_word"
nextWord''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_previous_word"
previousWord''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_show_cursor_with_b"
showCursorWithB''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_set_cursor_style"
cursorStyle''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_cursor_color"
cursorColor''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_set_cursor_color"
setCursorColor''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_scrollbar_width"
scrollbarWidth''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_set_scrollbar_width"
setScrollbarWidth''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_scrollbar_align"
scrollbarAlign''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_set_scrollbar_align"
setScrollbarAlign''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_word_start"
wordStart''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_word_end"
wordEnd''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_highlight_data"
highlightData''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CChar -> ((C2HSImp.FunPtr (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO ())))) -> ((C2HSImp.Ptr ()) -> (IO ()))))))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_position_style"
positionStyle''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_shortcut"
shortcut''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_set_shortcut"
setShortcut''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_textfont"
textfont''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_set_textfont"
setTextfont''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_textsize"
textsize''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_set_textsize"
setTextsize''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_textcolor"
textcolor''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_set_textcolor"
setTextcolor''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_x_to_col"
xToCol''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CDouble -> (IO C2HSImp.CDouble)))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_col_to_x"
colToX''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CDouble -> (IO C2HSImp.CDouble)))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h set_linenumber_width"
setLinenumberWidth''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h linenumber_width"
linenumberWidth''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h set_linenumber_font"
setLinenumberFont''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h linenumber_font"
linenumberFont''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h set_linenumber_size"
setLinenumberSize''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h linenumber_size"
linenumberSize''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h set_linenumber_fgcolor"
setLinenumberFgcolor''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h linenumber_fgcolor"
linenumberFgcolor''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h set_linenumber_bgcolor"
setLinenumberBgcolor''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h linenumber_bgcolor"
linenumberBgcolor''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h set_linenumber_align"
setLinenumberAlign''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h linenumber_align"
linenumberAlign''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h set_linenumber_format"
setLinenumberFormat''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ())))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h linenumber_format"
linenumberFormat''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_wrap_mode"
wrapMode''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_draw"
draw'''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_draw_super"
drawSuper''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_handle"
textDisplayHandle''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_handle_super"
handleSuper''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_resize"
resize''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_resize_super"
resizeSuper''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO ()))))))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_hide"
hide''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_hide_super"
hideSuper''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_show"
show''_ :: ((C2HSImp.Ptr ()) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TextDisplay.chs.h Fl_Text_Display_show_super"
showSuper''_ :: ((C2HSImp.Ptr ()) -> (IO ()))