Copyright | (c) Fumiaki Kinoshita 2019 |
---|---|
License | BSD3 |
Stability | Experimental |
Safe Haskell | None |
Language | Haskell2010 |
Maintainer : Fumiaki Kinoshita fumiexcel@gmail.com
Internal functions and datatypes
Synopsis
- unsignedVarInt :: (Bits a, Integral a) => a -> Builder
- varInt :: (Bits a, Integral a) => a -> Builder
- type Decoder = State ByteString
- evalDecoder :: Decoder a -> ByteString -> a
- newtype State s a = State {
- runState :: s -> (a, s)
- evalState :: State s a -> s -> a
- decodeVarInt :: (Num a, Bits a) => Decoder a
- decodeVarIntFinite :: forall a. (Num a, FiniteBits a) => Decoder a
- getWord8 :: Decoder Word8
- getWord16 :: Decoder Word16
- getWord32 :: Decoder Word32
- getWord64 :: Decoder Word64
- data DecodeException
- indexDefault :: a -> [a] -> Int -> a
- unsafeIndexV :: Unbox a => String -> Vector a -> Int -> a
- lookupWithIndexV :: Eq k => k -> Vector (k, v) -> Maybe (Int, v)
- newtype Strategy e r a = Strategy {
- unStrategy :: r -> Either e a
- throwStrategy :: e -> Strategy e r a
- newtype TransFusion f g a = TransFusion {
- unTransFusion :: forall h. Applicative h => (forall x. f x -> h (g x)) -> h a
Documentation
type Decoder = State ByteString Source #
evalDecoder :: Decoder a -> ByteString -> a Source #
A state monad. The reason being not State
from transformers is to
allow coercion for newtype deriving and DerivingVia.
decodeVarIntFinite :: forall a. (Num a, FiniteBits a) => Decoder a Source #
data DecodeException Source #
Instances
Eq DecodeException Source # | |
Defined in Data.Winery.Internal (==) :: DecodeException -> DecodeException -> Bool # (/=) :: DecodeException -> DecodeException -> Bool # | |
Read DecodeException Source # | |
Defined in Data.Winery.Internal | |
Show DecodeException Source # | |
Defined in Data.Winery.Internal showsPrec :: Int -> DecodeException -> ShowS # show :: DecodeException -> String # showList :: [DecodeException] -> ShowS # | |
Exception DecodeException Source # | |
Defined in Data.Winery.Internal |
indexDefault :: a -> [a] -> Int -> a Source #
newtype Strategy e r a Source #
A monad with Reader [r]
and Either WineryException
combined, used internally
to build an extractor.
r
is used to share environment such as extractors for fixpoints.
Strategy | |
|
throwStrategy :: e -> Strategy e r a Source #
newtype TransFusion f g a Source #
A Bazaar (chain of indexed store comonad)-like structure which instead works for natural transformations.
TransFusion | |
|
Instances
Functor (TransFusion f g) Source # | |
Defined in Data.Winery.Internal fmap :: (a -> b) -> TransFusion f g a -> TransFusion f g b # (<$) :: a -> TransFusion f g b -> TransFusion f g a # | |
Applicative (TransFusion f g) Source # | |
Defined in Data.Winery.Internal pure :: a -> TransFusion f g a # (<*>) :: TransFusion f g (a -> b) -> TransFusion f g a -> TransFusion f g b # liftA2 :: (a -> b -> c) -> TransFusion f g a -> TransFusion f g b -> TransFusion f g c # (*>) :: TransFusion f g a -> TransFusion f g b -> TransFusion f g b # (<*) :: TransFusion f g a -> TransFusion f g b -> TransFusion f g a # |