{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude, ExistentialQuantification #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE PatternSynonyms, ViewPatterns #-}
{-# LANGUAGE UnboxedTuples, MagicHash #-}
module GHC.Internal.IO.Encoding.Types (
    BufferCodec(.., BufferCodec, encode, recover, close, getState, setState),
    TextEncoding(..),
    TextEncoder, TextDecoder,
    CodeBuffer, EncodeBuffer, DecodeBuffer,
    CodingProgress(..),
    DecodeBuffer#, EncodeBuffer#,
    DecodingBuffer#, EncodingBuffer#
  ) where
import GHC.Internal.Base
import GHC.Internal.Word
import GHC.Internal.Show
import GHC.Internal.IO.Buffer
data BufferCodec from to state = BufferCodec# {
  forall from to state.
BufferCodec from to state -> CodeBuffer# from to
encode# :: CodeBuffer# from to,
   
   
   
   
   
   
   
   
   
   
   
   
   
   
  forall from to state.
BufferCodec from to state
-> Buffer from
-> Buffer to
-> State# RealWorld
-> (# State# RealWorld, Buffer from, Buffer to #)
recover# :: Buffer from -> Buffer to -> State# RealWorld -> (# State# RealWorld, Buffer from, Buffer to #),
   
   
   
   
   
   
   
   
   
   
   
   
   
   
   
   
   
  forall from to state. BufferCodec from to state -> IO ()
close# :: IO (),
   
   
   
  forall from to state. BufferCodec from to state -> IO state
getState# :: IO state,
   
   
   
   
   
   
   
   
   
   
   
  forall from to state. BufferCodec from to state -> state -> IO ()
setState# :: state -> IO ()
   
   
 }
type CodeBuffer      from to = Buffer from -> Buffer to -> IO (CodingProgress, Buffer from, Buffer to)
type DecodeBuffer            = CodeBuffer Word8 Char
type EncodeBuffer            = CodeBuffer Char Word8
type CodeBuffer#     from to = Buffer from -> Buffer to -> State# RealWorld -> (# State# RealWorld, CodingProgress, Buffer from, Buffer to #)
type DecodeBuffer#           = CodeBuffer# Word8 Char
type EncodeBuffer#           = CodeBuffer# Char  Word8
type CodingBuffer#   from to = State# RealWorld -> (# State# RealWorld, CodingProgress, Buffer from, Buffer to #)
type DecodingBuffer#         = CodingBuffer# Word8 Char
type EncodingBuffer#         = CodingBuffer# Char  Word8
type TextDecoder state = BufferCodec Word8 CharBufElem state
type TextEncoder state = BufferCodec CharBufElem Word8 state
data TextEncoding
  = forall dstate estate . TextEncoding  {
        TextEncoding -> String
textEncodingName :: String,
                   
                   
        ()
mkTextDecoder :: IO (TextDecoder dstate),
                   
                   
        ()
mkTextEncoder :: IO (TextEncoder estate)
                   
                   
  }
instance Show TextEncoding where
  show :: TextEncoding -> String
show TextEncoding
te = TextEncoding -> String
textEncodingName TextEncoding
te
data CodingProgress = InputUnderflow  
                                      
                    | OutputUnderflow 
                    | InvalidSequence 
                                      
                                      
                    deriving ( CodingProgress -> CodingProgress -> Bool
(CodingProgress -> CodingProgress -> Bool)
-> (CodingProgress -> CodingProgress -> Bool) -> Eq CodingProgress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CodingProgress -> CodingProgress -> Bool
== :: CodingProgress -> CodingProgress -> Bool
$c/= :: CodingProgress -> CodingProgress -> Bool
/= :: CodingProgress -> CodingProgress -> Bool
Eq   
                             , Int -> CodingProgress -> ShowS
[CodingProgress] -> ShowS
CodingProgress -> String
(Int -> CodingProgress -> ShowS)
-> (CodingProgress -> String)
-> ([CodingProgress] -> ShowS)
-> Show CodingProgress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CodingProgress -> ShowS
showsPrec :: Int -> CodingProgress -> ShowS
$cshow :: CodingProgress -> String
show :: CodingProgress -> String
$cshowList :: [CodingProgress] -> ShowS
showList :: [CodingProgress] -> ShowS
Show 
                             )
{-# COMPLETE BufferCodec #-}
pattern BufferCodec :: CodeBuffer from to
                    -> (Buffer from -> Buffer to -> IO (Buffer from, Buffer to))
                    -> IO ()
                    -> IO state
                    -> (state -> IO ())
                    -> BufferCodec from to state
pattern $mBufferCodec :: forall {r} {from} {to} {state}.
BufferCodec from to state
-> (CodeBuffer from to
    -> (Buffer from -> Buffer to -> IO (Buffer from, Buffer to))
    -> IO ()
    -> IO state
    -> (state -> IO ())
    -> r)
-> ((# #) -> r)
-> r
$bBufferCodec :: forall from to state.
CodeBuffer from to
-> (Buffer from -> Buffer to -> IO (Buffer from, Buffer to))
-> IO ()
-> IO state
-> (state -> IO ())
-> BufferCodec from to state
BufferCodec{forall from to state.
BufferCodec from to state -> CodeBuffer from to
encode, forall from to state.
BufferCodec from to state
-> Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
recover, forall from to state. BufferCodec from to state -> IO ()
close, forall from to state. BufferCodec from to state -> IO state
getState, forall from to state. BufferCodec from to state -> state -> IO ()
setState} <-
    BufferCodec# (getEncode -> encode) (getRecover -> recover) close getState setState
  where
    BufferCodec CodeBuffer from to
e Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
r IO ()
c IO state
g state -> IO ()
s = CodeBuffer# from to
-> (Buffer from
    -> Buffer to
    -> State# RealWorld
    -> (# State# RealWorld, Buffer from, Buffer to #))
-> IO ()
-> IO state
-> (state -> IO ())
-> BufferCodec from to state
forall from to state.
CodeBuffer# from to
-> (Buffer from
    -> Buffer to
    -> State# RealWorld
    -> (# State# RealWorld, Buffer from, Buffer to #))
-> IO ()
-> IO state
-> (state -> IO ())
-> BufferCodec from to state
BufferCodec# (CodeBuffer from to -> CodeBuffer# from to
forall from to. CodeBuffer from to -> CodeBuffer# from to
mkEncode CodeBuffer from to
e) ((Buffer from -> Buffer to -> IO (Buffer from, Buffer to))
-> Buffer from
-> Buffer to
-> State# RealWorld
-> (# State# RealWorld, Buffer from, Buffer to #)
forall from to.
(Buffer from -> Buffer to -> IO (Buffer from, Buffer to))
-> Buffer from
-> Buffer to
-> State# RealWorld
-> (# State# RealWorld, Buffer from, Buffer to #)
mkRecover Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
r) IO ()
c IO state
g state -> IO ()
s
getEncode :: CodeBuffer# from to -> CodeBuffer from to
getEncode :: forall from to. CodeBuffer# from to -> CodeBuffer from to
getEncode CodeBuffer# from to
e Buffer from
i Buffer to
o = (State# RealWorld
 -> (# State# RealWorld,
       (CodingProgress, Buffer from, Buffer to) #))
-> IO (CodingProgress, Buffer from, Buffer to)
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld
  -> (# State# RealWorld,
        (CodingProgress, Buffer from, Buffer to) #))
 -> IO (CodingProgress, Buffer from, Buffer to))
-> (State# RealWorld
    -> (# State# RealWorld,
          (CodingProgress, Buffer from, Buffer to) #))
-> IO (CodingProgress, Buffer from, Buffer to)
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
st ->
  let !(# State# RealWorld
st', CodingProgress
prog, Buffer from
i', Buffer to
o' #) = CodeBuffer# from to
e Buffer from
i Buffer to
o State# RealWorld
st in (# State# RealWorld
st', (CodingProgress
prog, Buffer from
i', Buffer to
o') #)
getRecover :: (Buffer from -> Buffer to -> State# RealWorld -> (# State# RealWorld, Buffer from, Buffer to #))
           -> (Buffer from -> Buffer to -> IO (Buffer from, Buffer to))
getRecover :: forall from to.
(Buffer from
 -> Buffer to
 -> State# RealWorld
 -> (# State# RealWorld, Buffer from, Buffer to #))
-> Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
getRecover Buffer from
-> Buffer to
-> State# RealWorld
-> (# State# RealWorld, Buffer from, Buffer to #)
r Buffer from
i Buffer to
o = (State# RealWorld
 -> (# State# RealWorld, (Buffer from, Buffer to) #))
-> IO (Buffer from, Buffer to)
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld
  -> (# State# RealWorld, (Buffer from, Buffer to) #))
 -> IO (Buffer from, Buffer to))
-> (State# RealWorld
    -> (# State# RealWorld, (Buffer from, Buffer to) #))
-> IO (Buffer from, Buffer to)
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
st ->
  let !(# State# RealWorld
st', Buffer from
i', Buffer to
o' #) = Buffer from
-> Buffer to
-> State# RealWorld
-> (# State# RealWorld, Buffer from, Buffer to #)
r Buffer from
i Buffer to
o State# RealWorld
st in (# State# RealWorld
st', (Buffer from
i', Buffer to
o') #)
mkEncode :: CodeBuffer from to -> CodeBuffer# from to
mkEncode :: forall from to. CodeBuffer from to -> CodeBuffer# from to
mkEncode CodeBuffer from to
e Buffer from
i Buffer to
o State# RealWorld
st = let !(# State# RealWorld
st', (CodingProgress
prog, Buffer from
i', Buffer to
o') #) = IO (CodingProgress, Buffer from, Buffer to)
-> State# RealWorld
-> (# State# RealWorld, (CodingProgress, Buffer from, Buffer to) #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (CodeBuffer from to
e Buffer from
i Buffer to
o) State# RealWorld
st in (# State# RealWorld
st', CodingProgress
prog, Buffer from
i', Buffer to
o' #)
mkRecover :: (Buffer from -> Buffer to -> IO (Buffer from, Buffer to))
          -> (Buffer from -> Buffer to -> State# RealWorld -> (# State# RealWorld, Buffer from, Buffer to #))
mkRecover :: forall from to.
(Buffer from -> Buffer to -> IO (Buffer from, Buffer to))
-> Buffer from
-> Buffer to
-> State# RealWorld
-> (# State# RealWorld, Buffer from, Buffer to #)
mkRecover Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
r Buffer from
i Buffer to
o State# RealWorld
st = let !(# State# RealWorld
st', (Buffer from
i', Buffer to
o') #) = IO (Buffer from, Buffer to)
-> State# RealWorld
-> (# State# RealWorld, (Buffer from, Buffer to) #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (Buffer from -> Buffer to -> IO (Buffer from, Buffer to)
r Buffer from
i Buffer to
o) State# RealWorld
st in (# State# RealWorld
st', Buffer from
i', Buffer to
o' #)