trifecta-2.1: A modern parser combinator library with convenient diagnostics

Copyright(C) 2011-2019 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Text.Trifecta.Util.It

Description

harder, better, faster, stronger...

Synopsis

Documentation

data It r a Source #

It is an Iteratee that can produce partial results.

It r a consumes a feed of rs and produces as on the way. New values can be fed using simplifyIt, the current (partial or final) result is extracted using extract.

>>> let keepIt    a = Pure a
>>> let replaceIt a = It a replaceIt
>>> extract (keepIt 0)
0
>>> extract (replaceIt 0)
0
>>> extract (simplifyIt (keepIt 0) 5)
0
>>> extract (simplifyIt (replaceIt 0) 5)
5

Constructors

Pure a

Final result, rest of the feed is discarded

It a (r -> It r a)

Intermediate result, consumed values produce new results

Instances
Profunctor It Source # 
Instance details

Defined in Text.Trifecta.Util.It

Methods

dimap :: (a -> b) -> (c -> d) -> It b c -> It a d #

lmap :: (a -> b) -> It b c -> It a c #

rmap :: (b -> c) -> It a b -> It a c #

(#.) :: Coercible c b => q b c -> It a b -> It a c #

(.#) :: Coercible b a => It b c -> q a b -> It a c #

Monad (It r) Source # 
Instance details

Defined in Text.Trifecta.Util.It

Methods

(>>=) :: It r a -> (a -> It r b) -> It r b #

(>>) :: It r a -> It r b -> It r b #

return :: a -> It r a #

fail :: String -> It r a #

Functor (It r) Source # 
Instance details

Defined in Text.Trifecta.Util.It

Methods

fmap :: (a -> b) -> It r a -> It r b #

(<$) :: a -> It r b -> It r a #

Applicative (It r) Source # 
Instance details

Defined in Text.Trifecta.Util.It

Methods

pure :: a -> It r a #

(<*>) :: It r (a -> b) -> It r a -> It r b #

liftA2 :: (a -> b -> c) -> It r a -> It r b -> It r c #

(*>) :: It r a -> It r b -> It r b #

(<*) :: It r a -> It r b -> It r a #

Comonad (It r) Source #

It is a cofree comonad

Instance details

Defined in Text.Trifecta.Util.It

Methods

extract :: It r a -> a #

duplicate :: It r a -> It r (It r a) #

extend :: (It r a -> b) -> It r a -> It r b #

ComonadApply (It r) Source # 
Instance details

Defined in Text.Trifecta.Util.It

Methods

(<@>) :: It r (a -> b) -> It r a -> It r b #

(@>) :: It r a -> It r b -> It r b #

(<@) :: It r a -> It r b -> It r a #

Show a => Show (It r a) Source # 
Instance details

Defined in Text.Trifecta.Util.It

Methods

showsPrec :: Int -> It r a -> ShowS #

show :: It r a -> String #

showList :: [It r a] -> ShowS #

needIt Source #

Arguments

:: a

Initial result

-> (r -> Maybe a)

Produce a result if possible

-> It r a 

Consumes input until a value can be produced.

>>> :{
let needTen = needIt 0 (\n -> if n < 10 then Nothing else Just n) :: It Int Int
:}
>>> extract needTen
0
>>> extract (simplifyIt needTen 5)
0
>>> extract (simplifyIt needTen 11)
11
>>> extract (simplifyIt (simplifyIt (simplifyIt needTen 5) 11) 15)
11

wantIt Source #

Arguments

:: a

Initial result

-> (r -> (#Bool, a#))

Produce a partial or final result

-> It r a 

Consumes input and produces partial results until a condition is met. Unlike needIt, partial results are already returned when the condition is not fulfilled yet.

>>> :{
let wantTen :: It Int Int
    wantTen = wantIt 0 (\n -> (# n >= 10, n #))
:}
>>> extract wantTen
0
>>> extract (simplifyIt wantTen 5)
5
>>> extract (simplifyIt wantTen 11)
11
>>> extract (simplifyIt (simplifyIt (simplifyIt wantTen 5) 11) 15)
11

simplifyIt :: It r a -> r -> It r a Source #

Feed a value to It, obtaining a new (partial or final) result.

foldIt :: (a -> o) -> (a -> (r -> o) -> o) -> It r a -> o Source #

The generalized fold (Böhm-Berarducci decoding) over 'It r a'.

foldIt satisfies the property:

foldIt Pure It = id

runIt :: (a -> o) -> (a -> (r -> It r a) -> o) -> It r a -> o Source #

Scott decoding of 'It r a'.

The scott decoding is similar to the generalized fold over a data type, but leaves the recursion step to the calling function.

runIt satiesfies the property:

runIt Pure It = id

See also the Scott decoding of lists:

runList :: (a -> [a] -> b) -> b -> [a] -> b

and compare it with Foldable (the Böhm-Berarducci decoding for lists):

foldr :: (a -> b -> b) -> b -> [a] -> b

fillIt :: r -> (Delta -> ByteString -> r) -> Delta -> It Rope r Source #

Given a position, go there, and grab the rest of the line forward from that point.

>>> :set -XOverloadedStrings
>>> let secondLine = fillIt Nothing (const Just) (delta ("foo\nb" :: Strict.ByteString))
>>> extract secondLine
Nothing
>>> extract (simplifyIt secondLine (ropeBS "foo"))
Nothing
>>> extract (simplifyIt secondLine (ropeBS "foo\nbar"))
Just "ar"
>>> extract (simplifyIt secondLine (ropeBS "foo\nbar\nbaz"))
Just "ar\n"

rewindIt :: Delta -> It Rope (Maybe ByteString) Source #

Return the text of the line that contains a given position

>>> :set -XOverloadedStrings
>>> let secondLine = rewindIt (delta ("foo\nb" :: Strict.ByteString))
>>> extract secondLine
Nothing
>>> extract (simplifyIt secondLine (ropeBS "foo"))
Nothing
>>> extract (simplifyIt secondLine (ropeBS "foo\nbar"))
Just "bar"
>>> extract (simplifyIt secondLine (ropeBS "foo\nbar\nbaz"))
Just "bar\n"

sliceIt :: Delta -> Delta -> It Rope ByteString Source #

Return the text between two offsets.

>>> :set -XOverloadedStrings
>>> let secondLine = sliceIt (delta ("foo\n" :: Strict.ByteString)) (delta ("foo\nbar\n" :: Strict.ByteString))
>>> extract secondLine
""
>>> extract (simplifyIt secondLine (ropeBS "foo"))
""
>>> extract (simplifyIt secondLine (ropeBS "foo\nbar"))
"bar"
>>> extract (simplifyIt secondLine (ropeBS "foo\nbar\nbaz"))
"bar\n"