{-# LANGUAGE CPP, ForeignFunctionInterface, BangPatterns #-}{-# LANGUAGE UnliftedFFITypes, MagicHash,
 UnboxedTuples, DeriveDataTypeable #-}#if __GLASGOW_HASKELL__ >= 703
{-# LANGUAGE Unsafe #-}#endif
{-# OPTIONS_HADDOCK not-home #-}-- |-- Module : Data.ByteString.Internal-- Copyright : (c) Don Stewart 2006-2008-- (c) Duncan Coutts 2006-2012-- License : BSD-style-- Maintainer : dons00@gmail.com, duncan@community.haskell.org-- Stability : unstable-- Portability : non-portable---- A module containing semi-public 'ByteString' internals. This exposes the-- 'ByteString' representation and low level construction functions. As such-- all the functions in this module are unsafe. The API is also not stable.---- Where possible application should instead use the functions from the normal-- public interface modules, such as "Data.ByteString.Unsafe". Packages that-- extend the ByteString system at a low level will need to use this module.--moduleData.ByteString.Internal(-- * The @ByteString@ type and representationByteString (..),-- instances: Eq, Ord, Show, Read, Data, Typeable-- * Conversion with lists: packing and unpackingpackBytes ,packUptoLenBytes ,unsafePackLenBytes ,packChars ,packUptoLenChars ,unsafePackLenChars ,unpackBytes ,unpackAppendBytesLazy ,unpackAppendBytesStrict ,unpackChars ,unpackAppendCharsLazy ,unpackAppendCharsStrict ,unsafePackAddress ,-- * Low level imperative constructioncreate ,-- :: Int -> (Ptr Word8 -> IO ()) -> IO ByteStringcreateUptoN ,-- :: Int -> (Ptr Word8 -> IO Int) -> IO ByteStringcreateAndTrim ,-- :: Int -> (Ptr Word8 -> IO Int) -> IO ByteStringcreateAndTrim' ,-- :: Int -> (Ptr Word8 -> IO (Int, Int, a)) -> IO (ByteString, a)unsafeCreate ,-- :: Int -> (Ptr Word8 -> IO ()) -> ByteStringunsafeCreateUptoN ,-- :: Int -> (Ptr Word8 -> IO Int) -> ByteStringmallocByteString ,-- :: Int -> IO (ForeignPtr a)-- * Conversion to and from ForeignPtrsfromForeignPtr ,-- :: ForeignPtr Word8 -> Int -> Int -> ByteStringtoForeignPtr ,-- :: ByteString -> (ForeignPtr Word8, Int, Int)-- * UtilitiesnullForeignPtr ,-- :: ForeignPtr Word8checkedAdd ,-- :: String -> Int -> Int -> Int-- * Standard C Functionsc_strlen ,-- :: CString -> IO CIntc_free_finalizer ,-- :: FunPtr (Ptr Word8 -> IO ())memchr ,-- :: Ptr Word8 -> Word8 -> CSize -> IO Ptr Word8memcmp ,-- :: Ptr Word8 -> Ptr Word8 -> Int -> IO CIntmemcpy ,-- :: Ptr Word8 -> Ptr Word8 -> Int -> IO ()memset ,-- :: Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)-- * cbits functionsc_reverse ,-- :: Ptr Word8 -> Ptr Word8 -> CInt -> IO ()c_intersperse ,-- :: Ptr Word8 -> Ptr Word8 -> CInt -> Word8 -> IO ()c_maximum ,-- :: Ptr Word8 -> CInt -> IO Word8c_minimum ,-- :: Ptr Word8 -> CInt -> IO Word8c_count ,-- :: Ptr Word8 -> CInt -> Word8 -> IO CInt-- * Charsw2c ,c2w ,isSpaceWord8 ,isSpaceChar8 ,-- * Deprecated and unmentionableaccursedUnutterablePerformIO ,-- :: IO a -> ainlinePerformIO -- :: IO a -> a)whereimportPreludehiding(concat,null)importqualifiedData.ListasListimportForeign.ForeignPtr(ForeignPtr,withForeignPtr)importForeign.Ptr(Ptr,FunPtr,plusPtr)importForeign.Storable(Storable(..))#if MIN_VERSION_base(4,5,0) || __GLASGOW_HASKELL__ >= 703
importForeign.C.Types(CInt(..),CSize(..),CULong(..))#else
importForeign.C.Types(CInt,CSize,CULong)#endif
importForeign.C.String(CString)#if !(MIN_VERSION_base(4,11,0)) && MIN_VERSION_base(4,9,0)
importData.Semigroup(Semigroup((<>)))#endif
#if !(MIN_VERSION_base(4,8,0))
importData.Monoid(Monoid(..))#endif
importControl.DeepSeq(NFData(rnf))importData.String(IsString(..))importControl.Exception(assert)importData.Char(ord)importData.Word(Word8)importData.Typeable(Typeable)importData.Data(Data(..),mkNoRepType)importGHC.Base(nullAddr#,realWorld#,unsafeChr)#if MIN_VERSION_base(4,4,0)
importGHC.CString(unpackCString#)#else
importGHC.Base(unpackCString#)#endif
importGHC.Prim(Addr#)#if __GLASGOW_HASKELL__ >= 611
importGHC.IO(IO(IO),unsafeDupablePerformIO)#else
importGHC.IOBase(IO(IO),RawBuffer,unsafeDupablePerformIO)#endif
importGHC.ForeignPtr(ForeignPtr(ForeignPtr),newForeignPtr_,mallocPlainForeignPtrBytes)importGHC.Ptr(Ptr(..),castPtr)-- CFILES stuff is Hugs only{-# CFILES cbits/fpstring.c #-}-- ------------------------------------------------------------------------------- | A space-efficient representation of a 'Word8' vector, supporting many-- efficient operations.---- A 'ByteString' contains 8-bit bytes, or by using the operations from-- "Data.ByteString.Char8" it can be interpreted as containing 8-bit-- characters.--dataByteString =PS {-# UNPACK#-}!(ForeignPtrWord8)-- payload{-# UNPACK#-}!Int-- offset{-# UNPACK#-}!Int-- lengthderiving(Typeable)instanceEqByteString where(== )=eq instanceOrdByteString wherecompare =compareBytes #if MIN_VERSION_base(4,9,0)
instanceSemigroupByteString where(<> )=append #endif
instanceMonoidByteString wheremempty =PS nullForeignPtr 00#if MIN_VERSION_base(4,9,0)
mappend =(<>)#else
mappend=append#endif
mconcat =concat instanceNFDataByteString wherernf PS {}=()instanceShowByteString whereshowsPrec p ps r =showsPrecp (unpackChars ps )r instanceReadByteString wherereadsPrec p str =[(packChars x ,y )|(x ,y )<-readsPrecp str ]instanceIsStringByteString wherefromString =packChars instanceDataByteString wheregfoldl f z txt =z packBytes `f `unpackBytes txt toConstr _=error"Data.ByteString.ByteString.toConstr"gunfold __=error"Data.ByteString.ByteString.gunfold"dataTypeOf _=mkNoRepType"Data.ByteString.ByteString"-------------------------------------------------------------------------- Packing and unpacking from listspackBytes::[Word8]->ByteString packBytes ws =unsafePackLenBytes (List.lengthws )ws packChars::[Char]->ByteString packChars cs =unsafePackLenChars (List.lengthcs )cs {-# INLINE[0]packChars#-}{-# RULES"ByteString packChars/packAddress"foralls.packChars(unpackCString#s)=accursedUnutterablePerformIO(unsafePackAddresss)#-}unsafePackLenBytes::Int->[Word8]->ByteString unsafePackLenBytes len xs0 =unsafeCreate len $\p ->go p xs0 wherego !_[]=return()go!p (x :xs )=pokep x >>go (p `plusPtr`1)xs unsafePackLenChars::Int->[Char]->ByteString unsafePackLenChars len cs0 =unsafeCreate len $\p ->go p cs0 wherego !_[]=return()go!p (c :cs )=pokep (c2w c )>>go (p `plusPtr`1)cs -- | /O(n)/ Pack a null-terminated sequence of bytes, pointed to by an-- Addr\# (an arbitrary machine address assumed to point outside the-- garbage-collected heap) into a @ByteString@. A much faster way to-- create an 'Addr#' is with an unboxed string literal, than to pack a-- boxed string. A unboxed string literal is compiled to a static @char-- []@ by GHC. Establishing the length of the string requires a call to-- @strlen(3)@, so the 'Addr#' must point to a null-terminated buffer (as-- is the case with @\"string\"\#@ literals in GHC). Use 'unsafePackAddressLen'-- if you know the length of the string statically.---- An example:---- > literalFS = unsafePackAddress "literal"#---- This function is /unsafe/. If you modify the buffer pointed to by the-- original 'Addr#' this modification will be reflected in the resulting-- @ByteString@, breaking referential transparency.---- Note this also won't work if your 'Addr#' has embedded @\'\0円\'@ characters in-- the string, as @strlen@ will return too short a length.--unsafePackAddress::Addr#->IOByteString unsafePackAddress addr# =dop <-newForeignPtr_(castPtrcstr )l <-c_strlen cstr return$PS p 0(fromIntegrall )wherecstr::CStringcstr =Ptraddr# {-# INLINEunsafePackAddress#-}packUptoLenBytes::Int->[Word8]->(ByteString ,[Word8])packUptoLenBytes len xs0 =unsafeCreateUptoN' len $\p ->go p len xs0 wherego !_!n []=return(len -n ,[])go!_!0xs =return(len ,xs )go!p !n (x :xs )=pokep x >>go (p `plusPtr`1)(n -1)xs packUptoLenChars::Int->[Char]->(ByteString ,[Char])packUptoLenChars len cs0 =unsafeCreateUptoN' len $\p ->go p len cs0 wherego !_!n []=return(len -n ,[])go!_!0cs =return(len ,cs )go!p !n (c :cs )=pokep (c2w c )>>go (p `plusPtr`1)(n -1)cs -- Unpacking bytestrings into lists effeciently is a tradeoff: on the one hand-- we would like to write a tight loop that just blats the list into memory, on-- the other hand we want it to be unpacked lazily so we don't end up with a-- massive list data structure in memory.---- Our strategy is to combine both: we will unpack lazily in reasonable sized-- chunks, where each chunk is unpacked strictly.---- unpackBytes and unpackChars do the lazy loop, while unpackAppendBytes and-- unpackAppendChars do the chunks strictly.unpackBytes::ByteString ->[Word8]unpackBytes bs =unpackAppendBytesLazy bs []unpackChars::ByteString ->[Char]unpackChars bs =unpackAppendCharsLazy bs []unpackAppendBytesLazy::ByteString ->[Word8]->[Word8]unpackAppendBytesLazy (PS fp off len )xs |len <=100=unpackAppendBytesStrict (PS fp off len )xs |otherwise=unpackAppendBytesStrict (PS fp off 100)remainder whereremainder =unpackAppendBytesLazy (PS fp (off +100)(len -100))xs -- Why 100 bytes you ask? Because on a 64bit machine the list we allocate-- takes just shy of 4k which seems like a reasonable amount.-- (5 words per list element, 8 bytes per word, 100 elements = 4000 bytes)unpackAppendCharsLazy::ByteString ->[Char]->[Char]unpackAppendCharsLazy (PS fp off len )cs |len <=100=unpackAppendCharsStrict (PS fp off len )cs |otherwise=unpackAppendCharsStrict (PS fp off 100)remainder whereremainder =unpackAppendCharsLazy (PS fp (off +100)(len -100))cs -- For these unpack functions, since we're unpacking the whole list strictly we-- build up the result list in an accumulator. This means we have to build up-- the list starting at the end. So our traversal starts at the end of the-- buffer and loops down until we hit the sentinal:unpackAppendBytesStrict::ByteString ->[Word8]->[Word8]unpackAppendBytesStrict (PS fp off len )xs =accursedUnutterablePerformIO $withForeignPtrfp $\base ->loop (base `plusPtr`(off -1))(base `plusPtr`(off -1+len ))xs whereloop !sentinal !p acc |p ==sentinal =returnacc |otherwise=dox <-peekp loop sentinal (p `plusPtr`(-1))(x :acc )unpackAppendCharsStrict::ByteString ->[Char]->[Char]unpackAppendCharsStrict (PS fp off len )xs =accursedUnutterablePerformIO $withForeignPtrfp $\base ->loop (base `plusPtr`(off -1))(base `plusPtr`(off -1+len ))xs whereloop !sentinal !p acc |p ==sentinal =returnacc |otherwise=dox <-peekp loop sentinal (p `plusPtr`(-1))(w2c x :acc )-------------------------------------------------------------------------- | The 0 pointer. Used to indicate the empty Bytestring.nullForeignPtr::ForeignPtrWord8nullForeignPtr =ForeignPtrnullAddr#(error"nullForeignPtr")--TODO: should ForeignPtrContents be strict?-- ----------------------------------------------------------------------- Low level constructors-- | /O(1)/ Build a ByteString from a ForeignPtr.---- If you do not need the offset parameter then you do should be using-- 'Data.ByteString.Unsafe.unsafePackCStringLen' or-- 'Data.ByteString.Unsafe.unsafePackCStringFinalizer' instead.--fromForeignPtr::ForeignPtrWord8->Int-- ^ Offset->Int-- ^ Length->ByteString fromForeignPtr =PS {-# INLINEfromForeignPtr#-}-- | /O(1)/ Deconstruct a ForeignPtr from a ByteStringtoForeignPtr::ByteString ->(ForeignPtrWord8,Int,Int)-- ^ (ptr, offset, length)toForeignPtr (PS ps s l )=(ps ,s ,l ){-# INLINEtoForeignPtr#-}-- | A way of creating ByteStrings outside the IO monad. The @Int@-- argument gives the final size of the ByteString.unsafeCreate::Int->(PtrWord8->IO())->ByteString unsafeCreate l f =unsafeDupablePerformIO(create l f ){-# INLINEunsafeCreate#-}-- | Like 'unsafeCreate' but instead of giving the final size of the-- ByteString, it is just an upper bound. The inner action returns-- the actual size. Unlike 'createAndTrim' the ByteString is not-- reallocated if the final size is less than the estimated size.unsafeCreateUptoN::Int->(PtrWord8->IOInt)->ByteString unsafeCreateUptoN l f =unsafeDupablePerformIO(createUptoN l f ){-# INLINEunsafeCreateUptoN#-}unsafeCreateUptoN'::Int->(PtrWord8->IO(Int,a ))->(ByteString ,a )unsafeCreateUptoN' l f =unsafeDupablePerformIO(createUptoN' l f ){-# INLINEunsafeCreateUptoN'#-}-- | Create ByteString of size @l@ and use action @f@ to fill it's contents.create::Int->(PtrWord8->IO())->IOByteString create l f =dofp <-mallocByteString l withForeignPtrfp $\p ->f p return$!PS fp 0l {-# INLINEcreate#-}-- | Create ByteString of up to size size @l@ and use action @f@ to fill it's-- contents which returns its true size.createUptoN::Int->(PtrWord8->IOInt)->IOByteString createUptoN l f =dofp <-mallocByteString l l' <-withForeignPtrfp $\p ->f p assert(l' <=l )$return$!PS fp 0l' {-# INLINEcreateUptoN#-}-- | Create ByteString of up to size @l@ and use action @f@ to fill it's contents which returns its true size.createUptoN'::Int->(PtrWord8->IO(Int,a ))->IO(ByteString ,a )createUptoN' l f =dofp <-mallocByteString l (l' ,res )<-withForeignPtrfp $\p ->f p assert(l' <=l )$return(PS fp 0l' ,res ){-# INLINEcreateUptoN'#-}-- | Given the maximum size needed and a function to make the contents-- of a ByteString, createAndTrim makes the 'ByteString'. The generating-- function is required to return the actual final size (<= the maximum-- size), and the resulting byte array is realloced to this size.---- createAndTrim is the main mechanism for creating custom, efficient-- ByteString functions, using Haskell or C functions to fill the space.--createAndTrim::Int->(PtrWord8->IOInt)->IOByteString createAndTrim l f =dofp <-mallocByteString l withForeignPtrfp $\p ->dol' <-f p ifassert(l' <=l )$l' >=l thenreturn$!PS fp 0l elsecreate l' $\p' ->memcpy p' p l' {-# INLINEcreateAndTrim#-}createAndTrim'::Int->(PtrWord8->IO(Int,Int,a ))->IO(ByteString ,a )createAndTrim' l f =dofp <-mallocByteString l withForeignPtrfp $\p ->do(off ,l' ,res )<-f p ifassert(l' <=l )$l' >=l thenreturn(PS fp 0l ,res )elsedops <-create l' $\p' ->memcpy p' (p `plusPtr`off )l' return(ps ,res )-- | Wrapper of 'mallocForeignPtrBytes' with faster implementation for GHC--mallocByteString::Int->IO(ForeignPtra )mallocByteString =mallocPlainForeignPtrBytes{-# INLINEmallocByteString#-}-------------------------------------------------------------------------- Implementations for Eq, Ord and Monoid instanceseq::ByteString ->ByteString ->Booleq a @(PS fp off len )b @(PS fp' off' len' )|len /=len' =False-- short cut on length|fp ==fp' &&off ==off' =True-- short cut for the same string|otherwise=compareBytes a b ==EQ{-# INLINEeq#-}-- ^ still neededcompareBytes::ByteString ->ByteString ->OrderingcompareBytes (PS __0)(PS __0)=EQ-- short cut for empty stringscompareBytes(PS fp1 off1 len1 )(PS fp2 off2 len2 )=accursedUnutterablePerformIO $withForeignPtrfp1 $\p1 ->withForeignPtrfp2 $\p2 ->doi <-memcmp (p1 `plusPtr`off1 )(p2 `plusPtr`off2 )(minlen1 len2 )return$!casei `compare`0ofEQ->len1 `compare`len2 x ->x append::ByteString ->ByteString ->ByteString append (PS __0)b =b appenda (PS __0)=a append(PS fp1 off1 len1 )(PS fp2 off2 len2 )=unsafeCreate (len1 +len2 )$\destptr1 ->doletdestptr2 =destptr1 `plusPtr`len1 withForeignPtrfp1 $\p1 ->memcpy destptr1 (p1 `plusPtr`off1 )len1 withForeignPtrfp2 $\p2 ->memcpy destptr2 (p2 `plusPtr`off2 )len2 concat::[ByteString ]->ByteString concat =\bss0 ->goLen0 bss0 bss0 -- The idea here is we first do a pass over the input list to determine:---- 1. is a copy necessary? e.g. @concat []@, @concat [mempty, "hello"]@,-- and @concat ["hello", mempty, mempty]@ can all be handled without-- copying.-- 2. if a copy is necessary, how large is the result going to be?---- If a copy is necessary then we create a buffer of the appropriate size-- and do another pass over the input list, copying the chunks into the-- buffer. Also, since foreign calls aren't entirely free we skip over-- empty chunks while copying.---- We pass the original [ByteString] (bss0) through as an argument through-- goLen0, goLen1, and goLen since we will need it again in goCopy. Passing-- it as an explicit argument avoids capturing it in these functions'-- closures which would result in unnecessary closure allocation.where-- It's still possible that the result is emptygoLen0 _[]=memptygoLen0bss0 (PS __0:bss )=goLen0 bss0 bss goLen0bss0 (bs :bss )=goLen1 bss0 bs bss -- It's still possible that the result is a single chunkgoLen1 _bs []=bs goLen1bss0 bs (PS __0:bss )=goLen1 bss0 bs bss goLen1bss0 bs (PS __len :bss )=goLen bss0 (checkedAdd "concat"len' len )bss wherePS __len' =bs -- General case, just find the total length we'll needgoLen bss0 !total (PS __len :bss )=goLen bss0 total' bss wheretotal' =checkedAdd "concat"total len goLenbss0 total []=unsafeCreate total $\ptr ->goCopy bss0 ptr -- Copy the datagoCopy []!_=return()goCopy(PS __0:bss )!ptr =goCopy bss ptr goCopy(PS fp off len :bss )!ptr =dowithForeignPtrfp $\p ->memcpy ptr (p `plusPtr`off )len goCopy bss (ptr `plusPtr`len ){-# NOINLINEconcat#-}{-# RULES"ByteString concat [] -> mempty"concat[]=mempty"ByteString concat [bs] -> bs"forallx.concat[x]=x#-}-- | Add two non-negative numbers. Errors out on overflow.checkedAdd::String->Int->Int->IntcheckedAdd fun x y |r >=0=r |otherwise=overflowError fun wherer =x +y {-# INLINEcheckedAdd#-}-------------------------------------------------------------------------- | Conversion between 'Word8' and 'Char'. Should compile to a no-op.w2c::Word8->Charw2c =unsafeChr.fromIntegral{-# INLINEw2c#-}-- | Unsafe conversion between 'Char' and 'Word8'. This is a no-op and-- silently truncates to 8 bits Chars > '255円'. It is provided as-- convenience for ByteString construction.c2w::Char->Word8c2w =fromIntegral.ord{-# INLINEc2w#-}-- | Selects words corresponding to white-space characters in the Latin-1 range-- ordered by frequency.isSpaceWord8::Word8->BoolisSpaceWord8 w =w ==0x20||w ==0x0A||-- LF, \nw ==0x09||-- HT, \tw ==0x0C||-- FF, \fw ==0x0D||-- CR, \rw ==0x0B||-- VT, \vw ==0xA0-- spotted by QC..{-# INLINEisSpaceWord8#-}-- | Selects white-space characters in the Latin-1 rangeisSpaceChar8::Char->BoolisSpaceChar8 c =c ==' '||c =='\t'||c =='\n'||c =='\r'||c =='\f'||c =='\v'||c =='\xa0'{-# INLINEisSpaceChar8#-}overflowError::String->a overflowError fun =error$"Data.ByteString."++fun ++": size overflow"-------------------------------------------------------------------------- | This \"function\" has a superficial similarity to 'unsafePerformIO' but-- it is in fact a malevolent agent of chaos. It unpicks the seams of reality-- (and the 'IO' monad) so that the normal rules no longer apply. It lulls you-- into thinking it is reasonable, but when you are not looking it stabs you-- in the back and aliases all of your mutable buffers. The carcass of many a-- seasoned Haskell programmer lie strewn at its feet.---- Witness the trail of destruction:---- * <https://github.com/haskell/bytestring/commit/71c4b438c675aa360c79d79acc9a491e7bbc26e7>---- * <https://github.com/haskell/bytestring/commit/210c656390ae617d9ee3b8bcff5c88dd17cef8da>---- * <https://ghc.haskell.org/trac/ghc/ticket/3486>---- * <https://ghc.haskell.org/trac/ghc/ticket/3487>---- * <https://ghc.haskell.org/trac/ghc/ticket/7270>---- Do not talk about \"safe\"! You do not know what is safe!---- Yield not to its blasphemous call! Flee traveller! Flee or you will be-- corrupted and devoured!--{-# INLINEaccursedUnutterablePerformIO#-}accursedUnutterablePerformIO::IOa ->a accursedUnutterablePerformIO (IOm )=casem realWorld#of(#_,r #)->r inlinePerformIO::IOa ->a inlinePerformIO =accursedUnutterablePerformIO {-# INLINEinlinePerformIO#-}{-# DEPRECATEDinlinePerformIO"If you think you know what you are doing, use 'unsafePerformIO'. If you are sure you know what you are doing, use 'unsafeDupablePerformIO'. If you enjoy sharing an address space with a malevolent agent of chaos, try 'accursedUnutterablePerformIO'."#-}-- ------------------------------------------------------------------------- Standard C functions--foreignimportccallunsafe"string.h strlen"c_strlen::CString->IOCSizeforeignimportccallunsafe"static stdlib.h &free"c_free_finalizer::FunPtr(PtrWord8->IO())foreignimportccallunsafe"string.h memchr"c_memchr::PtrWord8->CInt->CSize->IO(PtrWord8)memchr::PtrWord8->Word8->CSize->IO(PtrWord8)memchr p w s =c_memchr p (fromIntegralw )s foreignimportccallunsafe"string.h memcmp"c_memcmp::PtrWord8->PtrWord8->CSize->IOCIntmemcmp::PtrWord8->PtrWord8->Int->IOCIntmemcmp p q s =c_memcmp p q (fromIntegrals )foreignimportccallunsafe"string.h memcpy"c_memcpy::PtrWord8->PtrWord8->CSize->IO(PtrWord8)memcpy::PtrWord8->PtrWord8->Int->IO()memcpy p q s =c_memcpy p q (fromIntegrals )>>return(){-
foreign import ccall unsafe "string.h memmove" c_memmove
 :: Ptr Word8 -> Ptr Word8 -> CSize -> IO (Ptr Word8)
memmove :: Ptr Word8 -> Ptr Word8 -> CSize -> IO ()
memmove p q s = do c_memmove p q s
 return ()
-}foreignimportccallunsafe"string.h memset"c_memset::PtrWord8->CInt->CSize->IO(PtrWord8)memset::PtrWord8->Word8->CSize->IO(PtrWord8)memset p w s =c_memset p (fromIntegralw )s -- ------------------------------------------------------------------------- Uses our C code--foreignimportccallunsafe"static fpstring.h fps_reverse"c_reverse::PtrWord8->PtrWord8->CULong->IO()foreignimportccallunsafe"static fpstring.h fps_intersperse"c_intersperse::PtrWord8->PtrWord8->CULong->Word8->IO()foreignimportccallunsafe"static fpstring.h fps_maximum"c_maximum::PtrWord8->CULong->IOWord8foreignimportccallunsafe"static fpstring.h fps_minimum"c_minimum::PtrWord8->CULong->IOWord8foreignimportccallunsafe"static fpstring.h fps_count"c_count::PtrWord8->CULong->Word8->IOCULong

AltStyle によって変換されたページ (->オリジナル) /