Copyright | (C) 2011-2015 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe |
Language | Haskell2010 |
A rope is a data strucure to efficiently store and manipulate long strings. Wikipedia provides a nice overview: https://en.wikipedia.org/wiki/Rope_(data_structure)
Synopsis
- data Rope = Rope !Delta !(FingerTree Delta Strand)
- rope :: FingerTree Delta Strand -> Rope
- ropeBS :: ByteString -> Rope
- data Strand
- = Strand !ByteString !Delta
- | Skipping !Delta
- strand :: ByteString -> Strand
- strands :: Rope -> FingerTree Delta Strand
- grabRest :: Delta -> Rope -> r -> (Delta -> ByteString -> r) -> r
- grabLine :: Delta -> Rope -> r -> (Delta -> ByteString -> r) -> r
Documentation
Rope !Delta !(FingerTree Delta Strand) |
Instances
Show Rope Source # | |
Semigroup Rope Source # | |
Monoid Rope Source # | |
HasDelta Rope Source # | |
HasBytes Rope Source # | |
Measured Delta Rope Source # | |
Defined in Text.Trifecta.Rope | |
Reducer ByteString Rope Source # | |
Defined in Text.Trifecta.Rope unit :: ByteString -> Rope # snoc :: Rope -> ByteString -> Rope # cons :: ByteString -> Rope -> Rope # | |
Reducer Rope Rope Source # | |
Reducer Strand Rope Source # | |
Reducer [Char] Rope Source # | |
ropeBS :: ByteString -> Rope Source #
Construct a Rope
out of a single ByteString
strand.
Strand !ByteString !Delta | Data of a certain length |
Skipping !Delta | Absence of data of a certain length |
Instances
Data Strand Source # | |
Defined in Text.Trifecta.Rope gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Strand -> c Strand # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Strand # toConstr :: Strand -> Constr # dataTypeOf :: Strand -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Strand) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Strand) # gmapT :: (forall b. Data b => b -> b) -> Strand -> Strand # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Strand -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Strand -> r # gmapQ :: (forall d. Data d => d -> u) -> Strand -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Strand -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Strand -> m Strand # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Strand -> m Strand # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Strand -> m Strand # | |
Show Strand Source # | |
Generic Strand Source # | |
Hashable Strand Source # | |
Defined in Text.Trifecta.Rope | |
HasDelta Strand Source # | |
HasBytes Strand Source # | |
Measured Delta Strand Source # | |
Defined in Text.Trifecta.Rope | |
Reducer Strand Rope Source # | |
type Rep Strand Source # | |
Defined in Text.Trifecta.Rope type Rep Strand = D1 (MetaData "Strand" "Text.Trifecta.Rope" "trifecta-2-3LqJ6YGQno0FNVjGdpeVXY" False) (C1 (MetaCons "Strand" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 ByteString) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Delta)) :+: C1 (MetaCons "Skipping" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Delta))) |
strand :: ByteString -> Strand Source #
Construct a single Strand
out of a ByteString
.
:: Delta | Initial offset |
-> Rope | Input |
-> r | Default value if there is no input left |
-> (Delta -> ByteString -> r) | If there is some input left, create an |
-> r |
Grab the entire rest of the input Rope
, starting at an initial offset, or
return a default if we’re already at or beyond the end. Also see grabLine
.
Extract a suffix of a certain length from the input:
>>>
grabRest (delta ("Hello " :: ByteString)) (ropeBS "Hello World\nLorem") Nothing (\x y -> Just (x, Lazy.toString y))
Just (Columns 6 6,"World\nLorem")
Same deal, but over multiple strands:
>>>
grabRest (delta ("Hel" :: ByteString)) (ropeBS "Hello" <> ropeBS "World") Nothing (\x y -> Just (x, Lazy.toString y))
Just (Columns 3 3,"loWorld")
When the offset is too long, fall back to a default:
>>>
grabRest (delta ("OffetTooLong" :: ByteString)) (ropeBS "Hello") Nothing (\x y -> Just (x, Lazy.toString y))
Nothing
:: Delta | Initial offset |
-> Rope | Input |
-> r | Default value if there is no input left |
-> (Delta -> ByteString -> r) | If there is some input left, create an |
-> r |
Grab the rest of the line at a certain offset in the input Rope
, or
return a default if there is no newline left in the input. Also see
grabRest
.
>>>
grabLine (delta ("Hello " :: ByteString)) (ropeBS "Hello" <> ropeBS " World\nLorem") Nothing (\x y -> Just (x, Strict.toString y))
Just (Columns 6 6,"World\n")