{-# LANGUAGE GADTs #-}{-# LANGUAGE RankNTypes #-}{-# LANGUAGE TypeOperators #-}-- | @since 2.2.0moduleDistribution.Utils.IOData(-- * 'IOData' & 'IODataMode' typeIOData (..),IODataMode (..),KnownIODataMode (..),withIOData ,null ,hPutContents )whereimportqualifiedData.ByteString.LazyasLBSimportDistribution.Compat.Preludehiding(null)importqualifiedSystem.IOimportqualifiedPrelude-- | Represents either textual or binary data passed via I/O functions-- which support binary/text mode---- @since 2.2dataIOData =-- | How Text gets encoded is usually locale-dependent.IODataText String|-- | Raw binary which gets read/written in binary mode.IODataBinary LBS.ByteString-- | Applies a function polymorphic over 'IODataMode' to an 'IOData' value.withIOData ::IOData ->(forallmode .IODataMode mode ->mode ->r )->r withIOData :: forall r.
IOData -> (forall mode. IODataMode mode -> mode -> r) -> r
withIOData (IODataText String
str )forall mode. IODataMode mode -> mode -> r
k =IODataMode String -> String -> r
forall mode. IODataMode mode -> mode -> r
k IODataMode String
IODataModeText String
str withIOData (IODataBinary ByteString
lbs )forall mode. IODataMode mode -> mode -> r
k =IODataMode ByteString -> ByteString -> r
forall mode. IODataMode mode -> mode -> r
k IODataMode ByteString
IODataModeBinary ByteString
lbs -- | Test whether 'IOData' is emptynull ::IOData ->Boolnull :: IOData -> Bool
null (IODataText String
s )=String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.nullString
s null (IODataBinary ByteString
b )=ByteString -> Bool
LBS.nullByteString
b instanceNFDataIOData wherernf :: IOData -> ()
rnf (IODataText String
s )=String -> ()
forall a. NFData a => a -> ()
rnfString
s rnf(IODataBinary ByteString
lbs )=ByteString -> ()
forall a. NFData a => a -> ()
rnfByteString
lbs -- | @since 2.2classNFDatamode =>KnownIODataMode mode where-- | 'IOData' Wrapper for 'System.IO.hGetContents'---- __Note__: This operation uses lazy I/O. Use 'NFData' to force all-- data to be read and consequently the internal file handle to be-- closed.hGetIODataContents ::System.IO.Handle->Prelude.IOmode toIOData ::mode ->IOData iodataMode ::IODataMode mode -- | Phantom-typed GADT representation of the mode of 'IOData', containing no-- other data.---- @since 3.2dataIODataMode mode whereIODataModeText ::IODataMode StringIODataModeBinary ::IODataMode LBS.ByteStringinstancea ~Char=>KnownIODataMode [a ]wherehGetIODataContents :: Handle -> IO [a]
hGetIODataContents Handle
h =doHandle -> Bool -> IO ()
System.IO.hSetBinaryModeHandle
h Bool
FalseHandle -> IO String
System.IO.hGetContentsHandle
h toIOData :: [a] -> IOData
toIOData =[a] -> IOData
String -> IOData
IODataText iodataMode :: IODataMode [a]
iodataMode =IODataMode [a]
IODataMode String
IODataModeText instanceKnownIODataMode LBS.ByteStringwherehGetIODataContents :: Handle -> IO ByteString
hGetIODataContents Handle
h =doHandle -> Bool -> IO ()
System.IO.hSetBinaryModeHandle
h Bool
TrueHandle -> IO ByteString
LBS.hGetContentsHandle
h toIOData :: ByteString -> IOData
toIOData =ByteString -> IOData
IODataBinary iodataMode :: IODataMode ByteString
iodataMode =IODataMode ByteString
IODataModeBinary -- | 'IOData' Wrapper for 'System.IO.hPutStr' and 'System.IO.hClose'---- This is the dual operation to 'hGetIODataContents',-- and consequently the handle is closed with `hClose`.---- /Note:/ this performs lazy-IO.---- @since 2.2hPutContents ::System.IO.Handle->IOData ->Prelude.IO()hPutContents :: Handle -> IOData -> IO ()
hPutContents Handle
h (IODataText String
c )=doHandle -> Bool -> IO ()
System.IO.hSetBinaryModeHandle
h Bool
FalseHandle -> String -> IO ()
System.IO.hPutStrHandle
h String
c Handle -> IO ()
System.IO.hCloseHandle
h hPutContents Handle
h (IODataBinary ByteString
c )=doHandle -> Bool -> IO ()
System.IO.hSetBinaryModeHandle
h Bool
TrueHandle -> ByteString -> IO ()
LBS.hPutStrHandle
h ByteString
c Handle -> IO ()
System.IO.hCloseHandle
h 

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