{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude
           , BangPatterns
           , NondecreasingIndentation
           , UnboxedTuples
           , MagicHash
  #-}
{-# OPTIONS_GHC  -funbox-strict-fields #-}
module GHC.IO.Encoding.Latin1 (
  latin1, mkLatin1,
  latin1_checked, mkLatin1_checked,
  ascii, mkAscii,
  latin1_decode,
  ascii_decode,
  latin1_encode,
  latin1_checked_encode,
  ascii_encode,
  ) where
import GHC.Base
import GHC.Real
import GHC.Num
import GHC.IO.Buffer
import GHC.IO.Encoding.Failure
import GHC.IO.Encoding.Types
latin1 :: TextEncoding
latin1 :: TextEncoding
latin1 = CodingFailureMode -> TextEncoding
mkLatin1 CodingFailureMode
ErrorOnCodingFailure
mkLatin1 :: CodingFailureMode -> TextEncoding
mkLatin1 :: CodingFailureMode -> TextEncoding
mkLatin1 CodingFailureMode
cfm = TextEncoding { textEncodingName :: String
textEncodingName = String
"ISO-8859-1",
                              mkTextDecoder :: IO (TextDecoder ())
mkTextDecoder = CodingFailureMode -> IO (TextDecoder ())
latin1_DF CodingFailureMode
cfm,
                              mkTextEncoder :: IO (TextEncoder ())
mkTextEncoder = CodingFailureMode -> IO (TextEncoder ())
latin1_EF CodingFailureMode
cfm }
latin1_DF :: CodingFailureMode -> IO (TextDecoder ())
latin1_DF :: CodingFailureMode -> IO (TextDecoder ())
latin1_DF CodingFailureMode
cfm =
  TextDecoder () -> IO (TextDecoder ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (BufferCodec# {
             encode# :: CodeBuffer# Word8 Char
encode#   = CodeBuffer# Word8 Char
latin1_decode,
             recover# :: Buffer Word8
-> Buffer Char
-> State# RealWorld
-> (# State# RealWorld, Buffer Word8, Buffer Char #)
recover#  = CodingFailureMode
-> Buffer Word8
-> Buffer Char
-> State# RealWorld
-> (# State# RealWorld, Buffer Word8, Buffer Char #)
recoverDecode# CodingFailureMode
cfm,
             close# :: IO ()
close#    = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (),
             getState# :: IO ()
getState# = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (),
             setState# :: () -> IO ()
setState# = IO () -> () -> IO ()
forall a b. a -> b -> a
const (IO () -> () -> IO ()) -> IO () -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
          })
latin1_EF :: CodingFailureMode -> IO (TextEncoder ())
latin1_EF :: CodingFailureMode -> IO (TextEncoder ())
latin1_EF CodingFailureMode
cfm =
  TextEncoder () -> IO (TextEncoder ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (BufferCodec# {
             encode# :: CodeBuffer# Char Word8
encode#   = CodeBuffer# Char Word8
latin1_encode,
             recover# :: Buffer Char
-> Buffer Word8
-> State# RealWorld
-> (# State# RealWorld, Buffer Char, Buffer Word8 #)
recover#  = CodingFailureMode
-> Buffer Char
-> Buffer Word8
-> State# RealWorld
-> (# State# RealWorld, Buffer Char, Buffer Word8 #)
recoverEncode# CodingFailureMode
cfm,
             close# :: IO ()
close#    = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (),
             getState# :: IO ()
getState# = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (),
             setState# :: () -> IO ()
setState# = IO () -> () -> IO ()
forall a b. a -> b -> a
const (IO () -> () -> IO ()) -> IO () -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
          })
latin1_checked :: TextEncoding
latin1_checked :: TextEncoding
latin1_checked = CodingFailureMode -> TextEncoding
mkLatin1_checked CodingFailureMode
ErrorOnCodingFailure
mkLatin1_checked :: CodingFailureMode -> TextEncoding
mkLatin1_checked :: CodingFailureMode -> TextEncoding
mkLatin1_checked CodingFailureMode
cfm = TextEncoding { textEncodingName :: String
textEncodingName = String
"ISO-8859-1",
                                      mkTextDecoder :: IO (TextDecoder ())
mkTextDecoder = CodingFailureMode -> IO (TextDecoder ())
latin1_DF CodingFailureMode
cfm,
                                      mkTextEncoder :: IO (TextEncoder ())
mkTextEncoder = CodingFailureMode -> IO (TextEncoder ())
latin1_checked_EF CodingFailureMode
cfm }
latin1_checked_EF :: CodingFailureMode -> IO (TextEncoder ())
latin1_checked_EF :: CodingFailureMode -> IO (TextEncoder ())
latin1_checked_EF CodingFailureMode
cfm =
  TextEncoder () -> IO (TextEncoder ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (BufferCodec# {
             encode# :: CodeBuffer# Char Word8
encode#   = CodeBuffer# Char Word8
latin1_checked_encode,
             recover# :: Buffer Char
-> Buffer Word8
-> State# RealWorld
-> (# State# RealWorld, Buffer Char, Buffer Word8 #)
recover#  = CodingFailureMode
-> Buffer Char
-> Buffer Word8
-> State# RealWorld
-> (# State# RealWorld, Buffer Char, Buffer Word8 #)
recoverEncode# CodingFailureMode
cfm,
             close# :: IO ()
close#    = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (),
             getState# :: IO ()
getState# = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (),
             setState# :: () -> IO ()
setState# = IO () -> () -> IO ()
forall a b. a -> b -> a
const (IO () -> () -> IO ()) -> IO () -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
          })
ascii :: TextEncoding
ascii :: TextEncoding
ascii = CodingFailureMode -> TextEncoding
mkAscii CodingFailureMode
ErrorOnCodingFailure
mkAscii :: CodingFailureMode -> TextEncoding
mkAscii :: CodingFailureMode -> TextEncoding
mkAscii CodingFailureMode
cfm = TextEncoding { textEncodingName :: String
textEncodingName = String
"ASCII",
                             mkTextDecoder :: IO (TextDecoder ())
mkTextDecoder = CodingFailureMode -> IO (TextDecoder ())
ascii_DF CodingFailureMode
cfm,
                             mkTextEncoder :: IO (TextEncoder ())
mkTextEncoder = CodingFailureMode -> IO (TextEncoder ())
ascii_EF CodingFailureMode
cfm }
ascii_DF :: CodingFailureMode -> IO (TextDecoder ())
ascii_DF :: CodingFailureMode -> IO (TextDecoder ())
ascii_DF CodingFailureMode
cfm =
  TextDecoder () -> IO (TextDecoder ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (BufferCodec# {
             encode# :: CodeBuffer# Word8 Char
encode#   = CodeBuffer# Word8 Char
ascii_decode,
             recover# :: Buffer Word8
-> Buffer Char
-> State# RealWorld
-> (# State# RealWorld, Buffer Word8, Buffer Char #)
recover#  = CodingFailureMode
-> Buffer Word8
-> Buffer Char
-> State# RealWorld
-> (# State# RealWorld, Buffer Word8, Buffer Char #)
recoverDecode# CodingFailureMode
cfm,
             close# :: IO ()
close#    = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (),
             getState# :: IO ()
getState# = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (),
             setState# :: () -> IO ()
setState# = IO () -> () -> IO ()
forall a b. a -> b -> a
const (IO () -> () -> IO ()) -> IO () -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
          })
ascii_EF :: CodingFailureMode -> IO (TextEncoder ())
ascii_EF :: CodingFailureMode -> IO (TextEncoder ())
ascii_EF CodingFailureMode
cfm =
  TextEncoder () -> IO (TextEncoder ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (BufferCodec# {
             encode# :: CodeBuffer# Char Word8
encode#   = CodeBuffer# Char Word8
ascii_encode,
             recover# :: Buffer Char
-> Buffer Word8
-> State# RealWorld
-> (# State# RealWorld, Buffer Char, Buffer Word8 #)
recover#  = CodingFailureMode
-> Buffer Char
-> Buffer Word8
-> State# RealWorld
-> (# State# RealWorld, Buffer Char, Buffer Word8 #)
recoverEncode# CodingFailureMode
cfm,
             close# :: IO ()
close#    = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (),
             getState# :: IO ()
getState# = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (),
             setState# :: () -> IO ()
setState# = IO () -> () -> IO ()
forall a b. a -> b -> a
const (IO () -> () -> IO ()) -> IO () -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
          })
latin1_decode :: DecodeBuffer#
latin1_decode :: CodeBuffer# Word8 Char
latin1_decode 
  input :: Buffer Word8
input@Buffer{  bufRaw :: forall e. Buffer e -> RawBuffer e
bufRaw=RawBuffer Word8
iraw, bufL :: forall e. Buffer e -> Int
bufL=Int
ir0, bufR :: forall e. Buffer e -> Int
bufR=Int
iw,  bufSize :: forall e. Buffer e -> Int
bufSize=Int
_  }
  output :: Buffer Char
output@Buffer{ bufRaw :: forall e. Buffer e -> RawBuffer e
bufRaw=RawBuffer Char
oraw, bufL :: forall e. Buffer e -> Int
bufL=Int
_,   bufR :: forall e. Buffer e -> Int
bufR=Int
ow0, bufSize :: forall e. Buffer e -> Int
bufSize=Int
os }
  State# RealWorld
st
 = let 
       loop :: Int -> Int -> DecodingBuffer#
       loop :: Int -> Int -> DecodingBuffer#
loop !Int
ir !Int
ow State# RealWorld
st0
         | Int
ow Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
os = CodingProgress -> Int -> Int -> DecodingBuffer#
done CodingProgress
OutputUnderflow Int
ir Int
ow State# RealWorld
st0
         | Int
ir Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
iw = CodingProgress -> Int -> Int -> DecodingBuffer#
done CodingProgress
InputUnderflow Int
ir Int
ow State# RealWorld
st0
         | Bool
otherwise = do
              let !(# State# RealWorld
st1, Word8
c0 #) = IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (RawBuffer Word8 -> Int -> IO Word8
readWord8Buf RawBuffer Word8
iraw Int
ir) State# RealWorld
st0
                  !(# State# RealWorld
st2, Int
ow' #) = IO Int -> State# RealWorld -> (# State# RealWorld, Int #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (RawBuffer Char -> Int -> Char -> IO Int
writeCharBuf RawBuffer Char
oraw Int
ow (Int -> Char
unsafeChr (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
c0))) State# RealWorld
st1
              Int -> Int -> DecodingBuffer#
loop (Int
irInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
ow' State# RealWorld
st2
       
       {-# NOINLINE done #-}
       done :: CodingProgress -> Int -> Int -> DecodingBuffer#
       done :: CodingProgress -> Int -> Int -> DecodingBuffer#
done CodingProgress
why !Int
ir !Int
ow State# RealWorld
st' =
         let !ri :: Buffer Word8
ri = if Int
ir Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
iw then Buffer Word8
input{ bufL=0, bufR=0 } else Buffer Word8
input{ bufL=ir }
             !ro :: Buffer Char
ro = Buffer Char
output{ bufR=ow }
         in  (# State# RealWorld
st', CodingProgress
why, Buffer Word8
ri, Buffer Char
ro #)
    in
    Int -> Int -> DecodingBuffer#
loop Int
ir0 Int
ow0 State# RealWorld
st
ascii_decode :: DecodeBuffer#
ascii_decode :: CodeBuffer# Word8 Char
ascii_decode
  input :: Buffer Word8
input@Buffer{  bufRaw :: forall e. Buffer e -> RawBuffer e
bufRaw=RawBuffer Word8
iraw, bufL :: forall e. Buffer e -> Int
bufL=Int
ir0, bufR :: forall e. Buffer e -> Int
bufR=Int
iw,  bufSize :: forall e. Buffer e -> Int
bufSize=Int
_  }
  output :: Buffer Char
output@Buffer{ bufRaw :: forall e. Buffer e -> RawBuffer e
bufRaw=RawBuffer Char
oraw, bufL :: forall e. Buffer e -> Int
bufL=Int
_,   bufR :: forall e. Buffer e -> Int
bufR=Int
ow0, bufSize :: forall e. Buffer e -> Int
bufSize=Int
os }
  State# RealWorld
st
 = let
       loop :: Int -> Int -> DecodingBuffer#
       loop :: Int -> Int -> DecodingBuffer#
loop !Int
ir !Int
ow State# RealWorld
st0
         | Int
ow Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
os = CodingProgress -> Int -> Int -> DecodingBuffer#
done CodingProgress
OutputUnderflow Int
ir Int
ow State# RealWorld
st0
         | Int
ir Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
iw = CodingProgress -> Int -> Int -> DecodingBuffer#
done CodingProgress
InputUnderflow Int
ir Int
ow State# RealWorld
st0
         | Bool
otherwise = do
              let !(# State# RealWorld
st1, Word8
c0 #) = IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (RawBuffer Word8 -> Int -> IO Word8
readWord8Buf RawBuffer Word8
iraw Int
ir) State# RealWorld
st0
              if Word8
c0 Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
> Word8
0x7f then DecodingBuffer#
invalid State# RealWorld
st1 else do
                let !(# State# RealWorld
st2, Int
ow' #) = IO Int -> State# RealWorld -> (# State# RealWorld, Int #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (RawBuffer Char -> Int -> Char -> IO Int
writeCharBuf RawBuffer Char
oraw Int
ow (Int -> Char
unsafeChr (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
c0))) State# RealWorld
st1
                Int -> Int -> DecodingBuffer#
loop (Int
irInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
ow' State# RealWorld
st2
         where
           invalid :: DecodingBuffer#
           invalid :: DecodingBuffer#
invalid State# RealWorld
st' = CodingProgress -> Int -> Int -> DecodingBuffer#
done CodingProgress
InvalidSequence Int
ir Int
ow State# RealWorld
st'
       
       {-# NOINLINE done #-}
       done :: CodingProgress -> Int -> Int -> DecodingBuffer#
       done :: CodingProgress -> Int -> Int -> DecodingBuffer#
done CodingProgress
why !Int
ir !Int
ow State# RealWorld
st' = 
         let !ri :: Buffer Word8
ri = if Int
ir Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
iw then Buffer Word8
input{ bufL=0, bufR=0 } else Buffer Word8
input{ bufL=ir }
             !ro :: Buffer Char
ro = Buffer Char
output{ bufR=ow }
         in  (# State# RealWorld
st', CodingProgress
why, Buffer Word8
ri, Buffer Char
ro #)
    in
    Int -> Int -> DecodingBuffer#
loop Int
ir0 Int
ow0 State# RealWorld
st
latin1_encode :: EncodeBuffer#
latin1_encode :: CodeBuffer# Char Word8
latin1_encode
  input :: Buffer Char
input@Buffer{  bufRaw :: forall e. Buffer e -> RawBuffer e
bufRaw=RawBuffer Char
iraw, bufL :: forall e. Buffer e -> Int
bufL=Int
ir0, bufR :: forall e. Buffer e -> Int
bufR=Int
iw,  bufSize :: forall e. Buffer e -> Int
bufSize=Int
_  }
  output :: Buffer Word8
output@Buffer{ bufRaw :: forall e. Buffer e -> RawBuffer e
bufRaw=RawBuffer Word8
oraw, bufL :: forall e. Buffer e -> Int
bufL=Int
_,   bufR :: forall e. Buffer e -> Int
bufR=Int
ow0, bufSize :: forall e. Buffer e -> Int
bufSize=Int
os }
  State# RealWorld
st
 = let
      {-# NOINLINE done #-}
      done :: CodingProgress -> Int -> Int -> EncodingBuffer#
      done :: CodingProgress -> Int -> Int -> EncodingBuffer#
done CodingProgress
why !Int
ir !Int
ow State# RealWorld
st' = 
        let !ri :: Buffer Char
ri = if Int
ir Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
iw then Buffer Char
input{ bufL=0, bufR=0 } else Buffer Char
input{ bufL=ir }
            !ro :: Buffer Word8
ro = Buffer Word8
output{ bufR=ow }
        in  (# State# RealWorld
st', CodingProgress
why, Buffer Char
ri, Buffer Word8
ro #)
      loop :: Int -> Int -> EncodingBuffer#
      loop :: Int -> Int -> EncodingBuffer#
loop !Int
ir !Int
ow State# RealWorld
st0
        | Int
ow Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
os = CodingProgress -> Int -> Int -> EncodingBuffer#
done CodingProgress
OutputUnderflow Int
ir Int
ow State# RealWorld
st0
        | Int
ir Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
iw = CodingProgress -> Int -> Int -> EncodingBuffer#
done CodingProgress
InputUnderflow Int
ir Int
ow State# RealWorld
st0
        | Bool
otherwise = do
           let !(# State# RealWorld
st1, (Char
c,Int
ir') #) = IO (Char, Int)
-> State# RealWorld -> (# State# RealWorld, (Char, Int) #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (RawBuffer Char -> Int -> IO (Char, Int)
readCharBuf RawBuffer Char
iraw Int
ir) State# RealWorld
st0
               !(# State# RealWorld
st2, () #) = IO () -> State# RealWorld -> (# State# RealWorld, () #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (RawBuffer Word8 -> Int -> Word8 -> IO ()
writeWord8Buf RawBuffer Word8
oraw Int
ow (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
c))) State# RealWorld
st1
           Int -> Int -> EncodingBuffer#
loop Int
ir' (Int
owInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) State# RealWorld
st2
    in
    Int -> Int -> EncodingBuffer#
loop Int
ir0 Int
ow0 State# RealWorld
st
latin1_checked_encode :: EncodeBuffer#
latin1_checked_encode :: CodeBuffer# Char Word8
latin1_checked_encode Buffer Char
input Buffer Word8
output
 = Int -> CodeBuffer# Char Word8
single_byte_checked_encode Int
0xff Buffer Char
input Buffer Word8
output
ascii_encode :: EncodeBuffer#
ascii_encode :: CodeBuffer# Char Word8
ascii_encode Buffer Char
input Buffer Word8
output
 = Int -> CodeBuffer# Char Word8
single_byte_checked_encode Int
0x7f Buffer Char
input Buffer Word8
output
single_byte_checked_encode :: Int -> EncodeBuffer#
single_byte_checked_encode :: Int -> CodeBuffer# Char Word8
single_byte_checked_encode Int
max_legal_char
  input :: Buffer Char
input@Buffer{  bufRaw :: forall e. Buffer e -> RawBuffer e
bufRaw=RawBuffer Char
iraw, bufL :: forall e. Buffer e -> Int
bufL=Int
ir0, bufR :: forall e. Buffer e -> Int
bufR=Int
iw,  bufSize :: forall e. Buffer e -> Int
bufSize=Int
_  }
  output :: Buffer Word8
output@Buffer{ bufRaw :: forall e. Buffer e -> RawBuffer e
bufRaw=RawBuffer Word8
oraw, bufL :: forall e. Buffer e -> Int
bufL=Int
_,   bufR :: forall e. Buffer e -> Int
bufR=Int
ow0, bufSize :: forall e. Buffer e -> Int
bufSize=Int
os }
  State# RealWorld
st
 = let
      {-# NOINLINE done #-}
      done :: CodingProgress -> Int -> Int -> EncodingBuffer#
      done :: CodingProgress -> Int -> Int -> EncodingBuffer#
done CodingProgress
why !Int
ir !Int
ow State# RealWorld
st' = 
        let !ri :: Buffer Char
ri = if Int
ir Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
iw then Buffer Char
input{ bufL=0, bufR=0 } else Buffer Char
input{ bufL=ir }
            !ro :: Buffer Word8
ro = Buffer Word8
output{ bufR=ow }
        in  (# State# RealWorld
st', CodingProgress
why, Buffer Char
ri, Buffer Word8
ro #)
      loop :: Int -> Int -> EncodingBuffer#
      loop :: Int -> Int -> EncodingBuffer#
loop !Int
ir !Int
ow State# RealWorld
st0
        | Int
ow Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
os = CodingProgress -> Int -> Int -> EncodingBuffer#
done CodingProgress
OutputUnderflow Int
ir Int
ow State# RealWorld
st0
        | Int
ir Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
iw = CodingProgress -> Int -> Int -> EncodingBuffer#
done CodingProgress
InputUnderflow Int
ir Int
ow State# RealWorld
st0
        | Bool
otherwise = do
           let !(# State# RealWorld
st1, (Char
c,Int
ir') #) = IO (Char, Int)
-> State# RealWorld -> (# State# RealWorld, (Char, Int) #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (RawBuffer Char -> Int -> IO (Char, Int)
readCharBuf RawBuffer Char
iraw Int
ir) State# RealWorld
st0
           if Char -> Int
ord Char
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
max_legal_char then EncodingBuffer#
invalid State# RealWorld
st1 else do
             let !(# State# RealWorld
st2, () #) = IO () -> State# RealWorld -> (# State# RealWorld, () #)
forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)
unIO (RawBuffer Word8 -> Int -> Word8 -> IO ()
writeWord8Buf RawBuffer Word8
oraw Int
ow (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
c))) State# RealWorld
st1
             Int -> Int -> EncodingBuffer#
loop Int
ir' (Int
owInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) State# RealWorld
st2
        where
          invalid :: EncodingBuffer#
          invalid :: EncodingBuffer#
invalid State# RealWorld
st' = CodingProgress -> Int -> Int -> EncodingBuffer#
done CodingProgress
InvalidSequence Int
ir Int
ow State# RealWorld
st'
    in
    Int -> Int -> EncodingBuffer#
loop Int
ir0 Int
ow0 State# RealWorld
st
{-# INLINE single_byte_checked_encode #-}