Movatterモバイル変換
[0]ホーム
{-# LANGUAGE Trustworthy #-}{-# LANGUAGE NoImplicitPrelude , BangPatterns , NondecreasingIndentation , UnboxedTuples , MagicHash #-}{-# OPTIONS_GHC -funbox-strict-fields #-}------------------------------------------------------------------------------- |-- Module : GHC.IO.Encoding.Latin1-- Copyright : (c) The University of Glasgow, 2009-- License : see libraries/base/LICENSE---- Maintainer : libraries@haskell.org-- Stability : internal-- Portability : non-portable---- Single-byte encodings that map directly to Unicode code points.---- Portions Copyright : (c) Tom Harper 2008-2009,-- (c) Bryan O'Sullivan 2009,-- (c) Duncan Coutts 2009-------------------------------------------------------------------------------moduleGHC.IO.Encoding.Latin1(latin1,mkLatin1,latin1_checked,mkLatin1_checked,ascii,mkAscii,latin1_decode,ascii_decode,latin1_encode,latin1_checked_encode,ascii_encode,)whereimportGHC.BaseimportGHC.RealimportGHC.Num-- import GHC.IOimportGHC.IO.BufferimportGHC.IO.Encoding.FailureimportGHC.IO.Encoding.Types-- ------------------------------------------------------------------------------- Latin1latin1::TextEncodinglatin1 :: TextEncodinglatin1=CodingFailureMode -> TextEncodingmkLatin1CodingFailureModeErrorOnCodingFailure-- | @since 4.4.0.0mkLatin1::CodingFailureMode->TextEncodingmkLatin1 :: CodingFailureMode -> TextEncodingmkLatin1CodingFailureModecfm=TextEncoding{textEncodingName :: StringtextEncodingName=String"ISO-8859-1",mkTextDecoder :: IO (TextDecoder ())mkTextDecoder=CodingFailureMode -> IO (TextDecoder ())latin1_DFCodingFailureModecfm,mkTextEncoder :: IO (TextEncoder ())mkTextEncoder=CodingFailureMode -> IO (TextEncoder ())latin1_EFCodingFailureModecfm}latin1_DF::CodingFailureMode->IO(TextDecoder())latin1_DF :: CodingFailureMode -> IO (TextDecoder ())latin1_DFCodingFailureModecfm=TextDecoder () -> IO (TextDecoder ())forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(BufferCodec#{encode# :: CodeBuffer# Word8 Charencode#=CodeBuffer# Word8 Charlatin1_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#CodingFailureModecfm,close# :: IO ()close#=() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(),getState# :: IO ()getState#=() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(),setState# :: () -> IO ()setState#=IO () -> () -> IO ()forall a b. a -> b -> aconst(IO () -> () -> IO ()) -> IO () -> () -> IO ()forall a b. (a -> b) -> a -> b$() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn()})latin1_EF::CodingFailureMode->IO(TextEncoder())latin1_EF :: CodingFailureMode -> IO (TextEncoder ())latin1_EFCodingFailureModecfm=TextEncoder () -> IO (TextEncoder ())forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(BufferCodec#{encode# :: CodeBuffer# Char Word8encode#=CodeBuffer# Char Word8latin1_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#CodingFailureModecfm,close# :: IO ()close#=() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(),getState# :: IO ()getState#=() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(),setState# :: () -> IO ()setState#=IO () -> () -> IO ()forall a b. a -> b -> aconst(IO () -> () -> IO ()) -> IO () -> () -> IO ()forall a b. (a -> b) -> a -> b$() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn()})latin1_checked::TextEncodinglatin1_checked :: TextEncodinglatin1_checked=CodingFailureMode -> TextEncodingmkLatin1_checkedCodingFailureModeErrorOnCodingFailure-- | @since 4.4.0.0mkLatin1_checked::CodingFailureMode->TextEncodingmkLatin1_checked :: CodingFailureMode -> TextEncodingmkLatin1_checkedCodingFailureModecfm=TextEncoding{textEncodingName :: StringtextEncodingName=String"ISO-8859-1",mkTextDecoder :: IO (TextDecoder ())mkTextDecoder=CodingFailureMode -> IO (TextDecoder ())latin1_DFCodingFailureModecfm,mkTextEncoder :: IO (TextEncoder ())mkTextEncoder=CodingFailureMode -> IO (TextEncoder ())latin1_checked_EFCodingFailureModecfm}latin1_checked_EF::CodingFailureMode->IO(TextEncoder())latin1_checked_EF :: CodingFailureMode -> IO (TextEncoder ())latin1_checked_EFCodingFailureModecfm=TextEncoder () -> IO (TextEncoder ())forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(BufferCodec#{encode# :: CodeBuffer# Char Word8encode#=CodeBuffer# Char Word8latin1_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#CodingFailureModecfm,close# :: IO ()close#=() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(),getState# :: IO ()getState#=() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(),setState# :: () -> IO ()setState#=IO () -> () -> IO ()forall a b. a -> b -> aconst(IO () -> () -> IO ()) -> IO () -> () -> IO ()forall a b. (a -> b) -> a -> b$() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn()})-- ------------------------------------------------------------------------------- ASCII-- | @since 4.9.0.0ascii::TextEncodingascii :: TextEncodingascii=CodingFailureMode -> TextEncodingmkAsciiCodingFailureModeErrorOnCodingFailure-- | @since 4.9.0.0mkAscii::CodingFailureMode->TextEncodingmkAscii :: CodingFailureMode -> TextEncodingmkAsciiCodingFailureModecfm=TextEncoding{textEncodingName :: StringtextEncodingName=String"ASCII",mkTextDecoder :: IO (TextDecoder ())mkTextDecoder=CodingFailureMode -> IO (TextDecoder ())ascii_DFCodingFailureModecfm,mkTextEncoder :: IO (TextEncoder ())mkTextEncoder=CodingFailureMode -> IO (TextEncoder ())ascii_EFCodingFailureModecfm}ascii_DF::CodingFailureMode->IO(TextDecoder())ascii_DF :: CodingFailureMode -> IO (TextDecoder ())ascii_DFCodingFailureModecfm=TextDecoder () -> IO (TextDecoder ())forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(BufferCodec#{encode# :: CodeBuffer# Word8 Charencode#=CodeBuffer# Word8 Charascii_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#CodingFailureModecfm,close# :: IO ()close#=() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(),getState# :: IO ()getState#=() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(),setState# :: () -> IO ()setState#=IO () -> () -> IO ()forall a b. a -> b -> aconst(IO () -> () -> IO ()) -> IO () -> () -> IO ()forall a b. (a -> b) -> a -> b$() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn()})ascii_EF::CodingFailureMode->IO(TextEncoder())ascii_EF :: CodingFailureMode -> IO (TextEncoder ())ascii_EFCodingFailureModecfm=TextEncoder () -> IO (TextEncoder ())forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(BufferCodec#{encode# :: CodeBuffer# Char Word8encode#=CodeBuffer# Char Word8ascii_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#CodingFailureModecfm,close# :: IO ()close#=() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(),getState# :: IO ()getState#=() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(),setState# :: () -> IO ()setState#=IO () -> () -> IO ()forall a b. a -> b -> aconst(IO () -> () -> IO ()) -> IO () -> () -> IO ()forall a b. (a -> b) -> a -> b$() -> IO ()forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn()})-- ------------------------------------------------------------------------------- The actual decoders and encoders-- TODO: Eliminate code duplication between the checked and unchecked-- versions of the decoder or encoder (but don't change the Core!)latin1_decode::DecodeBuffer#latin1_decode :: CodeBuffer# Word8 Charlatin1_decodeinput :: Buffer Word8input@Buffer{bufRaw :: forall e. Buffer e -> RawBuffer ebufRaw=RawBuffer Word8iraw,bufL :: forall e. Buffer e -> IntbufL=Intir0,bufR :: forall e. Buffer e -> IntbufR=Intiw,bufSize :: forall e. Buffer e -> IntbufSize=Int_}output :: Buffer Charoutput@Buffer{bufRaw :: forall e. Buffer e -> RawBuffer ebufRaw=RawBuffer Charoraw,bufL :: forall e. Buffer e -> IntbufL=Int_,bufR :: forall e. Buffer e -> IntbufR=Intow0,bufSize :: forall e. Buffer e -> IntbufSize=Intos}State# RealWorldst=letloop::Int->Int->DecodingBuffer#loop :: Int -> Int -> DecodingBuffer#loop!Intir!IntowState# RealWorldst0|IntowInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Intos=CodingProgress -> Int -> Int -> DecodingBuffer#doneCodingProgressOutputUnderflowIntirIntowState# RealWorldst0|IntirInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Intiw=CodingProgress -> Int -> Int -> DecodingBuffer#doneCodingProgressInputUnderflowIntirIntowState# RealWorldst0|Boolotherwise=dolet!(#State# RealWorldst1,Word8c0#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8irawIntir)State# RealWorldst0!(#State# RealWorldst2,Intow'#)=IO Int -> State# RealWorld -> (# State# RealWorld, Int #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Char -> Int -> Char -> IO IntwriteCharBufRawBuffer CharorawIntow(Int -> CharunsafeChr(Word8 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralWord8c0)))State# RealWorldst1Int -> Int -> DecodingBuffer#loop(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int1)Intow'State# RealWorldst2-- lambda-lifted, to avoid thunks being built in the inner-loop:{-# NOINLINEdone#-}done::CodingProgress->Int->Int->DecodingBuffer#done :: CodingProgress -> Int -> Int -> DecodingBuffer#doneCodingProgresswhy!Intir!IntowState# RealWorldst'=let!ri :: Buffer Word8ri=ifIntirInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==IntiwthenBuffer Word8input{bufL=0,bufR=0}elseBuffer Word8input{bufL=ir}!ro :: Buffer Charro=Buffer Charoutput{bufR=ow}in(#State# RealWorldst',CodingProgresswhy,Buffer Word8ri,Buffer Charro#)inInt -> Int -> DecodingBuffer#loopIntir0Intow0State# RealWorldstascii_decode::DecodeBuffer#ascii_decode :: CodeBuffer# Word8 Charascii_decodeinput :: Buffer Word8input@Buffer{bufRaw :: forall e. Buffer e -> RawBuffer ebufRaw=RawBuffer Word8iraw,bufL :: forall e. Buffer e -> IntbufL=Intir0,bufR :: forall e. Buffer e -> IntbufR=Intiw,bufSize :: forall e. Buffer e -> IntbufSize=Int_}output :: Buffer Charoutput@Buffer{bufRaw :: forall e. Buffer e -> RawBuffer ebufRaw=RawBuffer Charoraw,bufL :: forall e. Buffer e -> IntbufL=Int_,bufR :: forall e. Buffer e -> IntbufR=Intow0,bufSize :: forall e. Buffer e -> IntbufSize=Intos}State# RealWorldst=letloop::Int->Int->DecodingBuffer#loop :: Int -> Int -> DecodingBuffer#loop!Intir!IntowState# RealWorldst0|IntowInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Intos=CodingProgress -> Int -> Int -> DecodingBuffer#doneCodingProgressOutputUnderflowIntirIntowState# RealWorldst0|IntirInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Intiw=CodingProgress -> Int -> Int -> DecodingBuffer#doneCodingProgressInputUnderflowIntirIntowState# RealWorldst0|Boolotherwise=dolet!(#State# RealWorldst1,Word8c0#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8irawIntir)State# RealWorldst0ifWord8c0Word8 -> Word8 -> Boolforall a. Ord a => a -> a -> Bool>Word80x7fthenDecodingBuffer#invalidState# RealWorldst1elsedolet!(#State# RealWorldst2,Intow'#)=IO Int -> State# RealWorld -> (# State# RealWorld, Int #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Char -> Int -> Char -> IO IntwriteCharBufRawBuffer CharorawIntow(Int -> CharunsafeChr(Word8 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralWord8c0)))State# RealWorldst1Int -> Int -> DecodingBuffer#loop(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int1)Intow'State# RealWorldst2whereinvalid::DecodingBuffer#invalid :: DecodingBuffer#invalidState# RealWorldst'=CodingProgress -> Int -> Int -> DecodingBuffer#doneCodingProgressInvalidSequenceIntirIntowState# RealWorldst'-- lambda-lifted, to avoid thunks being built in the inner-loop:{-# NOINLINEdone#-}done::CodingProgress->Int->Int->DecodingBuffer#done :: CodingProgress -> Int -> Int -> DecodingBuffer#doneCodingProgresswhy!Intir!IntowState# RealWorldst'=let!ri :: Buffer Word8ri=ifIntirInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==IntiwthenBuffer Word8input{bufL=0,bufR=0}elseBuffer Word8input{bufL=ir}!ro :: Buffer Charro=Buffer Charoutput{bufR=ow}in(#State# RealWorldst',CodingProgresswhy,Buffer Word8ri,Buffer Charro#)inInt -> Int -> DecodingBuffer#loopIntir0Intow0State# RealWorldstlatin1_encode::EncodeBuffer#latin1_encode :: CodeBuffer# Char Word8latin1_encodeinput :: Buffer Charinput@Buffer{bufRaw :: forall e. Buffer e -> RawBuffer ebufRaw=RawBuffer Chariraw,bufL :: forall e. Buffer e -> IntbufL=Intir0,bufR :: forall e. Buffer e -> IntbufR=Intiw,bufSize :: forall e. Buffer e -> IntbufSize=Int_}output :: Buffer Word8output@Buffer{bufRaw :: forall e. Buffer e -> RawBuffer ebufRaw=RawBuffer Word8oraw,bufL :: forall e. Buffer e -> IntbufL=Int_,bufR :: forall e. Buffer e -> IntbufR=Intow0,bufSize :: forall e. Buffer e -> IntbufSize=Intos}State# RealWorldst=let{-# NOINLINEdone#-}done::CodingProgress->Int->Int->EncodingBuffer#done :: CodingProgress -> Int -> Int -> EncodingBuffer#doneCodingProgresswhy!Intir!IntowState# RealWorldst'=let!ri :: Buffer Charri=ifIntirInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==IntiwthenBuffer Charinput{bufL=0,bufR=0}elseBuffer Charinput{bufL=ir}!ro :: Buffer Word8ro=Buffer Word8output{bufR=ow}in(#State# RealWorldst',CodingProgresswhy,Buffer Charri,Buffer Word8ro#)loop::Int->Int->EncodingBuffer#loop :: Int -> Int -> EncodingBuffer#loop!Intir!IntowState# RealWorldst0|IntowInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Intos=CodingProgress -> Int -> Int -> EncodingBuffer#doneCodingProgressOutputUnderflowIntirIntowState# RealWorldst0|IntirInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Intiw=CodingProgress -> Int -> Int -> EncodingBuffer#doneCodingProgressInputUnderflowIntirIntowState# RealWorldst0|Boolotherwise=dolet!(#State# RealWorldst1,(Charc,Intir')#)=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)readCharBufRawBuffer CharirawIntir)State# RealWorldst0!(#State# RealWorldst2,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8orawIntow(Int -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegral(Char -> IntordCharc)))State# RealWorldst1Int -> Int -> EncodingBuffer#loopIntir'(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int1)State# RealWorldst2inInt -> Int -> EncodingBuffer#loopIntir0Intow0State# RealWorldstlatin1_checked_encode::EncodeBuffer#latin1_checked_encode :: CodeBuffer# Char Word8latin1_checked_encodeBuffer CharinputBuffer Word8output=Int -> CodeBuffer# Char Word8single_byte_checked_encodeInt0xffBuffer CharinputBuffer Word8outputascii_encode::EncodeBuffer#ascii_encode :: CodeBuffer# Char Word8ascii_encodeBuffer CharinputBuffer Word8output=Int -> CodeBuffer# Char Word8single_byte_checked_encodeInt0x7fBuffer CharinputBuffer Word8outputsingle_byte_checked_encode::Int->EncodeBuffer#single_byte_checked_encode :: Int -> CodeBuffer# Char Word8single_byte_checked_encodeIntmax_legal_charinput :: Buffer Charinput@Buffer{bufRaw :: forall e. Buffer e -> RawBuffer ebufRaw=RawBuffer Chariraw,bufL :: forall e. Buffer e -> IntbufL=Intir0,bufR :: forall e. Buffer e -> IntbufR=Intiw,bufSize :: forall e. Buffer e -> IntbufSize=Int_}output :: Buffer Word8output@Buffer{bufRaw :: forall e. Buffer e -> RawBuffer ebufRaw=RawBuffer Word8oraw,bufL :: forall e. Buffer e -> IntbufL=Int_,bufR :: forall e. Buffer e -> IntbufR=Intow0,bufSize :: forall e. Buffer e -> IntbufSize=Intos}State# RealWorldst=let{-# NOINLINEdone#-}done::CodingProgress->Int->Int->EncodingBuffer#done :: CodingProgress -> Int -> Int -> EncodingBuffer#doneCodingProgresswhy!Intir!IntowState# RealWorldst'=let!ri :: Buffer Charri=ifIntirInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==IntiwthenBuffer Charinput{bufL=0,bufR=0}elseBuffer Charinput{bufL=ir}!ro :: Buffer Word8ro=Buffer Word8output{bufR=ow}in(#State# RealWorldst',CodingProgresswhy,Buffer Charri,Buffer Word8ro#)loop::Int->Int->EncodingBuffer#loop :: Int -> Int -> EncodingBuffer#loop!Intir!IntowState# RealWorldst0|IntowInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Intos=CodingProgress -> Int -> Int -> EncodingBuffer#doneCodingProgressOutputUnderflowIntirIntowState# RealWorldst0|IntirInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Intiw=CodingProgress -> Int -> Int -> EncodingBuffer#doneCodingProgressInputUnderflowIntirIntowState# RealWorldst0|Boolotherwise=dolet!(#State# RealWorldst1,(Charc,Intir')#)=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)readCharBufRawBuffer CharirawIntir)State# RealWorldst0ifChar -> IntordCharcInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>Intmax_legal_charthenEncodingBuffer#invalidState# RealWorldst1elsedolet!(#State# RealWorldst2,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8orawIntow(Int -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegral(Char -> IntordCharc)))State# RealWorldst1Int -> Int -> EncodingBuffer#loopIntir'(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int1)State# RealWorldst2whereinvalid::EncodingBuffer#invalid :: EncodingBuffer#invalidState# RealWorldst'=CodingProgress -> Int -> Int -> EncodingBuffer#doneCodingProgressInvalidSequenceIntirIntowState# RealWorldst'inInt -> Int -> EncodingBuffer#loopIntir0Intow0State# RealWorldst{-# INLINEsingle_byte_checked_encode#-}
[8]ページ先頭