ListLike-4.7.8.2: Generalized support for list-like structures
CopyrightCopyright (C) 2007 John Goerzen
LicenseBSD3
MaintainerDavid Fox <dsf@seereason.com>, Andreas Abel
Stabilitystable
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.ListLike.IO

Description

String-like functions

Written by John Goerzen, jgoerzen@complete.org

Synopsis

Documentation

class ListLike full item => ListLikeIO full item | full -> item where Source #

An extension to ListLike for those data types that support I/O. These functions mirror those in System.IO for the most part. They also share the same names; see the comments in Data.ListLike for help importing them.

Note that some types may not be capable of lazy reading or writing. Therefore, the usual semantics of System.IO functions regarding laziness may or may not be available from a particular implementation.

Minimal complete definition:

  • hGetLine
  • hGetContents
  • hGet
  • hGetNonBlocking
  • hPutStr

Minimal complete definition

hGetLine, hGetContents, hGet, hGetNonBlocking, hPutStr

Methods

hGetLine :: Handle -> IO full Source #

Reads a line from the specified handle

hGetContents :: Handle -> IO full Source #

Read entire handle contents. May be done lazily like hGetContents.

hGet :: Handle -> Int -> IO full Source #

Read specified number of bytes. See hGet for particular semantics.

hGetNonBlocking :: Handle -> Int -> IO full Source #

Non-blocking read. See hGetNonBlocking for more.

hPutStr :: Handle -> full -> IO () Source #

Writing entire data.

hPutStrLn :: Handle -> full -> IO () Source #

Write data plus newline character.

getLine :: IO full Source #

Read one line

getContents :: IO full Source #

Read entire content from stdin. See hGetContents.

putStr :: full -> IO () Source #

Write data to stdout.

putStrLn :: full -> IO () Source #

Write data plus newline character to stdout.

interact :: (full -> full) -> IO () Source #

Interact with stdin and stdout by using a function to transform input to output. May be lazy. See interact for more.

readFile :: FilePath -> IO full Source #

Read file. May be lazy.

writeFile :: FilePath -> full -> IO () Source #

Write data to file.

appendFile :: FilePath -> full -> IO () Source #

Append data to file.

Instances

Instances details
ListLikeIO CharString Char Source # 
Instance details

Defined in Data.ListLike.CharString

Methods

hGetLine :: Handle -> IO CharString Source #

hGetContents :: Handle -> IO CharString Source #

hGet :: Handle -> Int -> IO CharString Source #

hGetNonBlocking :: Handle -> Int -> IO CharString Source #

hPutStr :: Handle -> CharString -> IO () Source #

hPutStrLn :: Handle -> CharString -> IO () Source #

getLine :: IO CharString Source #

getContents :: IO CharString Source #

putStr :: CharString -> IO () Source #

putStrLn :: CharString -> IO () Source #

interact :: (CharString -> CharString) -> IO () Source #

readFile :: FilePath -> IO CharString Source #

writeFile :: FilePath -> CharString -> IO () Source #

appendFile :: FilePath -> CharString -> IO () Source #

ListLikeIO CharStringLazy Char Source # 
Instance details

Defined in Data.ListLike.CharString

Methods

hGetLine :: Handle -> IO CharStringLazy Source #

hGetContents :: Handle -> IO CharStringLazy Source #

hGet :: Handle -> Int -> IO CharStringLazy Source #

hGetNonBlocking :: Handle -> Int -> IO CharStringLazy Source #

hPutStr :: Handle -> CharStringLazy -> IO () Source #

hPutStrLn :: Handle -> CharStringLazy -> IO () Source #

getLine :: IO CharStringLazy Source #

getContents :: IO CharStringLazy Source #

putStr :: CharStringLazy -> IO () Source #

putStrLn :: CharStringLazy -> IO () Source #

interact :: (CharStringLazy -> CharStringLazy) -> IO () Source #

readFile :: FilePath -> IO CharStringLazy Source #

writeFile :: FilePath -> CharStringLazy -> IO () Source #

appendFile :: FilePath -> CharStringLazy -> IO () Source #

ListLikeIO Chars Char Source # 
Instance details

Defined in Data.ListLike.Chars

Methods

hGetLine :: Handle -> IO Chars Source #

hGetContents :: Handle -> IO Chars Source #

hGet :: Handle -> Int -> IO Chars Source #

hGetNonBlocking :: Handle -> Int -> IO Chars Source #

hPutStr :: Handle -> Chars -> IO () Source #

hPutStrLn :: Handle -> Chars -> IO () Source #

getLine :: IO Chars Source #

getContents :: IO Chars Source #

putStr :: Chars -> IO () Source #

putStrLn :: Chars -> IO () Source #

interact :: (Chars -> Chars) -> IO () Source #

readFile :: FilePath -> IO Chars Source #

writeFile :: FilePath -> Chars -> IO () Source #

appendFile :: FilePath -> Chars -> IO () Source #

ListLikeIO ByteString Word8 Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

hGetLine :: Handle -> IO ByteString Source #

hGetContents :: Handle -> IO ByteString Source #

hGet :: Handle -> Int -> IO ByteString Source #

hGetNonBlocking :: Handle -> Int -> IO ByteString Source #

hPutStr :: Handle -> ByteString -> IO () Source #

hPutStrLn :: Handle -> ByteString -> IO () Source #

getLine :: IO ByteString Source #

getContents :: IO ByteString Source #

putStr :: ByteString -> IO () Source #

putStrLn :: ByteString -> IO () Source #

interact :: (ByteString -> ByteString) -> IO () Source #

readFile :: FilePath -> IO ByteString Source #

writeFile :: FilePath -> ByteString -> IO () Source #

appendFile :: FilePath -> ByteString -> IO () Source #

ListLikeIO ByteString Word8 Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

hGetLine :: Handle -> IO ByteString Source #

hGetContents :: Handle -> IO ByteString Source #

hGet :: Handle -> Int -> IO ByteString Source #

hGetNonBlocking :: Handle -> Int -> IO ByteString Source #

hPutStr :: Handle -> ByteString -> IO () Source #

hPutStrLn :: Handle -> ByteString -> IO () Source #

getLine :: IO ByteString Source #

getContents :: IO ByteString Source #

putStr :: ByteString -> IO () Source #

putStrLn :: ByteString -> IO () Source #

interact :: (ByteString -> ByteString) -> IO () Source #

readFile :: FilePath -> IO ByteString Source #

writeFile :: FilePath -> ByteString -> IO () Source #

appendFile :: FilePath -> ByteString -> IO () Source #

ListLikeIO Text Char Source # 
Instance details

Defined in Data.ListLike.Text.Text

Methods

hGetLine :: Handle -> IO Text Source #

hGetContents :: Handle -> IO Text Source #

hGet :: Handle -> Int -> IO Text Source #

hGetNonBlocking :: Handle -> Int -> IO Text Source #

hPutStr :: Handle -> Text -> IO () Source #

hPutStrLn :: Handle -> Text -> IO () Source #

getLine :: IO Text Source #

getContents :: IO Text Source #

putStr :: Text -> IO () Source #

putStrLn :: Text -> IO () Source #

interact :: (Text -> Text) -> IO () Source #

readFile :: FilePath -> IO Text Source #

writeFile :: FilePath -> Text -> IO () Source #

appendFile :: FilePath -> Text -> IO () Source #

ListLikeIO Builder Char Source # 
Instance details

Defined in Data.ListLike.Text.Builder

Methods

hGetLine :: Handle -> IO Builder Source #

hGetContents :: Handle -> IO Builder Source #

hGet :: Handle -> Int -> IO Builder Source #

hGetNonBlocking :: Handle -> Int -> IO Builder Source #

hPutStr :: Handle -> Builder -> IO () Source #

hPutStrLn :: Handle -> Builder -> IO () Source #

getLine :: IO Builder Source #

getContents :: IO Builder Source #

putStr :: Builder -> IO () Source #

putStrLn :: Builder -> IO () Source #

interact :: (Builder -> Builder) -> IO () Source #

readFile :: FilePath -> IO Builder Source #

writeFile :: FilePath -> Builder -> IO () Source #

appendFile :: FilePath -> Builder -> IO () Source #

ListLikeIO Text Char Source # 
Instance details

Defined in Data.ListLike.Text.TextLazy

Methods

hGetLine :: Handle -> IO Text Source #

hGetContents :: Handle -> IO Text Source #

hGet :: Handle -> Int -> IO Text Source #

hGetNonBlocking :: Handle -> Int -> IO Text Source #

hPutStr :: Handle -> Text -> IO () Source #

hPutStrLn :: Handle -> Text -> IO () Source #

getLine :: IO Text Source #

getContents :: IO Text Source #

putStr :: Text -> IO () Source #

putStrLn :: Text -> IO () Source #

interact :: (Text -> Text) -> IO () Source #

readFile :: FilePath -> IO Text Source #

writeFile :: FilePath -> Text -> IO () Source #

appendFile :: FilePath -> Text -> IO () Source #

ListLikeIO String Char Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

hGetLine :: Handle -> IO String Source #

hGetContents :: Handle -> IO String Source #

hGet :: Handle -> Int -> IO String Source #

hGetNonBlocking :: Handle -> Int -> IO String Source #

hPutStr :: Handle -> String -> IO () Source #

hPutStrLn :: Handle -> String -> IO () Source #

getLine :: IO String Source #

getContents :: IO String Source #

putStr :: String -> IO () Source #

putStrLn :: String -> IO () Source #

interact :: (String -> String) -> IO () Source #

readFile :: FilePath -> IO String Source #

writeFile :: FilePath -> String -> IO () Source #

appendFile :: FilePath -> String -> IO () Source #

ListLikeIO (Seq Char) Char Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

hGetLine :: Handle -> IO (Seq Char) Source #

hGetContents :: Handle -> IO (Seq Char) Source #

hGet :: Handle -> Int -> IO (Seq Char) Source #

hGetNonBlocking :: Handle -> Int -> IO (Seq Char) Source #

hPutStr :: Handle -> Seq Char -> IO () Source #

hPutStrLn :: Handle -> Seq Char -> IO () Source #

getLine :: IO (Seq Char) Source #

getContents :: IO (Seq Char) Source #

putStr :: Seq Char -> IO () Source #

putStrLn :: Seq Char -> IO () Source #

interact :: (Seq Char -> Seq Char) -> IO () Source #

readFile :: FilePath -> IO (Seq Char) Source #

writeFile :: FilePath -> Seq Char -> IO () Source #

appendFile :: FilePath -> Seq Char -> IO () Source #

ListLikeIO (UTF8 ByteString) Char Source # 
Instance details

Defined in Data.ListLike.UTF8

Methods

hGetLine :: Handle -> IO (UTF8 ByteString) Source #

hGetContents :: Handle -> IO (UTF8 ByteString) Source #

hGet :: Handle -> Int -> IO (UTF8 ByteString) Source #

hGetNonBlocking :: Handle -> Int -> IO (UTF8 ByteString) Source #

hPutStr :: Handle -> UTF8 ByteString -> IO () Source #

hPutStrLn :: Handle -> UTF8 ByteString -> IO () Source #

getLine :: IO (UTF8 ByteString) Source #

getContents :: IO (UTF8 ByteString) Source #

putStr :: UTF8 ByteString -> IO () Source #

putStrLn :: UTF8 ByteString -> IO () Source #

interact :: (UTF8 ByteString -> UTF8 ByteString) -> IO () Source #

readFile :: FilePath -> IO (UTF8 ByteString) Source #

writeFile :: FilePath -> UTF8 ByteString -> IO () Source #

appendFile :: FilePath -> UTF8 ByteString -> IO () Source #

ListLikeIO (UTF8 ByteString) Char Source # 
Instance details

Defined in Data.ListLike.UTF8

Methods

hGetLine :: Handle -> IO (UTF8 ByteString) Source #

hGetContents :: Handle -> IO (UTF8 ByteString) Source #

hGet :: Handle -> Int -> IO (UTF8 ByteString) Source #

hGetNonBlocking :: Handle -> Int -> IO (UTF8 ByteString) Source #

hPutStr :: Handle -> UTF8 ByteString -> IO () Source #

hPutStrLn :: Handle -> UTF8 ByteString -> IO () Source #

getLine :: IO (UTF8 ByteString) Source #

getContents :: IO (UTF8 ByteString) Source #

putStr :: UTF8 ByteString -> IO () Source #

putStrLn :: UTF8 ByteString -> IO () Source #

interact :: (UTF8 ByteString -> UTF8 ByteString) -> IO () Source #

readFile :: FilePath -> IO (UTF8 ByteString) Source #

writeFile :: FilePath -> UTF8 ByteString -> IO () Source #

appendFile :: FilePath -> UTF8 ByteString -> IO () Source #

(Integral i, Ix i) => ListLikeIO (Array i Char) Char Source # 
Instance details

Defined in Data.ListLike.Instances

Methods

hGetLine :: Handle -> IO (Array i Char) Source #

hGetContents :: Handle -> IO (Array i Char) Source #

hGet :: Handle -> Int -> IO (Array i Char) Source #

hGetNonBlocking :: Handle -> Int -> IO (Array i Char) Source #

hPutStr :: Handle -> Array i Char -> IO () Source #

hPutStrLn :: Handle -> Array i Char -> IO () Source #

getLine :: IO (Array i Char) Source #

getContents :: IO (Array i Char) Source #

putStr :: Array i Char -> IO () Source #

putStrLn :: Array i Char -> IO () Source #

interact :: (Array i Char -> Array i Char) -> IO () Source #

readFile :: FilePath -> IO (Array i Char) Source #

writeFile :: FilePath -> Array i Char -> IO () Source #

appendFile :: FilePath -> Array i Char -> IO () Source #