Movatterモバイル変換
[0]ホーム
{-# LANGUAGE Trustworthy #-}{-# LANGUAGE NoImplicitPrelude , BangPatterns , NondecreasingIndentation , MagicHash , UnboxedTuples #-}{-# OPTIONS_GHC -funbox-strict-fields #-}------------------------------------------------------------------------------- |-- Module : GHC.IO.Encoding.UTF8-- Copyright : (c) The University of Glasgow, 2009-- License : see libraries/base/LICENSE---- Maintainer : libraries@haskell.org-- Stability : internal-- Portability : non-portable---- UTF-8 Codec for the IO library---- This is one of several UTF-8 implementations provided by GHC; see Note-- [GHC's many UTF-8 implementations] in "GHC.Encoding.UTF8" for an-- overview.---- Portions Copyright : (c) Tom Harper 2008-2009,-- (c) Bryan O'Sullivan 2009,-- (c) Duncan Coutts 2009-------------------------------------------------------------------------------moduleGHC.IO.Encoding.UTF8(utf8,mkUTF8,utf8_bom,mkUTF8_bom)whereimportGHC.BaseimportGHC.RealimportGHC.NumimportGHC.IORef-- import GHC.IOimportGHC.IO.BufferimportGHC.IO.Encoding.FailureimportGHC.IO.Encoding.TypesimportGHC.WordimportData.Bitsutf8::TextEncodingutf8 :: TextEncodingutf8=CodingFailureMode -> TextEncodingmkUTF8CodingFailureModeErrorOnCodingFailure-- | @since 4.4.0.0mkUTF8::CodingFailureMode->TextEncodingmkUTF8 :: CodingFailureMode -> TextEncodingmkUTF8CodingFailureModecfm=TextEncoding{textEncodingName :: StringtextEncodingName=String"UTF-8",mkTextDecoder :: IO (TextDecoder ())mkTextDecoder=CodingFailureMode -> IO (TextDecoder ())utf8_DFCodingFailureModecfm,mkTextEncoder :: IO (TextEncoder ())mkTextEncoder=CodingFailureMode -> IO (TextEncoder ())utf8_EFCodingFailureModecfm}utf8_DF::CodingFailureMode->IO(TextDecoder())utf8_DF :: CodingFailureMode -> IO (TextDecoder ())utf8_DFCodingFailureModecfm=TextDecoder () -> IO (TextDecoder ())forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(BufferCodec#{encode# :: CodeBuffer# Word8 Charencode#=CodeBuffer# Word8 Charutf8_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()})utf8_EF::CodingFailureMode->IO(TextEncoder())utf8_EF :: CodingFailureMode -> IO (TextEncoder ())utf8_EFCodingFailureModecfm=TextEncoder () -> IO (TextEncoder ())forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(BufferCodec#{encode# :: CodeBuffer# Char Word8encode#=CodeBuffer# Char Word8utf8_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()})utf8_bom::TextEncodingutf8_bom :: TextEncodingutf8_bom=CodingFailureMode -> TextEncodingmkUTF8_bomCodingFailureModeErrorOnCodingFailuremkUTF8_bom::CodingFailureMode->TextEncodingmkUTF8_bom :: CodingFailureMode -> TextEncodingmkUTF8_bomCodingFailureModecfm=TextEncoding{textEncodingName :: StringtextEncodingName=String"UTF-8BOM",mkTextDecoder :: IO (TextDecoder Bool)mkTextDecoder=CodingFailureMode -> IO (TextDecoder Bool)utf8_bom_DFCodingFailureModecfm,mkTextEncoder :: IO (TextEncoder Bool)mkTextEncoder=CodingFailureMode -> IO (TextEncoder Bool)utf8_bom_EFCodingFailureModecfm}utf8_bom_DF::CodingFailureMode->IO(TextDecoderBool)utf8_bom_DF :: CodingFailureMode -> IO (TextDecoder Bool)utf8_bom_DFCodingFailureModecfm=doIORef Boolref<-Bool -> IO (IORef Bool)forall a. a -> IO (IORef a)newIORefBoolTrueTextDecoder Bool -> IO (TextDecoder Bool)forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(BufferCodec#{encode# :: CodeBuffer# Word8 Charencode#=IORef Bool -> CodeBuffer# Word8 Charutf8_bom_decodeIORef Boolref,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 BoolgetState#=IORef Bool -> IO Boolforall a. IORef a -> IO areadIORefIORef Boolref,setState# :: Bool -> IO ()setState#=IORef Bool -> Bool -> IO ()forall a. IORef a -> a -> IO ()writeIORefIORef Boolref})utf8_bom_EF::CodingFailureMode->IO(TextEncoderBool)utf8_bom_EF :: CodingFailureMode -> IO (TextEncoder Bool)utf8_bom_EFCodingFailureModecfm=doIORef Boolref<-Bool -> IO (IORef Bool)forall a. a -> IO (IORef a)newIORefBoolTrueTextEncoder Bool -> IO (TextEncoder Bool)forall a. a -> IO aforall (m :: * -> *) a. Monad m => a -> m areturn(BufferCodec#{encode# :: CodeBuffer# Char Word8encode#=IORef Bool -> CodeBuffer# Char Word8utf8_bom_encodeIORef Boolref,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 BoolgetState#=IORef Bool -> IO Boolforall a. IORef a -> IO areadIORefIORef Boolref,setState# :: Bool -> IO ()setState#=IORef Bool -> Bool -> IO ()forall a. IORef a -> a -> IO ()writeIORefIORef Boolref})utf8_bom_decode::IORefBool->DecodeBuffer#utf8_bom_decode :: IORef Bool -> CodeBuffer# Word8 Charutf8_bom_decodeIORef Boolrefinput :: Buffer Word8input@Buffer{bufRaw :: forall e. Buffer e -> RawBuffer ebufRaw=RawBuffer Word8iraw,bufL :: forall e. Buffer e -> IntbufL=Intir,bufR :: forall e. Buffer e -> IntbufR=Intiw,bufSize :: forall e. Buffer e -> IntbufSize=Int_}Buffer CharoutputState# RealWorldst0=dolet!(#State# RealWorldst1,Boolfirst#)=IO Bool -> State# RealWorld -> (# State# RealWorld, Bool #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(IORef Bool -> IO Boolforall a. IORef a -> IO areadIORefIORef Boolref)State# RealWorldst0ifBool -> BoolnotBoolfirstthenCodeBuffer# Word8 Charutf8_decodeBuffer Word8inputBuffer CharoutputState# RealWorldst1elsedoletno_bom :: (# State# RealWorld, CodingProgress, Buffer Word8, Buffer Char #)no_bom=let!(#State# RealWorldst',()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(IORef Bool -> Bool -> IO ()forall a. IORef a -> a -> IO ()writeIORefIORef BoolrefBoolFalse)State# RealWorldst1inCodeBuffer# Word8 Charutf8_decodeBuffer Word8inputBuffer CharoutputState# RealWorldst'ifIntiwInt -> Int -> Intforall a. Num a => a -> a -> a-IntirInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<Int1then(#State# RealWorldst1,CodingProgressInputUnderflow,Buffer Word8input,Buffer Charoutput#)elsedolet!(#State# RealWorldst2,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# RealWorldst1if(Word8c0Word8 -> Word8 -> Boolforall a. Eq a => a -> a -> Bool/=Word8bom0)then(# State# RealWorld, CodingProgress, Buffer Word8, Buffer Char #)no_bomelsedoifIntiwInt -> Int -> Intforall a. Num a => a -> a -> a-IntirInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<Int2then(#State# RealWorldst2,CodingProgressInputUnderflow,Buffer Word8input,Buffer Charoutput#)elsedolet!(#State# RealWorldst3,Word8c1#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8iraw(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int1))State# RealWorldst2if(Word8c1Word8 -> Word8 -> Boolforall a. Eq a => a -> a -> Bool/=Word8bom1)then(# State# RealWorld, CodingProgress, Buffer Word8, Buffer Char #)no_bomelsedoifIntiwInt -> Int -> Intforall a. Num a => a -> a -> a-IntirInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<Int3then(#State# RealWorldst3,CodingProgressInputUnderflow,Buffer Word8input,Buffer Charoutput#)elsedolet!(#State# RealWorldst4,Word8c2#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8iraw(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int2))State# RealWorldst3if(Word8c2Word8 -> Word8 -> Boolforall a. Eq a => a -> a -> Bool/=Word8bom2)then(# State# RealWorld, CodingProgress, Buffer Word8, Buffer Char #)no_bomelsedo-- found a BOM, ignore it and carry onlet!(#State# RealWorldst5,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(IORef Bool -> Bool -> IO ()forall a. IORef a -> a -> IO ()writeIORefIORef BoolrefBoolFalse)State# RealWorldst4CodeBuffer# Word8 Charutf8_decodeBuffer Word8input{bufL=ir+3}Buffer CharoutputState# RealWorldst5utf8_bom_encode::IORefBool->EncodeBuffer#utf8_bom_encode :: IORef Bool -> CodeBuffer# Char Word8utf8_bom_encodeIORef BoolrefBuffer Charinputoutput :: 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=Intow,bufSize :: forall e. Buffer e -> IntbufSize=Intos}State# RealWorldst0=dolet!(#State# RealWorldst1,Boolb#)=IO Bool -> State# RealWorld -> (# State# RealWorld, Bool #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(IORef Bool -> IO Boolforall a. IORef a -> IO areadIORefIORef Boolref)State# RealWorldst0ifBool -> BoolnotBoolbthenCodeBuffer# Char Word8utf8_encodeBuffer CharinputBuffer Word8outputState# RealWorldst1elseifIntosInt -> Int -> Intforall a. Num a => a -> a -> a-IntowInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<Int3then(#State# RealWorldst1,CodingProgressOutputUnderflow,Buffer Charinput,Buffer Word8output#)elsedolet!(#State# RealWorldst2,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(IORef Bool -> Bool -> IO ()forall a. IORef a -> a -> IO ()writeIORefIORef BoolrefBoolFalse)State# RealWorldst1!(#State# RealWorldst3,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8orawIntowWord8bom0)State# RealWorldst2!(#State# RealWorldst4,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8oraw(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int1)Word8bom1)State# RealWorldst3!(#State# RealWorldst5,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8oraw(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int2)Word8bom2)State# RealWorldst4CodeBuffer# Char Word8utf8_encodeBuffer CharinputBuffer Word8output{bufR=ow+3}State# RealWorldst5bom0,bom1,bom2::Word8bom0 :: Word8bom0=Word80xefbom1 :: Word8bom1=Word80xbbbom2 :: Word8bom2=Word80xbfutf8_decode::DecodeBuffer#utf8_decode :: CodeBuffer# Word8 Charutf8_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# RealWorldst0caseWord8c0ofWord8_|Word8c0Word8 -> Word8 -> Boolforall a. Ord a => a -> a -> Bool<=Word80x7f->dolet!(#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|Word8c0Word8 -> Word8 -> Boolforall a. Ord a => a -> a -> Bool>=Word80xc0Bool -> Bool -> Bool&&Word8c0Word8 -> Word8 -> Boolforall a. Ord a => a -> a -> Bool<=Word80xc1->DecodingBuffer#invalidState# RealWorldst1-- Overlong forms|Word8c0Word8 -> Word8 -> Boolforall a. Ord a => a -> a -> Bool>=Word80xc2Bool -> Bool -> Bool&&Word8c0Word8 -> Word8 -> Boolforall a. Ord a => a -> a -> Bool<=Word80xdf->ifIntiwInt -> Int -> Intforall a. Num a => a -> a -> a-IntirInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<Int2thenCodingProgress -> Int -> Int -> DecodingBuffer#doneCodingProgressInputUnderflowIntirIntowState# RealWorldst1elsedolet!(#State# RealWorldst2,Word8c1#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8iraw(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int1))State# RealWorldst1if(Word8c1Word8 -> Word8 -> Boolforall a. Ord a => a -> a -> Bool<Word80x80Bool -> Bool -> Bool||Word8c1Word8 -> Word8 -> Boolforall a. Ord a => a -> a -> Bool>=Word80xc0)thenDecodingBuffer#invalidState# RealWorldst2elsedolet!(#State# RealWorldst3,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(Word8 -> Word8 -> Charchr2Word8c0Word8c1))State# RealWorldst2Int -> Int -> DecodingBuffer#loop(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int2)Intow'State# RealWorldst3|Word8c0Word8 -> Word8 -> Boolforall a. Ord a => a -> a -> Bool>=Word80xe0Bool -> Bool -> Bool&&Word8c0Word8 -> Word8 -> Boolforall a. Ord a => a -> a -> Bool<=Word80xef->caseIntiwInt -> Int -> Intforall a. Num a => a -> a -> a-IntirofInt1->CodingProgress -> Int -> Int -> DecodingBuffer#doneCodingProgressInputUnderflowIntirIntowState# RealWorldst1Int2->do-- check for an error even when we don't have-- the full sequence yet (#3341)let!(#State# RealWorldst2,Word8c1#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8iraw(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int1))State# RealWorldst1ifBool -> Boolnot(Word8 -> Word8 -> Word8 -> Boolvalidate3Word8c0Word8c1Word80x80)thenDecodingBuffer#invalidState# RealWorldst2elseCodingProgress -> Int -> Int -> DecodingBuffer#doneCodingProgressInputUnderflowIntirIntowState# RealWorldst2Int_->dolet!(#State# RealWorldst2,Word8c1#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8iraw(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int1))State# RealWorldst1let!(#State# RealWorldst3,Word8c2#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8iraw(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int2))State# RealWorldst2ifBool -> Boolnot(Word8 -> Word8 -> Word8 -> Boolvalidate3Word8c0Word8c1Word8c2)thenDecodingBuffer#invalidState# RealWorldst3elsedolet!(#State# RealWorldst4,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(Word8 -> Word8 -> Word8 -> Charchr3Word8c0Word8c1Word8c2))State# RealWorldst3Int -> Int -> DecodingBuffer#loop(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int3)Intow'State# RealWorldst4|Word8c0Word8 -> Word8 -> Boolforall a. Ord a => a -> a -> Bool>=Word80xf0->caseIntiwInt -> Int -> Intforall a. Num a => a -> a -> a-IntirofInt1->CodingProgress -> Int -> Int -> DecodingBuffer#doneCodingProgressInputUnderflowIntirIntowState# RealWorldst1Int2->do-- check for an error even when we don't have-- the full sequence yet (#3341)let!(#State# RealWorldst2,Word8c1#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8iraw(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int1))State# RealWorldst1ifBool -> Boolnot(Word8 -> Word8 -> Word8 -> Word8 -> Boolvalidate4Word8c0Word8c1Word80x80Word80x80)thenDecodingBuffer#invalidState# RealWorldst2elseCodingProgress -> Int -> Int -> DecodingBuffer#doneCodingProgressInputUnderflowIntirIntowState# RealWorldst2Int3->dolet!(#State# RealWorldst2,Word8c1#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8iraw(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int1))State# RealWorldst1!(#State# RealWorldst3,Word8c2#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8iraw(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int2))State# RealWorldst2ifBool -> Boolnot(Word8 -> Word8 -> Word8 -> Word8 -> Boolvalidate4Word8c0Word8c1Word8c2Word80x80)thenDecodingBuffer#invalidState# RealWorldst3elseCodingProgress -> Int -> Int -> DecodingBuffer#doneCodingProgressInputUnderflowIntirIntowState# RealWorldst3Int_->dolet!(#State# RealWorldst2,Word8c1#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8iraw(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int1))State# RealWorldst1!(#State# RealWorldst3,Word8c2#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8iraw(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int2))State# RealWorldst2!(#State# RealWorldst4,Word8c3#)=IO Word8 -> State# RealWorld -> (# State# RealWorld, Word8 #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> IO Word8readWord8BufRawBuffer Word8iraw(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int3))State# RealWorldst3ifBool -> Boolnot(Word8 -> Word8 -> Word8 -> Word8 -> Boolvalidate4Word8c0Word8c1Word8c2Word8c3)thenDecodingBuffer#invalidState# RealWorldst4elsedolet!(#State# RealWorldst5,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(Word8 -> Word8 -> Word8 -> Word8 -> Charchr4Word8c0Word8c1Word8c2Word8c3))State# RealWorldst4Int -> Int -> DecodingBuffer#loop(IntirInt -> Int -> Intforall a. Num a => a -> a -> a+Int4)Intow'State# RealWorldst5|Boolotherwise->DecodingBuffer#invalidState# RealWorldst1whereinvalid::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# RealWorldstutf8_encode::EncodeBuffer#utf8_encode :: CodeBuffer# Char Word8utf8_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# RealWorldst0caseChar -> IntordCharcofIntx|IntxInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<=Int0x7F->dolet!(#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 -> bfromIntegralIntx))State# RealWorldst1Int -> Int -> EncodingBuffer#loopIntir'(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int1)State# RealWorldst2|IntxInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<=Int0x07FF->ifIntosInt -> Int -> Intforall a. Num a => a -> a -> a-IntowInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<Int2thenCodingProgress -> Int -> Int -> EncodingBuffer#doneCodingProgressOutputUnderflowIntirIntowState# RealWorldst1elsedolet(Word8c1,Word8c2)=Char -> (Word8, Word8)ord2Charc!(#State# RealWorldst2,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8orawIntowWord8c1)State# RealWorldst1!(#State# RealWorldst3,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8oraw(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int1)Word8c2)State# RealWorldst2Int -> Int -> EncodingBuffer#loopIntir'(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int2)State# RealWorldst3|IntxInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<=Int0xFFFF->ifChar -> BoolisSurrogateCharcthenCodingProgress -> Int -> Int -> EncodingBuffer#doneCodingProgressInvalidSequenceIntirIntowState# RealWorldst1elsedoifIntosInt -> Int -> Intforall a. Num a => a -> a -> a-IntowInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<Int3thenCodingProgress -> Int -> Int -> EncodingBuffer#doneCodingProgressOutputUnderflowIntirIntowState# RealWorldst1elsedolet(Word8c1,Word8c2,Word8c3)=Char -> (Word8, Word8, Word8)ord3Charc!(#State# RealWorldst2,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8orawIntowWord8c1)State# RealWorldst1!(#State# RealWorldst3,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8oraw(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int1)Word8c2)State# RealWorldst2!(#State# RealWorldst4,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8oraw(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int2)Word8c3)State# RealWorldst3Int -> Int -> EncodingBuffer#loopIntir'(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int3)State# RealWorldst4|Boolotherwise->doifIntosInt -> Int -> Intforall a. Num a => a -> a -> a-IntowInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<Int4thenCodingProgress -> Int -> Int -> EncodingBuffer#doneCodingProgressOutputUnderflowIntirIntowState# RealWorldst1elsedolet(Word8c1,Word8c2,Word8c3,Word8c4)=Char -> (Word8, Word8, Word8, Word8)ord4Charc!(#State# RealWorldst2,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8orawIntowWord8c1)State# RealWorldst1!(#State# RealWorldst3,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8oraw(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int1)Word8c2)State# RealWorldst2!(#State# RealWorldst4,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8oraw(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int2)Word8c3)State# RealWorldst3!(#State# RealWorldst5,()#)=IO () -> State# RealWorld -> (# State# RealWorld, () #)forall a. IO a -> State# RealWorld -> (# State# RealWorld, a #)unIO(RawBuffer Word8 -> Int -> Word8 -> IO ()writeWord8BufRawBuffer Word8oraw(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int3)Word8c4)State# RealWorldst4Int -> Int -> EncodingBuffer#loopIntir'(IntowInt -> Int -> Intforall a. Num a => a -> a -> a+Int4)State# RealWorldst5inInt -> Int -> EncodingBuffer#loopIntir0Intow0State# RealWorldst-- ------------------------------------------------------------------------------- UTF-8 primitives, lifted from Data.Text.Fusion.Utf8ord2::Char->(Word8,Word8)ord2 :: Char -> (Word8, Word8)ord2Charc=Bool -> (Word8, Word8) -> (Word8, Word8)forall a. (?callStack::CallStack) => Bool -> a -> aassert(IntnInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Int0x80Bool -> Bool -> Bool&&IntnInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<=Int0x07ff)(Word8x1,Word8x2)wheren :: Intn=Char -> IntordCharcx1 :: Word8x1=Int -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegral(Int -> Word8) -> Int -> Word8forall a b. (a -> b) -> a -> b$(IntnInt -> Int -> Intforall a. Bits a => a -> Int -> a`shiftR`Int6)Int -> Int -> Intforall a. Num a => a -> a -> a+Int0xC0x2 :: Word8x2=Int -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegral(Int -> Word8) -> Int -> Word8forall a b. (a -> b) -> a -> b$(IntnInt -> Int -> Intforall a. Bits a => a -> a -> a.&.Int0x3F)Int -> Int -> Intforall a. Num a => a -> a -> a+Int0x80ord3::Char->(Word8,Word8,Word8)ord3 :: Char -> (Word8, Word8, Word8)ord3Charc=Bool -> (Word8, Word8, Word8) -> (Word8, Word8, Word8)forall a. (?callStack::CallStack) => Bool -> a -> aassert(IntnInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Int0x0800Bool -> Bool -> Bool&&IntnInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<=Int0xffff)(Word8x1,Word8x2,Word8x3)wheren :: Intn=Char -> IntordCharcx1 :: Word8x1=Int -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegral(Int -> Word8) -> Int -> Word8forall a b. (a -> b) -> a -> b$(IntnInt -> Int -> Intforall a. Bits a => a -> Int -> a`shiftR`Int12)Int -> Int -> Intforall a. Num a => a -> a -> a+Int0xE0x2 :: Word8x2=Int -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegral(Int -> Word8) -> Int -> Word8forall a b. (a -> b) -> a -> b$((IntnInt -> Int -> Intforall a. Bits a => a -> Int -> a`shiftR`Int6)Int -> Int -> Intforall a. Bits a => a -> a -> a.&.Int0x3F)Int -> Int -> Intforall a. Num a => a -> a -> a+Int0x80x3 :: Word8x3=Int -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegral(Int -> Word8) -> Int -> Word8forall a b. (a -> b) -> a -> b$(IntnInt -> Int -> Intforall a. Bits a => a -> a -> a.&.Int0x3F)Int -> Int -> Intforall a. Num a => a -> a -> a+Int0x80ord4::Char->(Word8,Word8,Word8,Word8)ord4 :: Char -> (Word8, Word8, Word8, Word8)ord4Charc=Bool-> (Word8, Word8, Word8, Word8) -> (Word8, Word8, Word8, Word8)forall a. (?callStack::CallStack) => Bool -> a -> aassert(IntnInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>=Int0x10000)(Word8x1,Word8x2,Word8x3,Word8x4)wheren :: Intn=Char -> IntordCharcx1 :: Word8x1=Int -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegral(Int -> Word8) -> Int -> Word8forall a b. (a -> b) -> a -> b$(IntnInt -> Int -> Intforall a. Bits a => a -> Int -> a`shiftR`Int18)Int -> Int -> Intforall a. Num a => a -> a -> a+Int0xF0x2 :: Word8x2=Int -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegral(Int -> Word8) -> Int -> Word8forall a b. (a -> b) -> a -> b$((IntnInt -> Int -> Intforall a. Bits a => a -> Int -> a`shiftR`Int12)Int -> Int -> Intforall a. Bits a => a -> a -> a.&.Int0x3F)Int -> Int -> Intforall a. Num a => a -> a -> a+Int0x80x3 :: Word8x3=Int -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegral(Int -> Word8) -> Int -> Word8forall a b. (a -> b) -> a -> b$((IntnInt -> Int -> Intforall a. Bits a => a -> Int -> a`shiftR`Int6)Int -> Int -> Intforall a. Bits a => a -> a -> a.&.Int0x3F)Int -> Int -> Intforall a. Num a => a -> a -> a+Int0x80x4 :: Word8x4=Int -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegral(Int -> Word8) -> Int -> Word8forall a b. (a -> b) -> a -> b$(IntnInt -> Int -> Intforall a. Bits a => a -> a -> a.&.Int0x3F)Int -> Int -> Intforall a. Num a => a -> a -> a+Int0x80chr2::Word8->Word8->Charchr2 :: Word8 -> Word8 -> Charchr2(W8#Word8#x1#)(W8#Word8#x2#)=Char# -> CharC#(Int# -> Char#chr#(Int#z1#Int# -> Int# -> Int#+#Int#z2#))where!y1# :: Int#y1#=Word# -> Int#word2Int#(Word8# -> Word#word8ToWord#Word8#x1#)!y2# :: Int#y2#=Word# -> Int#word2Int#(Word8# -> Word#word8ToWord#Word8#x2#)!z1# :: Int#z1#=Int# -> Int# -> Int#uncheckedIShiftL#(Int#y1#Int# -> Int# -> Int#-#Int#0xC0#)Int#6#!z2# :: Int#z2#=Int#y2#Int# -> Int# -> Int#-#Int#0x80#{-# INLINEchr2#-}chr3::Word8->Word8->Word8->Charchr3 :: Word8 -> Word8 -> Word8 -> Charchr3(W8#Word8#x1#)(W8#Word8#x2#)(W8#Word8#x3#)=Char# -> CharC#(Int# -> Char#chr#(Int#z1#Int# -> Int# -> Int#+#Int#z2#Int# -> Int# -> Int#+#Int#z3#))where!y1# :: Int#y1#=Word# -> Int#word2Int#(Word8# -> Word#word8ToWord#Word8#x1#)!y2# :: Int#y2#=Word# -> Int#word2Int#(Word8# -> Word#word8ToWord#Word8#x2#)!y3# :: Int#y3#=Word# -> Int#word2Int#(Word8# -> Word#word8ToWord#Word8#x3#)!z1# :: Int#z1#=Int# -> Int# -> Int#uncheckedIShiftL#(Int#y1#Int# -> Int# -> Int#-#Int#0xE0#)Int#12#!z2# :: Int#z2#=Int# -> Int# -> Int#uncheckedIShiftL#(Int#y2#Int# -> Int# -> Int#-#Int#0x80#)Int#6#!z3# :: Int#z3#=Int#y3#Int# -> Int# -> Int#-#Int#0x80#{-# INLINEchr3#-}chr4::Word8->Word8->Word8->Word8->Charchr4 :: Word8 -> Word8 -> Word8 -> Word8 -> Charchr4(W8#Word8#x1#)(W8#Word8#x2#)(W8#Word8#x3#)(W8#Word8#x4#)=Char# -> CharC#(Int# -> Char#chr#(Int#z1#Int# -> Int# -> Int#+#Int#z2#Int# -> Int# -> Int#+#Int#z3#Int# -> Int# -> Int#+#Int#z4#))where!y1# :: Int#y1#=Word# -> Int#word2Int#(Word8# -> Word#word8ToWord#Word8#x1#)!y2# :: Int#y2#=Word# -> Int#word2Int#(Word8# -> Word#word8ToWord#Word8#x2#)!y3# :: Int#y3#=Word# -> Int#word2Int#(Word8# -> Word#word8ToWord#Word8#x3#)!y4# :: Int#y4#=Word# -> Int#word2Int#(Word8# -> Word#word8ToWord#Word8#x4#)!z1# :: Int#z1#=Int# -> Int# -> Int#uncheckedIShiftL#(Int#y1#Int# -> Int# -> Int#-#Int#0xF0#)Int#18#!z2# :: Int#z2#=Int# -> Int# -> Int#uncheckedIShiftL#(Int#y2#Int# -> Int# -> Int#-#Int#0x80#)Int#12#!z3# :: Int#z3#=Int# -> Int# -> Int#uncheckedIShiftL#(Int#y3#Int# -> Int# -> Int#-#Int#0x80#)Int#6#!z4# :: Int#z4#=Int#y4#Int# -> Int# -> Int#-#Int#0x80#{-# INLINEchr4#-}between::Word8-- ^ byte to check->Word8-- ^ lower bound->Word8-- ^ upper bound->Boolbetween :: Word8 -> Word8 -> Word8 -> BoolbetweenWord8xWord8yWord8z=Word8xWord8 -> Word8 -> Boolforall a. Ord a => a -> a -> Bool>=Word8yBool -> Bool -> Bool&&Word8xWord8 -> Word8 -> Boolforall a. Ord a => a -> a -> Bool<=Word8z{-# INLINEbetween#-}validate3::Word8->Word8->Word8->Bool{-# INLINEvalidate3#-}validate3 :: Word8 -> Word8 -> Word8 -> Boolvalidate3Word8x1Word8x2Word8x3=Boolvalidate3_1Bool -> Bool -> Bool||Boolvalidate3_2Bool -> Bool -> Bool||Boolvalidate3_3Bool -> Bool -> Bool||Boolvalidate3_4wherevalidate3_1 :: Boolvalidate3_1=(Word8x1Word8 -> Word8 -> Boolforall a. Eq a => a -> a -> Bool==Word80xE0)Bool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x2Word80xA0Word80xBFBool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x3Word80x80Word80xBFvalidate3_2 :: Boolvalidate3_2=Word8 -> Word8 -> Word8 -> BoolbetweenWord8x1Word80xE1Word80xECBool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x2Word80x80Word80xBFBool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x3Word80x80Word80xBFvalidate3_3 :: Boolvalidate3_3=Word8x1Word8 -> Word8 -> Boolforall a. Eq a => a -> a -> Bool==Word80xEDBool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x2Word80x80Word80x9FBool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x3Word80x80Word80xBFvalidate3_4 :: Boolvalidate3_4=Word8 -> Word8 -> Word8 -> BoolbetweenWord8x1Word80xEEWord80xEFBool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x2Word80x80Word80xBFBool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x3Word80x80Word80xBFvalidate4::Word8->Word8->Word8->Word8->Bool{-# INLINEvalidate4#-}validate4 :: Word8 -> Word8 -> Word8 -> Word8 -> Boolvalidate4Word8x1Word8x2Word8x3Word8x4=Boolvalidate4_1Bool -> Bool -> Bool||Boolvalidate4_2Bool -> Bool -> Bool||Boolvalidate4_3wherevalidate4_1 :: Boolvalidate4_1=Word8x1Word8 -> Word8 -> Boolforall a. Eq a => a -> a -> Bool==Word80xF0Bool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x2Word80x90Word80xBFBool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x3Word80x80Word80xBFBool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x4Word80x80Word80xBFvalidate4_2 :: Boolvalidate4_2=Word8 -> Word8 -> Word8 -> BoolbetweenWord8x1Word80xF1Word80xF3Bool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x2Word80x80Word80xBFBool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x3Word80x80Word80xBFBool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x4Word80x80Word80xBFvalidate4_3 :: Boolvalidate4_3=Word8x1Word8 -> Word8 -> Boolforall a. Eq a => a -> a -> Bool==Word80xF4Bool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x2Word80x80Word80x8FBool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x3Word80x80Word80xBFBool -> Bool -> Bool&&Word8 -> Word8 -> Word8 -> BoolbetweenWord8x4Word80x80Word80xBF
[8]ページ先頭