{-# LANGUAGE MultiParamTypeClasses
            ,FunctionalDependencies #-}


{-
Copyright (C) 2007 John Goerzen <jgoerzen@complete.org>

All rights reserved.

For license and copyright information, see the file COPYRIGHT

-}

{- |
   Module     : Data.ListLike.IO
   Copyright  : Copyright (C) 2007 John Goerzen
   License    : BSD3

   Maintainer : John Lato <jwlato@gmail.com>
   Stability  : provisional
   Portability: portable

String-like functions

Written by John Goerzen, jgoerzen\@complete.org
-}

module Data.ListLike.IO
    ( ListLikeIO(..)
    )
       where
import Prelude hiding (length, head, last, null, tail, map, filter, concat,
                       any, lookup, init, all, foldl, foldr, foldl1, foldr1,
                       maximum, minimum, iterate, span, break, takeWhile,
                       dropWhile, reverse, zip, zipWith, sequence,
                       sequence_, mapM, mapM_, concatMap, and, or, sum,
                       product, repeat, replicate, cycle, take, drop,
                       splitAt, elem, notElem, unzip, lines, words,
                       unlines, unwords, putStr, getContents)
import qualified System.IO as IO
import Data.ListLike.Base

{- | 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
-}
class (ListLike full item) => ListLikeIO full item | full -> item where
    {- | Reads a line from the specified handle -}
    hGetLine :: IO.Handle -> IO full

    -- | Read entire handle contents.  May be done lazily like
    -- 'System.IO.hGetContents'.
    hGetContents :: IO.Handle -> IO full

    -- | Read specified number of bytes.  See 'System.IO.hGet' for
    -- particular semantics.
    hGet :: IO.Handle -> Int -> IO full

    -- | Non-blocking read.  See 'System.IO.hGetNonBlocking' for more.
    hGetNonBlocking :: IO.Handle -> Int -> IO full

    -- | Writing entire data.
    hPutStr :: IO.Handle -> full -> IO ()

    -- | Write data plus newline character.
    hPutStrLn :: IO.Handle -> full -> IO ()
    hPutStrLn Handle
fp full
x =
        do Handle -> full -> IO ()
forall full item. ListLikeIO full item => Handle -> full -> IO ()
hPutStr Handle
fp full
x
           Handle -> String -> IO ()
IO.hPutStrLn Handle
fp String
""

    -- | Read one line
    getLine :: IO full
    getLine = Handle -> IO full
forall full item. ListLikeIO full item => Handle -> IO full
hGetLine Handle
IO.stdin

    -- | Read entire content from stdin.  See 'hGetContents'.
    getContents :: IO full
    getContents = Handle -> IO full
forall full item. ListLikeIO full item => Handle -> IO full
hGetContents Handle
IO.stdin

    -- | Write data to stdout.
    putStr :: full -> IO ()
    putStr = Handle -> full -> IO ()
forall full item. ListLikeIO full item => Handle -> full -> IO ()
hPutStr Handle
IO.stdout

    -- | Write data plus newline character to stdout.
    putStrLn :: full -> IO ()
    putStrLn = Handle -> full -> IO ()
forall full item. ListLikeIO full item => Handle -> full -> IO ()
hPutStrLn Handle
IO.stdout

    -- | Interact with stdin and stdout by using a function to transform
    -- input to output.  May be lazy.  See 'System.IO.interact' for more.
    interact :: (full -> full) -> IO ()
    interact full -> full
func =
        do full
c <- IO full
forall full item. ListLikeIO full item => IO full
getContents
           full -> IO ()
forall full item. ListLikeIO full item => full -> IO ()
putStr (full -> full
func full
c)

    -- | Read file.  May be lazy.
    readFile :: FilePath -> IO full
    readFile String
fn =
        do Handle
fp <- String -> IOMode -> IO Handle
IO.openFile String
fn IOMode
IO.ReadMode
           Handle -> IO full
forall full item. ListLikeIO full item => Handle -> IO full
hGetContents Handle
fp

    -- | Write data to file.
    writeFile :: FilePath -> full -> IO ()
    writeFile String
fn full
x =
        do Handle
fp <- String -> IOMode -> IO Handle
IO.openFile String
fn IOMode
IO.WriteMode
           Handle -> full -> IO ()
forall full item. ListLikeIO full item => Handle -> full -> IO ()
hPutStr Handle
fp full
x
           Handle -> IO ()
IO.hClose Handle
fp

    -- | Append data to file.
    appendFile :: FilePath -> full -> IO ()
    appendFile String
fn full
x =
        do Handle
fp <- String -> IOMode -> IO Handle
IO.openFile String
fn IOMode
IO.AppendMode
           Handle -> full -> IO ()
forall full item. ListLikeIO full item => Handle -> full -> IO ()
hPutStr Handle
fp full
x
           Handle -> IO ()
IO.hClose Handle
fp