capnp-0.6.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Capnp.TraversalLimit

Description

This module is used to mitigate several pitfalls with the capnproto format, which could potentially lead to denial of service vulnerabilities.

In particular, while they are illegal according to the spec, it is possible to encode objects which have many pointers pointing the same place, or even cycles. A naive traversal therefore could involve quite a lot of computation for a message that is very small on the wire.

Accordingly, most implementations of the format keep track of how many bytes of a message have been accessed, and start signaling errors after a certain value (the "traversal limit") has been reached. The Haskell implementation is no exception; this module implements that logic. We provide a monad transformer and mtl-style type class to track the limit; reading from the message happens inside of this monad.

Synopsis

Documentation

class Monad m => MonadLimit m where Source #

mtl-style type class to track the traversal limit. This is used by other parts of the library which actually do the reading.

Methods

invoice :: WordCount -> m () Source #

invoice n deducts n from the traversal limit, signaling an error if the limit is exhausted.

Instances
MonadThrow m => MonadLimit (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> LimitT m () Source #

MonadLimit (PureBuilder s) Source # 
Instance details

Defined in Internal.BuildPure

(Monoid w, MonadLimit m) => MonadLimit (WriterT w m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> WriterT w m () Source #

MonadLimit m => MonadLimit (StateT s m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> StateT s m () Source #

MonadLimit m => MonadLimit (StateT s m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> StateT s m () Source #

MonadLimit m => MonadLimit (ReaderT r m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> ReaderT r m () Source #

(Monoid w, MonadLimit m) => MonadLimit (RWST r w s m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> RWST r w s m () Source #

data LimitT m a Source #

Monad transformer implementing MonadLimit. The underlying monad must implement MonadThrow. invoice calls throwM TraversalLimitError when the limit is exhausted.

Instances
MonadTrans LimitT Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

lift :: Monad m => m a -> LimitT m a #

MonadState s m => MonadState s (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

get :: LimitT m s #

put :: s -> LimitT m () #

state :: (s -> (a, s)) -> LimitT m a #

Monad m => Monad (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

(>>=) :: LimitT m a -> (a -> LimitT m b) -> LimitT m b #

(>>) :: LimitT m a -> LimitT m b -> LimitT m b #

return :: a -> LimitT m a #

fail :: String -> LimitT m a #

Functor m => Functor (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

fmap :: (a -> b) -> LimitT m a -> LimitT m b #

(<$) :: a -> LimitT m b -> LimitT m a #

MonadFail m => MonadFail (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

fail :: String -> LimitT m a #

Monad m => Applicative (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

pure :: a -> LimitT m a #

(<*>) :: LimitT m (a -> b) -> LimitT m a -> LimitT m b #

liftA2 :: (a -> b -> c) -> LimitT m a -> LimitT m b -> LimitT m c #

(*>) :: LimitT m a -> LimitT m b -> LimitT m b #

(<*) :: LimitT m a -> LimitT m b -> LimitT m a #

MonadIO m => MonadIO (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

liftIO :: IO a -> LimitT m a #

MonadThrow m => MonadThrow (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

throwM :: Exception e => e -> LimitT m a #

(PrimMonad m, s ~ PrimState m) => PrimMonad (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Associated Types

type PrimState (LimitT m) :: Type #

Methods

primitive :: (State# (PrimState (LimitT m)) -> (#State# (PrimState (LimitT m)), a#)) -> LimitT m a #

MonadThrow m => MonadLimit (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> LimitT m () Source #

type PrimState (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

runLimitT :: MonadThrow m => WordCount -> LimitT m a -> m (a, WordCount) Source #

Run a LimitT, returning the value from the computation and the remaining traversal limit.

evalLimitT :: MonadThrow m => WordCount -> LimitT m a -> m a Source #

Run a LimitT, returning the value from the computation.

execLimitT :: MonadThrow m => WordCount -> LimitT m a -> m WordCount Source #

Run a LimitT, returning the remaining traversal limit.

defaultLimit :: WordCount Source #

A sensible default traversal limit. Currently 64 MiB.