User Tools

Site Tools


codesnippets:filesystemioandstreams

Filesystem IO and streams

  • example:
    • code, module FileSystem
      {-|
      Description : is to provides a generalised, abstract, and save interface to the files system.
      Copyright   : (c) Jörg K.-H. W. Brüggmann, 2021
      License     : CC0 1.0 Universal
      Maintainer  : ...@...
      Stability   : experimental
      Portability : POSIX
       
      * traits:
       
          * abstractions:
       
              * uniform types for identification of input and output streams ('Inp', 'Out')
       
              * higher order functions encapsulated in data types ('DataReader', 'DataWriter') are applied on streams
       
          * can not cause error by "invalid characters", as long as the stream handler functions do not cause them
       
          * supports the following file system features:
       
              * deletion of files
       
              * processing (read and write at once) and writing streams
       
          * supports the following data types:
       
              * Octets
       
      NOTE: There is no isolated read function like the write function, because this would lead to errors like "illegal operation (delayed read on closed handle)".
      Background: The function hGetContents needs an open file handle, that may be closed before the lazy String has been evaluated.
       
      * example
       
          @
      import qualified FileSystem as FS
      import qualified System.IO as SysIo
       
      main :: IO ()
      main = 
              FS.processData
                  (FS.DataReader (FS.FileInp ".\\test\\a.txt") SysIo.hGetContents)
                  [
                      FS.DataWriter (FS.FileOut ".\\test\\b.txt") SysIo.hPutStr, 
                      FS.DataWriter FS.StdOut SysIo.hPutStr, 
                      FS.DataWriter FS.StdErr SysIo.hPutStr
                  ]
          @
       
          * copies the file "a.txt" in ".\test" to "b.txt"
          * sends the file content of "a.txt" also to 'stdout', and 'stderr'
          * will not cause uncaught exception caused by "invalid characters"
      -}
      module FileSystem (
              Inp(..), 
              Out(..), 
              DataReader(..), 
              DataWriter(..), 
              removeFileIfExists, 
              processData, 
              writeToData
          ) where
       
      import qualified System.IO as SysIo
      import qualified System.IO.Error as Err
      import qualified Control.Exception as Excp
      import qualified System.Directory as Dir
       
      -- input streams
      data Inp = 
         StdInp
       | FileInp String
       deriving (Eq, Show)
       
      -- output streams
      data Out = 
         NullOut
       | StdOut
       | StdErr
       | FileOut String
       deriving (Eq, Show)
       
      removeFileIfExists :: FilePath -> IO ()
      removeFileIfExists fileName = Dir.removeFile fileName `Excp.catch` handleExists
          where
              handleExists :: Err.IOError -> IO ()
              handleExists e | Err.isDoesNotExistError e = return ()
                             | otherwise = Excp.throwIO e
       
      data DataReader s = 
          DataReader { 
              rinp :: Inp, 
              rfRead :: (SysIo.Handle -> IO s) }
       
      data DataWriter s = 
          DataWriter { 
              rout :: Out, 
              rfWrite :: (SysIo.Handle -> s -> IO ()) }
       
      processData :: (DataReader a) -> [DataWriter a] -> IO ()
      processData (DataReader StdInp f) lwrt = 
          do
              dt <- f SysIo.stdin
              processData' dt lwrt
      processData (DataReader (FileInp sFileName) f) lwrt = 
          do
              hFile <- SysIo.openFile sFileName SysIo.ReadMode
              dt <- f hFile
              processData' dt lwrt
              SysIo.hClose hFile
       
      processData' :: a -> [DataWriter a] -> IO ()
      processData' x [] = return ()
      processData' x (wrt:lrwrt) = 
          do
              writeToData wrt x
              processData' x lrwrt
       
      writeToData :: (DataWriter a) -> a -> IO ()
      writeToData (DataWriter NullOut _) _ = return ()
      writeToData (DataWriter StdOut f) x = f SysIo.stdout x
      writeToData (DataWriter StdErr f) x = f SysIo.stderr x
      writeToData (DataWriter (FileOut sFileName) f) x = 
          do
              hFile <- SysIo.openFile sFileName SysIo.WriteMode
              f hFile x
              SysIo.hClose hFile
    • code, use case of files system
      import qualified FileSystem as FS
      import qualified System.IO as SysIo
       
      main :: IO ()
      main = 
              FS.processData
                  (FS.DataReader (FS.FileInp ".\\test\\a.txt") SysIo.hGetContents)
                  [
                      FS.DataWriter (FS.FileOut ".\\test\\b.txt") SysIo.hPutStr, 
                      FS.DataWriter FS.StdOut SysIo.hPutStr, 
                      FS.DataWriter FS.StdErr SysIo.hPutStr
                  ]
    • compiles, error and warning free, with compiler: GHC 8.10.4, using compiler option -Wall
    • executes with output as file copy of “a.txt” to “b.txt”, stdout, and stderr
  • example, with conversions
    • code:
      import qualified FileSystem as FS
      import qualified System.IO as SysIo
      import qualified Data.Char as Ch
       
      main :: IO ()
      main = 
              FS.processData
                  (FS.DataReader (FS.FileInp ".\\test\\a.txt") hGetToUpper)
                  [
                      FS.DataWriter (FS.FileOut ".\\test\\b.txt") SysIo.hPutStr, 
                      FS.DataWriter FS.StdOut hPutToLower, 
                      FS.DataWriter FS.StdErr SysIo.hPutStr
                  ]
       
      hGetToUpper :: SysIo.Handle -> IO String
      hGetToUpper h = 
          do
              s <- SysIo.hGetContents h
              return (fmap Ch.toUpper s)
       
      hPutToLower :: SysIo.Handle -> String -> IO ()
      hPutToLower h s = SysIo.hPutStr h (fmap Ch.toLower s)
    • input, file “a.txt”
      The quick brown fox jumps over the lazy dog.
    • output, in terminal:
      the quick brown fox jumps over the lazy dog.
      THE QUICK BROWN FOX JUMPS OVER THE LAZY DOG.
    • output, file “b.txt”:
      THE QUICK BROWN FOX JUMPS OVER THE LAZY DOG.

This website uses cookies. By using the website, you agree with storing cookies on your computer. Also you acknowledge that you have read and understand our Privacy Policy. If you do not agree leave the website.More information about cookies
You could leave a comment if you were logged in.
codesnippets/filesystemioandstreams.txt · Last modified: by 127.0.0.1

Except where otherwise noted, content on this wiki is licensed under the following license: CC0 1.0 Universal
CC0 1.0 Universal Donate Powered by PHP Valid HTML5 Valid CSS Driven by DokuWiki