Movatterモバイル変換


[0]ホーム

URL:


{-# LANGUAGE Trustworthy #-}{-# LANGUAGE CPP, NoImplicitPrelude #-}------------------------------------------------------------------------------- |-- Module      :  Foreign.C.String-- Copyright   :  (c) The FFI task force 2001-- License     :  BSD-style (see the file libraries/base/LICENSE)---- Maintainer  :  ffi@haskell.org-- Stability   :  provisional-- Portability :  portable---- Utilities for primitive marshalling of C strings.---- The marshalling converts each Haskell character, representing a Unicode-- code point, to one or more bytes in a manner that, by default, is-- determined by the current locale.  As a consequence, no guarantees-- can be made about the relative length of a Haskell string and its-- corresponding C string, and therefore all the marshalling routines-- include memory allocation.  The translation between Unicode and the-- encoding of the current locale may be lossy.-------------------------------------------------------------------------------moduleForeign.C.String(-- representation of strings in C-- * C stringsCString,CStringLen,-- ** Using a locale-dependent encoding-- | These functions are different from their @CAString@ counterparts-- in that they will use an encoding determined by the current locale,-- rather than always assuming ASCII.-- conversion of C strings into Haskell strings--peekCString,peekCStringLen,-- conversion of Haskell strings into C strings--newCString,newCStringLen,-- conversion of Haskell strings into C strings using temporary storage--withCString,withCStringLen,charIsRepresentable,-- ** Using 8-bit characters-- | These variants of the above functions are for use with C libraries-- that are ignorant of Unicode.  These functions should be used with-- care, as a loss of information can occur.castCharToCChar,castCCharToChar,castCharToCUChar,castCUCharToChar,castCharToCSChar,castCSCharToChar,peekCAString,peekCAStringLen,newCAString,newCAStringLen,withCAString,withCAStringLen,-- * C wide strings-- | These variants of the above functions are for use with C libraries-- that encode Unicode using the C @wchar_t@ type in a system-dependent-- way.  The only encodings supported are---- * UTF-32 (the C compiler defines @__STDC_ISO_10646__@), or---- * UTF-16 (as used on Windows systems).CWString,CWStringLen,peekCWString,peekCWStringLen,newCWString,newCWStringLen,withCWString,withCWStringLen,)whereimportForeign.Marshal.ArrayimportForeign.C.TypesimportForeign.PtrimportForeign.StorableimportData.WordimportGHC.CharimportGHC.ListimportGHC.RealimportGHC.NumimportGHC.Baseimport{-# SOURCE#-}GHC.IO.EncodingimportqualifiedGHC.ForeignasGHC------------------------------------------------------------------------------- Strings-- representation of strings in C-- -------------------------------- | A C string is a reference to an array of C characters terminated by NUL.typeCString=PtrCChar-- | A string with explicit length information in bytes instead of a-- terminating NUL (allowing NUL characters in the middle of the string).typeCStringLen=(PtrCChar,Int)-- exported functions-- ---------------------- * the following routines apply the default conversion when converting the--   C-land character encoding into the Haskell-land character encoding-- | Marshal a NUL terminated C string into a Haskell string.--peekCString::CString->IOStringpeekCString :: CString -> IO StringpeekCStringCStrings=IO TextEncodinggetForeignEncodingIO TextEncoding -> (TextEncoding -> IO String) -> IO Stringforall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b>>=(TextEncoding -> CString -> IO String)-> CString -> TextEncoding -> IO Stringforall a b c. (a -> b -> c) -> b -> a -> cflipTextEncoding -> CString -> IO StringGHC.peekCStringCStrings-- | Marshal a C string with explicit length into a Haskell string.--peekCStringLen::CStringLen->IOStringpeekCStringLen :: CStringLen -> IO StringpeekCStringLenCStringLens=IO TextEncodinggetForeignEncodingIO TextEncoding -> (TextEncoding -> IO String) -> IO Stringforall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b>>=(TextEncoding -> CStringLen -> IO String)-> CStringLen -> TextEncoding -> IO Stringforall a b c. (a -> b -> c) -> b -> a -> cflipTextEncoding -> CStringLen -> IO StringGHC.peekCStringLenCStringLens-- | Marshal a Haskell string into a NUL terminated C string.---- * the Haskell string may /not/ contain any NUL characters---- * new storage is allocated for the C string and must be--   explicitly freed using 'Foreign.Marshal.Alloc.free' or--   'Foreign.Marshal.Alloc.finalizerFree'.--newCString::String->IOCStringnewCString :: String -> IO CStringnewCStringStrings=IO TextEncodinggetForeignEncodingIO TextEncoding -> (TextEncoding -> IO CString) -> IO CStringforall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b>>=(TextEncoding -> String -> IO CString)-> String -> TextEncoding -> IO CStringforall a b c. (a -> b -> c) -> b -> a -> cflipTextEncoding -> String -> IO CStringGHC.newCStringStrings-- | Marshal a Haskell string into a C string (ie, character array) with-- explicit length information.---- * new storage is allocated for the C string and must be--   explicitly freed using 'Foreign.Marshal.Alloc.free' or--   'Foreign.Marshal.Alloc.finalizerFree'.--newCStringLen::String->IOCStringLennewCStringLen :: String -> IO CStringLennewCStringLenStrings=IO TextEncodinggetForeignEncodingIO TextEncoding -> (TextEncoding -> IO CStringLen) -> IO CStringLenforall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b>>=(TextEncoding -> String -> IO CStringLen)-> String -> TextEncoding -> IO CStringLenforall a b c. (a -> b -> c) -> b -> a -> cflipTextEncoding -> String -> IO CStringLenGHC.newCStringLenStrings-- | Marshal a Haskell string into a NUL terminated C string using temporary-- storage.---- * the Haskell string may /not/ contain any NUL characters---- * the memory is freed when the subcomputation terminates (either--   normally or via an exception), so the pointer to the temporary--   storage must /not/ be used after this.--withCString::String->(CString->IOa)->IOawithCString :: String -> (CString -> IO a) -> IO awithCStringStringsCString -> IO af=IO TextEncodinggetForeignEncodingIO TextEncoding -> (TextEncoding -> IO a) -> IO aforall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b>>=\TextEncodingenc->TextEncoding -> String -> (CString -> IO a) -> IO aforall a. TextEncoding -> String -> (CString -> IO a) -> IO aGHC.withCStringTextEncodingencStringsCString -> IO af-- | Marshal a Haskell string into a C string (ie, character array)-- in temporary storage, with explicit length information.---- * the memory is freed when the subcomputation terminates (either--   normally or via an exception), so the pointer to the temporary--   storage must /not/ be used after this.--withCStringLen::String->(CStringLen->IOa)->IOawithCStringLen :: String -> (CStringLen -> IO a) -> IO awithCStringLenStringsCStringLen -> IO af=IO TextEncodinggetForeignEncodingIO TextEncoding -> (TextEncoding -> IO a) -> IO aforall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b>>=\TextEncodingenc->TextEncoding -> String -> (CStringLen -> IO a) -> IO aforall a. TextEncoding -> String -> (CStringLen -> IO a) -> IO aGHC.withCStringLenTextEncodingencStringsCStringLen -> IO af-- -- | Determines whether a character can be accurately encoded in a 'CString'.-- -- Unrepresentable characters are converted to '?' or their nearest visual equivalent.charIsRepresentable::Char->IOBoolcharIsRepresentable :: Char -> IO BoolcharIsRepresentableCharc=IO TextEncodinggetForeignEncodingIO TextEncoding -> (TextEncoding -> IO Bool) -> IO Boolforall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b>>=(TextEncoding -> Char -> IO Bool)-> Char -> TextEncoding -> IO Boolforall a b c. (a -> b -> c) -> b -> a -> cflipTextEncoding -> Char -> IO BoolGHC.charIsRepresentableCharc-- single byte characters-- --------------------------   ** NOTE: These routines don't handle conversions! **-- | Convert a C byte, representing a Latin-1 character, to the corresponding-- Haskell character.castCCharToChar::CChar->CharcastCCharToChar :: CChar -> CharcastCCharToCharCCharch=Int -> CharunsafeChr(Word8 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegral(CChar -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegralCCharch::Word8))-- | Convert a Haskell character to a C character.-- This function is only safe on the first 256 characters.castCharToCChar::Char->CCharcastCharToCChar :: Char -> CCharcastCharToCCharCharch=Int -> CCharforall a b. (Integral a, Num b) => a -> bfromIntegral(Char -> IntordCharch)-- | Convert a C @unsigned char@, representing a Latin-1 character, to-- the corresponding Haskell character.castCUCharToChar::CUChar->CharcastCUCharToChar :: CUChar -> CharcastCUCharToCharCUCharch=Int -> CharunsafeChr(Word8 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegral(CUChar -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegralCUCharch::Word8))-- | Convert a Haskell character to a C @unsigned char@.-- This function is only safe on the first 256 characters.castCharToCUChar::Char->CUCharcastCharToCUChar :: Char -> CUCharcastCharToCUCharCharch=Int -> CUCharforall a b. (Integral a, Num b) => a -> bfromIntegral(Char -> IntordCharch)-- | Convert a C @signed char@, representing a Latin-1 character, to the-- corresponding Haskell character.castCSCharToChar::CSChar->CharcastCSCharToChar :: CSChar -> CharcastCSCharToCharCSCharch=Int -> CharunsafeChr(Word8 -> Intforall a b. (Integral a, Num b) => a -> bfromIntegral(CSChar -> Word8forall a b. (Integral a, Num b) => a -> bfromIntegralCSCharch::Word8))-- | Convert a Haskell character to a C @signed char@.-- This function is only safe on the first 256 characters.castCharToCSChar::Char->CSCharcastCharToCSChar :: Char -> CSCharcastCharToCSCharCharch=Int -> CSCharforall a b. (Integral a, Num b) => a -> bfromIntegral(Char -> IntordCharch)-- | Marshal a NUL terminated C string into a Haskell string.--peekCAString::CString->IOStringpeekCAString :: CString -> IO StringpeekCAStringCStringcp=doIntl<-CChar -> CString -> IO Intforall a. (Storable a, Eq a) => a -> Ptr a -> IO IntlengthArray0CCharnULCStringcpifIntlInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<=Int0thenString -> IO Stringforall (m :: * -> *) a. Monad m => a -> m areturnString""elseString -> Int -> IO StringloopString""(IntlInt -> Int -> Intforall a. Num a => a -> a -> a-Int1)whereloop :: String -> Int -> IO StringloopStringsInti=doCCharxval<-CString -> Int -> IO CCharforall a. Storable a => Ptr a -> Int -> IO apeekElemOffCStringcpIntiletval :: Charval=CChar -> CharcastCCharToCharCCharxvalCharvalChar -> IO String -> IO String`seq`ifIntiInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<=Int0thenString -> IO Stringforall (m :: * -> *) a. Monad m => a -> m areturn(CharvalChar -> String -> Stringforall a. a -> [a] -> [a]:Strings)elseString -> Int -> IO Stringloop(CharvalChar -> String -> Stringforall a. a -> [a] -> [a]:Strings)(IntiInt -> Int -> Intforall a. Num a => a -> a -> a-Int1)-- | Marshal a C string with explicit length into a Haskell string.--peekCAStringLen::CStringLen->IOStringpeekCAStringLen :: CStringLen -> IO StringpeekCAStringLen(CStringcp,Intlen)|IntlenInt -> Int -> Boolforall a. Ord a => a -> a -> Bool<=Int0=String -> IO Stringforall (m :: * -> *) a. Monad m => a -> m areturnString""-- being (too?) nice.|Boolotherwise=String -> Int -> IO Stringloop[](IntlenInt -> Int -> Intforall a. Num a => a -> a -> a-Int1)whereloop :: String -> Int -> IO StringloopStringaccInti=doCCharxval<-CString -> Int -> IO CCharforall a. Storable a => Ptr a -> Int -> IO apeekElemOffCStringcpIntiletval :: Charval=CChar -> CharcastCCharToCharCCharxval-- blow away the coercion ASAP.if(CharvalChar -> Bool -> Bool`seq`(IntiInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Int0))thenString -> IO Stringforall (m :: * -> *) a. Monad m => a -> m areturn(CharvalChar -> String -> Stringforall a. a -> [a] -> [a]:Stringacc)elseString -> Int -> IO Stringloop(CharvalChar -> String -> Stringforall a. a -> [a] -> [a]:Stringacc)(IntiInt -> Int -> Intforall a. Num a => a -> a -> a-Int1)-- | Marshal a Haskell string into a NUL terminated C string.---- * the Haskell string may /not/ contain any NUL characters---- * new storage is allocated for the C string and must be--   explicitly freed using 'Foreign.Marshal.Alloc.free' or--   'Foreign.Marshal.Alloc.finalizerFree'.--newCAString::String->IOCStringnewCAString :: String -> IO CStringnewCAStringStringstr=doCStringptr<-Int -> IO CStringforall a. Storable a => Int -> IO (Ptr a)mallocArray0(String -> Intforall a. [a] -> IntlengthStringstr)letgo :: String -> Int -> IO ()go[]Intn=CString -> Int -> CChar -> IO ()forall a. Storable a => Ptr a -> Int -> a -> IO ()pokeElemOffCStringptrIntnCCharnULgo(Charc:Stringcs)Intn=doCString -> Int -> CChar -> IO ()forall a. Storable a => Ptr a -> Int -> a -> IO ()pokeElemOffCStringptrIntn(Char -> CCharcastCharToCCharCharc);String -> Int -> IO ()goStringcs(IntnInt -> Int -> Intforall a. Num a => a -> a -> a+Int1)String -> Int -> IO ()goStringstrInt0CString -> IO CStringforall (m :: * -> *) a. Monad m => a -> m areturnCStringptr-- | Marshal a Haskell string into a C string (ie, character array) with-- explicit length information.---- * new storage is allocated for the C string and must be--   explicitly freed using 'Foreign.Marshal.Alloc.free' or--   'Foreign.Marshal.Alloc.finalizerFree'.--newCAStringLen::String->IOCStringLennewCAStringLen :: String -> IO CStringLennewCAStringLenStringstr=doCStringptr<-Int -> IO CStringforall a. Storable a => Int -> IO (Ptr a)mallocArray0Intlenletgo :: String -> Int -> IO ()go[]Intn=IntnInt -> IO () -> IO ()`seq`() -> IO ()forall (m :: * -> *) a. Monad m => a -> m areturn()-- make it strict in ngo(Charc:Stringcs)Intn=doCString -> Int -> CChar -> IO ()forall a. Storable a => Ptr a -> Int -> a -> IO ()pokeElemOffCStringptrIntn(Char -> CCharcastCharToCCharCharc);String -> Int -> IO ()goStringcs(IntnInt -> Int -> Intforall a. Num a => a -> a -> a+Int1)String -> Int -> IO ()goStringstrInt0CStringLen -> IO CStringLenforall (m :: * -> *) a. Monad m => a -> m areturn(CStringptr,Intlen)wherelen :: Intlen=String -> Intforall a. [a] -> IntlengthStringstr-- | Marshal a Haskell string into a NUL terminated C string using temporary-- storage.---- * the Haskell string may /not/ contain any NUL characters---- * the memory is freed when the subcomputation terminates (either--   normally or via an exception), so the pointer to the temporary--   storage must /not/ be used after this.--withCAString::String->(CString->IOa)->IOawithCAString :: String -> (CString -> IO a) -> IO awithCAStringStringstrCString -> IO af=Int -> (CString -> IO a) -> IO aforall a b. Storable a => Int -> (Ptr a -> IO b) -> IO ballocaArray0(String -> Intforall a. [a] -> IntlengthStringstr)((CString -> IO a) -> IO a) -> (CString -> IO a) -> IO aforall a b. (a -> b) -> a -> b$\CStringptr->letgo :: String -> Int -> IO ()go[]Intn=CString -> Int -> CChar -> IO ()forall a. Storable a => Ptr a -> Int -> a -> IO ()pokeElemOffCStringptrIntnCCharnULgo(Charc:Stringcs)Intn=doCString -> Int -> CChar -> IO ()forall a. Storable a => Ptr a -> Int -> a -> IO ()pokeElemOffCStringptrIntn(Char -> CCharcastCharToCCharCharc);String -> Int -> IO ()goStringcs(IntnInt -> Int -> Intforall a. Num a => a -> a -> a+Int1)indoString -> Int -> IO ()goStringstrInt0CString -> IO afCStringptr-- | Marshal a Haskell string into a C string (ie, character array)-- in temporary storage, with explicit length information.---- * the memory is freed when the subcomputation terminates (either--   normally or via an exception), so the pointer to the temporary--   storage must /not/ be used after this.--withCAStringLen::String->(CStringLen->IOa)->IOawithCAStringLen :: String -> (CStringLen -> IO a) -> IO awithCAStringLenStringstrCStringLen -> IO af=Int -> (CString -> IO a) -> IO aforall a b. Storable a => Int -> (Ptr a -> IO b) -> IO ballocaArrayIntlen((CString -> IO a) -> IO a) -> (CString -> IO a) -> IO aforall a b. (a -> b) -> a -> b$\CStringptr->letgo :: String -> Int -> IO ()go[]Intn=IntnInt -> IO () -> IO ()`seq`() -> IO ()forall (m :: * -> *) a. Monad m => a -> m areturn()-- make it strict in ngo(Charc:Stringcs)Intn=doCString -> Int -> CChar -> IO ()forall a. Storable a => Ptr a -> Int -> a -> IO ()pokeElemOffCStringptrIntn(Char -> CCharcastCharToCCharCharc);String -> Int -> IO ()goStringcs(IntnInt -> Int -> Intforall a. Num a => a -> a -> a+Int1)indoString -> Int -> IO ()goStringstrInt0CStringLen -> IO af(CStringptr,Intlen)wherelen :: Intlen=String -> Intforall a. [a] -> IntlengthStringstr-- auxiliary definitions-- ------------------------ C's end of string character--nUL::CCharnUL :: CCharnUL=CChar0-- allocate an array to hold the list and pair it with the number of elementsnewArrayLen::Storablea=>[a]->IO(Ptra,Int)newArrayLen :: [a] -> IO (Ptr a, Int)newArrayLen[a]xs=doPtr aa<-[a] -> IO (Ptr a)forall a. Storable a => [a] -> IO (Ptr a)newArray[a]xs(Ptr a, Int) -> IO (Ptr a, Int)forall (m :: * -> *) a. Monad m => a -> m areturn(Ptr aa,[a] -> Intforall a. [a] -> Intlength[a]xs)------------------------------------------------------------------------------- Wide strings-- representation of wide strings in C-- ------------------------------------- | A C wide string is a reference to an array of C wide characters-- terminated by NUL.typeCWString=PtrCWchar-- | A wide character string with explicit length information in 'CWchar's-- instead of a terminating NUL (allowing NUL characters in the middle-- of the string).typeCWStringLen=(PtrCWchar,Int)-- | Marshal a NUL terminated C wide string into a Haskell string.--peekCWString::CWString->IOStringpeekCWString :: CWString -> IO StringpeekCWStringCWStringcp=do[CWchar]cs<-CWchar -> CWString -> IO [CWchar]forall a. (Storable a, Eq a) => a -> Ptr a -> IO [a]peekArray0CWcharwNULCWStringcpString -> IO Stringforall (m :: * -> *) a. Monad m => a -> m areturn([CWchar] -> StringcWcharsToChars[CWchar]cs)-- | Marshal a C wide string with explicit length into a Haskell string.--peekCWStringLen::CWStringLen->IOStringpeekCWStringLen :: CWStringLen -> IO StringpeekCWStringLen(CWStringcp,Intlen)=do[CWchar]cs<-Int -> CWString -> IO [CWchar]forall a. Storable a => Int -> Ptr a -> IO [a]peekArrayIntlenCWStringcpString -> IO Stringforall (m :: * -> *) a. Monad m => a -> m areturn([CWchar] -> StringcWcharsToChars[CWchar]cs)-- | Marshal a Haskell string into a NUL terminated C wide string.---- * the Haskell string may /not/ contain any NUL characters---- * new storage is allocated for the C wide string and must--   be explicitly freed using 'Foreign.Marshal.Alloc.free' or--   'Foreign.Marshal.Alloc.finalizerFree'.--newCWString::String->IOCWStringnewCWString :: String -> IO CWStringnewCWString=CWchar -> [CWchar] -> IO CWStringforall a. Storable a => a -> [a] -> IO (Ptr a)newArray0CWcharwNUL([CWchar] -> IO CWString)-> (String -> [CWchar]) -> String -> IO CWStringforall b c a. (b -> c) -> (a -> b) -> a -> c.String -> [CWchar]charsToCWchars-- | Marshal a Haskell string into a C wide string (ie, wide character array)-- with explicit length information.---- * new storage is allocated for the C wide string and must--   be explicitly freed using 'Foreign.Marshal.Alloc.free' or--   'Foreign.Marshal.Alloc.finalizerFree'.--newCWStringLen::String->IOCWStringLennewCWStringLen :: String -> IO CWStringLennewCWStringLenStringstr=[CWchar] -> IO CWStringLenforall a. Storable a => [a] -> IO (Ptr a, Int)newArrayLen(String -> [CWchar]charsToCWcharsStringstr)-- | Marshal a Haskell string into a NUL terminated C wide string using-- temporary storage.---- * the Haskell string may /not/ contain any NUL characters---- * the memory is freed when the subcomputation terminates (either--   normally or via an exception), so the pointer to the temporary--   storage must /not/ be used after this.--withCWString::String->(CWString->IOa)->IOawithCWString :: String -> (CWString -> IO a) -> IO awithCWString=CWchar -> [CWchar] -> (CWString -> IO a) -> IO aforall a b. Storable a => a -> [a] -> (Ptr a -> IO b) -> IO bwithArray0CWcharwNUL([CWchar] -> (CWString -> IO a) -> IO a)-> (String -> [CWchar]) -> String -> (CWString -> IO a) -> IO aforall b c a. (b -> c) -> (a -> b) -> a -> c.String -> [CWchar]charsToCWchars-- | Marshal a Haskell string into a C wide string (i.e. wide-- character array) in temporary storage, with explicit length-- information.---- * the memory is freed when the subcomputation terminates (either--   normally or via an exception), so the pointer to the temporary--   storage must /not/ be used after this.--withCWStringLen::String->(CWStringLen->IOa)->IOawithCWStringLen :: String -> (CWStringLen -> IO a) -> IO awithCWStringLenStringstrCWStringLen -> IO af=[CWchar] -> (Int -> CWString -> IO a) -> IO aforall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO bwithArrayLen(String -> [CWchar]charsToCWcharsStringstr)((Int -> CWString -> IO a) -> IO a)-> (Int -> CWString -> IO a) -> IO aforall a b. (a -> b) -> a -> b$\IntlenCWStringptr->CWStringLen -> IO af(CWStringptr,Intlen)-- auxiliary definitions-- ----------------------wNUL::CWcharwNUL :: CWcharwNUL=CWchar0cWcharsToChars::[CWchar]->[Char]charsToCWchars::[Char]->[CWchar]#if defined(mingw32_HOST_OS)-- On Windows, wchar_t is 16 bits wide and CWString uses the UTF-16 encoding.-- coding errors generate Chars in the surrogate rangecWcharsToChars=mapchr.fromUTF16.mapfromIntegralwherefromUTF16(c1:c2:wcs)|0xd800<=c1&&c1<=0xdbff&&0xdc00<=c2&&c2<=0xdfff=((c1-0xd800)*0x400+(c2-0xdc00)+0x10000):fromUTF16wcsfromUTF16(c:wcs)=c:fromUTF16wcsfromUTF16[]=[]charsToCWchars=foldrutf16Char[].mapordwhereutf16Charcwcs|c<0x10000=fromIntegralc:wcs|otherwise=letc'=c-0x10000infromIntegral(c'`div`0x400+0xd800):fromIntegral(c'`mod`0x400+0xdc00):wcs#else /* !mingw32_HOST_OS */cWcharsToChars :: [CWchar] -> StringcWcharsToChars[CWchar]xs=(CWchar -> Char) -> [CWchar] -> Stringforall a b. (a -> b) -> [a] -> [b]mapCWchar -> CharcastCWcharToChar[CWchar]xscharsToCWchars :: String -> [CWchar]charsToCWcharsStringxs=(Char -> CWchar) -> String -> [CWchar]forall a b. (a -> b) -> [a] -> [b]mapChar -> CWcharcastCharToCWcharStringxs-- These conversions only make sense if __STDC_ISO_10646__ is defined-- (meaning that wchar_t is ISO 10646, aka Unicode)castCWcharToChar::CWchar->CharcastCWcharToChar :: CWchar -> CharcastCWcharToCharCWcharch=Int -> Charchr(CWchar -> Intforall a b. (Integral a, Num b) => a -> bfromIntegralCWcharch)castCharToCWchar::Char->CWcharcastCharToCWchar :: Char -> CWcharcastCharToCWcharCharch=Int -> CWcharforall a b. (Integral a, Num b) => a -> bfromIntegral(Char -> IntordCharch)#endif /* !mingw32_HOST_OS */

[8]ページ先頭

©2009-2025 Movatter.jp