lazy-scope
Safe HaskellNone
LanguageGHC2024

Lazy.Scope

Documentation

data LazyT (s :: k) (m :: k1 -> Type) (a :: k1) Source #

Instances

Instances details
MonadReader r m => MonadReader r (LazyT s m) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

ask :: LazyT s m r #

local :: (r -> r) -> LazyT s m a -> LazyT s m a #

reader :: (r -> a) -> LazyT s m a #

MonadState s' m => MonadState s' (LazyT s m) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

get :: LazyT s m s' #

put :: s' -> LazyT s m () #

state :: (s' -> (a, s')) -> LazyT s m a #

MonadTrans (LazyT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

lift :: Monad m => m a -> LazyT s m a #

Applicative m => Applicative (LazyT s m) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

pure :: a -> LazyT s m a #

(<*>) :: LazyT s m (a -> b) -> LazyT s m a -> LazyT s m b #

liftA2 :: (a -> b -> c) -> LazyT s m a -> LazyT s m b -> LazyT s m c #

(*>) :: LazyT s m a -> LazyT s m b -> LazyT s m b #

(<*) :: LazyT s m a -> LazyT s m b -> LazyT s m a #

Functor m => Functor (LazyT s m) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

fmap :: (a -> b) -> LazyT s m a -> LazyT s m b #

(<$) :: a -> LazyT s m b -> LazyT s m a #

Monad m => Monad (LazyT s m) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

(>>=) :: LazyT s m a -> (a -> LazyT s m b) -> LazyT s m b #

(>>) :: LazyT s m a -> LazyT s m b -> LazyT s m b #

return :: a -> LazyT s m a #

MonadFail m => MonadFail (LazyT s m) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

fail :: String -> LazyT s m a #

MonadIO m => MonadIO (LazyT s m) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

liftIO :: IO a -> LazyT s m a #

MonadUnliftIO m => MonadUnliftIO (LazyT s m) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

withRunInIO :: ((forall a. LazyT s m a -> IO a) -> IO b) -> LazyT s m b #

data Handle (s :: k) Source #

Instances

Instances details
Show (Handle s) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

showsPrec :: Int -> Handle s -> ShowS #

show :: Handle s -> String #

showList :: [Handle s] -> ShowS #

Eq (Handle s) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

(==) :: Handle s -> Handle s -> Bool #

(/=) :: Handle s -> Handle s -> Bool #

data HandlePosn (s :: k) Source #

Instances

Instances details
Show (HandlePosn s) Source # 
Instance details

Defined in Lazy.Scope.Type

Eq (HandlePosn s) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

(==) :: HandlePosn s -> HandlePosn s -> Bool #

(/=) :: HandlePosn s -> HandlePosn s -> Bool #

type Bs (s :: k) = Scoped s LByteString Source #

data Scoped (s :: k) a Source #

Instances

Instances details
Applicative (Scoped s) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

pure :: a -> Scoped s a #

(<*>) :: Scoped s (a -> b) -> Scoped s a -> Scoped s b #

liftA2 :: (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c #

(*>) :: Scoped s a -> Scoped s b -> Scoped s b #

(<*) :: Scoped s a -> Scoped s b -> Scoped s a #

Functor (Scoped s) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

fmap :: (a -> b) -> Scoped s a -> Scoped s b #

(<$) :: a -> Scoped s b -> Scoped s a #

NFData a => NFData (Scoped s a) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

rnf :: Scoped s a -> () #

Monoid a => Monoid (Scoped s a) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

mempty :: Scoped s a #

mappend :: Scoped s a -> Scoped s a -> Scoped s a #

mconcat :: [Scoped s a] -> Scoped s a #

Semigroup a => Semigroup (Scoped s a) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

(<>) :: Scoped s a -> Scoped s a -> Scoped s a #

sconcat :: NonEmpty (Scoped s a) -> Scoped s a #

stimes :: Integral b => b -> Scoped s a -> Scoped s a #

IsString a => IsString (Scoped s a) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

fromString :: String -> Scoped s a #

Bounded a => Bounded (Scoped s a) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

minBound :: Scoped s a #

maxBound :: Scoped s a #

Num a => Num (Scoped s a) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

(+) :: Scoped s a -> Scoped s a -> Scoped s a #

(-) :: Scoped s a -> Scoped s a -> Scoped s a #

(*) :: Scoped s a -> Scoped s a -> Scoped s a #

negate :: Scoped s a -> Scoped s a #

abs :: Scoped s a -> Scoped s a #

signum :: Scoped s a -> Scoped s a #

fromInteger :: Integer -> Scoped s a #

Show a => Show (Scoped s a) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

showsPrec :: Int -> Scoped s a -> ShowS #

show :: Scoped s a -> String #

showList :: [Scoped s a] -> ShowS #

Eq a => Eq (Scoped s a) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

(==) :: Scoped s a -> Scoped s a -> Bool #

(/=) :: Scoped s a -> Scoped s a -> Bool #

Ord a => Ord (Scoped s a) Source # 
Instance details

Defined in Lazy.Scope.Type

Methods

compare :: Scoped s a -> Scoped s a -> Ordering #

(<) :: Scoped s a -> Scoped s a -> Bool #

(<=) :: Scoped s a -> Scoped s a -> Bool #

(>) :: Scoped s a -> Scoped s a -> Bool #

(>=) :: Scoped s a -> Scoped s a -> Bool #

max :: Scoped s a -> Scoped s a -> Scoped s a #

min :: Scoped s a -> Scoped s a -> Scoped s a #

hGetContents :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m (Bs s) Source #

hGetNonBlocking :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> Int -> LazyT s m (Bs s) Source #

hPutNonBlocking :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> Bs s -> LazyT s m (Bs s) Source #

hFileSize :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m Integer Source #

hFlush :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m () Source #

hGet :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> Int -> LazyT s m ByteString Source #

hGetBuf :: forall {k} (m :: Type -> Type) (s :: k) a. MonadIO m => Handle s -> Ptr a -> Int -> LazyT s m Int Source #

hGetBufNonBlocking :: forall {k} (m :: Type -> Type) (s :: k) a. MonadIO m => Handle s -> Ptr a -> Int -> LazyT s m Int Source #

hGetBufSome :: forall {k} (m :: Type -> Type) (s :: k) a. MonadIO m => Handle s -> Ptr a -> Int -> LazyT s m Int Source #

hGetBuffering :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m BufferMode Source #

hGetChar :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m Char Source #

hGetEcho :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m Bool Source #

hGetEncoding :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m (Maybe TextEncoding) Source #

hGetLine :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m String Source #

hGetPosn :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m (HandlePosn s) Source #

hIsEOF :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m Bool Source #

hIsReadable :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m Bool Source #

hIsSeekable :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m Bool Source #

hIsTerminalDevice :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m Bool Source #

hIsWritable :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m Bool Source #

hLookAhead :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m Char Source #

hPrint :: forall {k} (m :: Type -> Type) a (s :: k). (MonadIO m, Show a) => Handle s -> a -> LazyT s m () Source #

hPut :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> ByteString -> LazyT s m () Source #

hPutBs :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> Bs s -> LazyT s m () Source #

hPutBuf :: forall {k} (m :: Type -> Type) (s :: k) a. MonadIO m => Handle s -> Ptr a -> Int -> LazyT s m () Source #

hPutBufNonBlocking :: forall {k} (m :: Type -> Type) (s :: k) a. MonadIO m => Handle s -> Ptr a -> Int -> LazyT s m Int Source #

hPutChar :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> Char -> LazyT s m () Source #

hPutStr :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> String -> LazyT s m () Source #

hPutStrLn :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> String -> LazyT s m () Source #

hReady :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m Bool Source #

hSeek :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> SeekMode -> Integer -> LazyT s m () Source #

hSetBinaryMode :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> Bool -> LazyT s m () Source #

hSetBuffering :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> BufferMode -> LazyT s m () Source #

hSetEcho :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> Bool -> LazyT s m () Source #

hSetEncoding :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> TextEncoding -> LazyT s m () Source #

hSetFileSize :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> Integer -> LazyT s m () Source #

hSetNewlineMode :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> NewlineMode -> LazyT s m () Source #

hSetPosn :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => HandlePosn s -> LazyT s m () Source #

hShow :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m String Source #

hTell :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> LazyT s m Integer Source #

hWaitForInput :: forall {k} (m :: Type -> Type) (s :: k). MonadIO m => Handle s -> Int -> LazyT s m Bool Source #

(!?) :: forall {k} (s :: k). Bs s -> I64 s -> Scoped s (Maybe Word8) Source #

all :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> B s Source #

any :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> B s Source #

break :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) Source #

breakEnd :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) Source #

bs2Scoped :: forall {k} a (s :: k). (LByteString -> a) -> Bs s -> Scoped s a Source #

compareLength :: forall {k} (s :: k). Bs s -> I64 s -> Scoped s Ordering Source #

concat :: forall {k} (s :: k). [Bs s] -> Bs s Source #

concatMap :: forall {k} (s :: k). (Word8 -> LByteString) -> Bs s -> Bs s Source #

condM :: forall {k1} {k2} (s :: k1) m (a :: k2). [(Scoped s Bool, m a)] -> m a -> m a Source #

cons :: forall {k} (s :: k). W8 s -> Bs s -> Bs s Source #

copy :: forall {k} (s :: k). Bs s -> Bs s Source #

count :: forall {k} (s :: k). W8 s -> Bs s -> I64 s Source #

cycle :: forall {k} (s :: k). HasCallStack => Bs s -> Bs s Source #

drop :: forall {k} (s :: k). I64 s -> Bs s -> Bs s Source #

dropEnd :: forall {k} (s :: k). I64 s -> Bs s -> Bs s Source #

dropWhile :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Bs s Source #

dropWhileEnd :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Bs s Source #

elem :: forall {k} (s :: k). W8 s -> Bs s -> B s Source #

elemIndex :: forall {k} (s :: k). W8 s -> Bs s -> Scoped s (Maybe Int64) Source #

elemIndexEnd :: forall {k} (s :: k). W8 s -> Bs s -> Scoped s (Maybe Int64) Source #

elemIndices :: forall {k} (s :: k). W8 s -> Bs s -> Scoped s [Int64] Source #

empty :: forall {k} (s :: k). Bs s Source #

filter :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Bs s Source #

find :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Scoped s (Maybe Word8) Source #

findIndex :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Scoped s (Maybe Int64) Source #

findIndexEnd :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Scoped s (Maybe Int64) Source #

findIndices :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Scoped s [Int64] Source #

foldl' :: forall {k} (s :: k) a. (Scoped s a -> Word8 -> Scoped s a) -> Scoped s a -> Bs s -> Scoped s a Source #

foldr' :: forall {k} (s :: k) a. (Word8 -> Scoped s a -> Scoped s a) -> Scoped s a -> Bs s -> Scoped s a Source #

group :: forall {k} (s :: k). Bs s -> Scoped s [LByteString] Source #

groupBy :: forall {k} (s :: k). (Word8 -> Word8 -> Bool) -> Bs s -> Scoped s [LByteString] Source #

index :: forall {k} (s :: k). HasCallStack => Bs s -> I64 s -> W8 s Source #

indexMaybe :: forall {k} (s :: k). Bs s -> I64 s -> Scoped s (Maybe Word8) Source #

inits :: forall {k} (s :: k). Bs s -> Scoped s [LByteString] Source #

initsNE :: forall {k} (s :: k). Bs s -> Scoped s (NonEmpty LByteString) Source #

intercalate :: forall {k} (s :: k). Bs s -> [Bs s] -> Bs s Source #

intersperse :: forall {k} (s :: k). W8 s -> Bs s -> Bs s Source #

isPrefixOf :: forall {k} (s :: k). Bs s -> Bs s -> B s Source #

isSuffixOf :: forall {k} (s :: k). Bs s -> Bs s -> B s Source #

iterate :: forall {k} (s :: k). (W8 s -> W8 s) -> W8 s -> Bs s Source #

length :: forall {k} (s :: k). Bs s -> I64 s Source #

mapAccumL :: forall {k} acc (s :: k). (acc -> W8 s -> (acc, W8 s)) -> acc -> Bs s -> (acc, Bs s) Source #

mapAccumR :: forall {k} acc (s :: k). (acc -> W8 s -> (acc, W8 s)) -> acc -> Bs s -> (acc, Bs s) Source #

mapLbs :: forall {k} (s :: k). (LByteString -> LByteString) -> Bs s -> Bs s Source #

maximum :: forall {k} (s :: k). HasCallStack => Bs s -> W8 s Source #

minimum :: forall {k} (s :: k). HasCallStack => Bs s -> W8 s Source #

notElem :: forall {k} (s :: k). W8 s -> Bs s -> B s Source #

null :: forall {k} (s :: k). Bs s -> B s Source #

pack :: forall {k} (s :: k). [W8 s] -> Bs s Source #

packZipWith :: forall {k} (s :: k). (Word8 -> Word8 -> Word8) -> Bs s -> Bs s -> Bs s Source #

partition :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) Source #

repeat :: forall {k} (s :: k). W8 s -> Bs s Source #

replicate :: forall {k} (s :: k). I64 s -> W8 s -> Bs s Source #

reverse :: forall {k} (s :: k). Bs s -> Bs s Source #

scanl :: forall {k} (s :: k). (W8 s -> W8 s -> W8 s) -> W8 s -> Bs s -> Bs s Source #

scanl1 :: forall {k} (s :: k). (W8 s -> W8 s -> W8 s) -> Bs s -> Bs s Source #

scanr :: forall {k} (s :: k). (W8 s -> W8 s -> W8 s) -> W8 s -> Bs s -> Bs s Source #

scanr1 :: forall {k} (s :: k). (W8 s -> W8 s -> W8 s) -> Bs s -> Bs s Source #

scoped2Bs :: forall {k} a (s :: k). (a -> LByteString) -> Scoped s a -> Bs s Source #

singleton :: forall {k} (s :: k). W8 s -> Bs s Source #

snoc :: forall {k} (s :: k). Bs s -> W8 s -> Bs s Source #

span :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) Source #

spanEnd :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) Source #

splitAt :: forall {k} (s :: k). I64 s -> Bs s -> (Bs s, Bs s) Source #

splitWith :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Scoped s [LByteString] Source #

stripPrefix :: forall {k} (s :: k). Bs s -> Bs s -> Scoped s (Maybe LByteString) Source #

stripSuffix :: forall {k} (s :: k). Bs s -> Bs s -> Scoped s (Maybe LByteString) Source #

tails :: forall {k} (s :: k). Bs s -> Scoped s [LByteString] Source #

tailsNE :: forall {k} (s :: k). Bs s -> Scoped s (NonEmpty LByteString) Source #

take :: forall {k} (s :: k). Int64 -> Bs s -> Bs s Source #

takeWhile :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Bs s Source #

takeWhileEnd :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Bs s Source #

toBs :: forall {k} (s :: k). LByteString -> Bs s Source #

toLbs :: forall {k} (m :: Type -> Type) (s :: k). Monad m => Bs s -> LazyT s m LByteString Source #

transpose :: forall {k} (s :: k). [Bs s] -> [Bs s] Source #

unScope :: forall {k} a (m :: Type -> Type) (s :: k). (NFData a, Monad m) => Scoped s a -> LazyT s m a Source #

uncons :: forall {k} (s :: k). Bs s -> Scoped s (Maybe (Word8, LByteString)) Source #

unfoldr :: forall {k} a (s :: k). (a -> Maybe (W8 s, a)) -> a -> Bs s Source #

unpack8 :: forall {k} (m :: Type -> Type) (s :: k). Monad m => Bs s -> LazyT s m String Source #

unsnoc :: forall {k} (s :: k). Bs s -> Scoped s (Maybe (LByteString, Word8)) Source #

unzip :: forall {k} (s :: k). Scoped s [(Word8, Word8)] -> (Bs s, Bs s) Source #

zip :: forall {k} (s :: k). Bs s -> Bs s -> Scoped s [(Word8, Word8)] Source #

zipWith :: forall {k} a (s :: k). (Word8 -> Word8 -> a) -> Bs s -> Bs s -> Scoped s [a] Source #

class WithFile a where Source #

Methods

withFile :: forall {k} r m. (NFData r, MonadUnliftIO m) => a -> IOMode -> (forall (s :: k). Handle s -> LazyT s m r) -> m r Source #

withBinaryFile :: forall {k} r m. (NFData r, MonadUnliftIO m) => a -> IOMode -> (forall (s :: k). Handle s -> LazyT s m r) -> m r Source #

Instances

Instances details
WithFile FilePath Source # 
Instance details

Defined in Lazy.Scope.Io

Methods

withFile :: forall {k} r m. (NFData r, MonadUnliftIO m) => FilePath -> IOMode -> (forall (s :: k). Handle s -> LazyT s m r) -> m r Source #

withBinaryFile :: forall {k} r m. (NFData r, MonadUnliftIO m) => FilePath -> IOMode -> (forall (s :: k). Handle s -> LazyT s m r) -> m r Source #