diffing dir...
Thu Jul 8 11:37:07 EDT 2010 Axe...@in...
* Fix documentation and don't import internal functions from ByteString.
Ignore-this: 6347b22b1641978869ebe1dd67f4f9a9
{
hunk ./gtk/Graphics/UI/Gtk/Multiline/TextBuffer.chs 93
+ textBufferGetByteStringSlice,
hunk ./gtk/Graphics/UI/Gtk/Multiline/TextBuffer.chs 203
-import Data.ByteString.Internal (c_strlen)
hunk ./gtk/Graphics/UI/Gtk/Multiline/TextBuffer.chs 433
--- | Same as 'textBufferSetText', but use to read *huge* file.
--- When you read content from huge file, 'ByteString' will save
--- much memory than 'String'.
--- NOTE, you need make sure 'ByteString' is a valid UTF-8 [_$_]
--- when you call this function.
+-- | Returns the text in the range [@start@,@end@). Excludes undisplayed text
+-- (text marked with tags that set the invisibility attribute) if
+-- @includeHiddenChars@ is @False@. The returned string includes a
+-- @(chr 0xFFFC)@ character whenever the buffer contains embedded images, so
+-- character indexes into the returned string /do/ correspond to
+-- character indexes into the buffer. Contrast with 'textBufferGetText'. Note
+-- that @(chr 0xFFFC)@ can occur in normal text as well, so it is not a reliable
+-- indicator that a pixbuf or widget is in the buffer.
hunk ./gtk/Graphics/UI/Gtk/Multiline/TextBuffer.chs 442
--- Below is example code to read huge file.
+textBufferGetSlice :: TextBufferClass self => self
+ -> TextIter -- ^ @start@ - start of a range
+ -> TextIter -- ^ @end@ - end of a range
+ -> Bool -- ^ @includeHiddenChars@ - whether to include invisible text
+ -> IO String
+textBufferGetSlice self start end includeHiddenChars =
+ {# call unsafe text_buffer_get_slice #}
+ (toTextBuffer self)
+ start
+ end
+ (fromBool includeHiddenChars)
+ >>= readUTFString
+
+-- | Deletes current contents of @buffer@, and inserts @text@ instead. Similar
+-- to 'textBufferSetText' but uses 'ByteString' buffers.
hunk ./gtk/Graphics/UI/Gtk/Multiline/TextBuffer.chs 458
--- textBufferSetByteString textBuffer =<< Data.ByteString.readFile "hugeFile"
+-- * The passed-in buffer must contain a valid UTF-8 encoded string.
hunk ./gtk/Graphics/UI/Gtk/Multiline/TextBuffer.chs 470
--- | Same as `textBufferGetText`, but use to get *huge* string.
+-- | Returns the text in the range [@start@,@end@). Similar to
+-- `textBufferGetText` but uses 'ByteString' buffers.
+--
+-- * The returned buffer is a UTF-8 encoded string.
+--
hunk ./gtk/Graphics/UI/Gtk/Multiline/TextBuffer.chs 480
-textBufferGetByteString self start end includeHiddenChars =
- {# call unsafe text_buffer_get_text #}
+textBufferGetByteString self start end includeHiddenChars = do
+ sPtr <- {# call unsafe text_buffer_get_text #}
hunk ./gtk/Graphics/UI/Gtk/Multiline/TextBuffer.chs 486
- >>= \strPtr -> do
- strLen <- c_strlen strPtr
- unsafePackCStringFinalizer (castPtr strPtr) (fromIntegral strLen) ({#call unsafe g_free#} (castPtr strPtr))
+ sLen <- lengthArray0 0 sPtr
+ unsafePackCStringFinalizer (castPtr sPtr) (fromIntegral sLen)
+ ({#call unsafe g_free#} (castPtr sPtr))
hunk ./gtk/Graphics/UI/Gtk/Multiline/TextBuffer.chs 490
--- | Returns the text in the range [@start@,@end@). Excludes undisplayed text
--- (text marked with tags that set the invisibility attribute) if
--- @includeHiddenChars@ is @False@. The returned string includes a
--- @(chr 0xFFFC)@ character whenever the buffer contains embedded images, so
--- character indexes into the returned string /do/ correspond to
--- character indexes into the buffer. Contrast with 'textBufferGetText'. Note
--- that @(chr 0xFFFC)@ can occur in normal text as well, so it is not a reliable
--- indicator that a pixbuf or widget is in the buffer.
+-- | Returns the text in the range [@start@,@end@). Similar to
+-- `textBufferGetSlice` but uses 'ByteString' buffers.
hunk ./gtk/Graphics/UI/Gtk/Multiline/TextBuffer.chs 493
-textBufferGetSlice :: TextBufferClass self => self
+-- * The returned buffer is a UTF-8 encoded string.
+--
+textBufferGetByteStringSlice :: TextBufferClass self => self
hunk ./gtk/Graphics/UI/Gtk/Multiline/TextBuffer.chs 499
- -> IO String
-textBufferGetSlice self start end includeHiddenChars =
- {# call unsafe text_buffer_get_slice #}
+ -> IO ByteString
+textBufferGetByteStringSlice self start end includeHiddenChars = do
+ sPtr <- {# call unsafe text_buffer_get_slice #}
hunk ./gtk/Graphics/UI/Gtk/Multiline/TextBuffer.chs 506
- >>= readUTFString
+ sLen <- lengthArray0 0 sPtr
+ unsafePackCStringFinalizer (castPtr sPtr) (fromIntegral sLen)
+ ({#call unsafe g_free#} (castPtr sPtr))
}
|