Skip to content

Commit

Permalink
Don't use CPP
Browse files Browse the repository at this point in the history
  • Loading branch information
sol committed Jul 2, 2023
1 parent 52910b7 commit 174705a
Show file tree
Hide file tree
Showing 3 changed files with 133 additions and 98 deletions.
82 changes: 0 additions & 82 deletions System/File/Common.hs

This file was deleted.

84 changes: 80 additions & 4 deletions System/File/OsPath.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
{-# LANGUAGE CPP #-}

module System.File.OsPath where

import qualified System.File.Platform as P
Expand All @@ -12,8 +10,86 @@ import System.OsString.Internal.Types
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL

#define FILE_PATH OsPath
#include "Common.hs"
-- | Like 'openFile', but open the file in binary mode.
-- On Windows, reading a file in text mode (which is the default)
-- will translate CRLF to LF, and writing will translate LF to CRLF.
-- This is usually what you want with text files. With binary files
-- this is undesirable; also, as usual under Microsoft operating systems,
-- text mode treats control-Z as EOF. Binary mode turns off all special
-- treatment of end-of-line and end-of-file characters.
-- (See also 'System.IO.hSetBinaryMode'.)

-- On POSIX systems, 'openBinaryFile' is an /interruptible operation/ as
-- described in "Control.Exception".
openBinaryFile :: OsPath -> IOMode -> IO Handle
openBinaryFile fp iomode = do
h <- openFile fp iomode
hSetBinaryMode h True
pure h

-- | Run an action on a file.
--
-- The 'Handle' is automatically closed afther the action.
withFile :: OsPath -> IOMode -> (Handle -> IO r) -> IO r
withFile fp iomode action = bracket
(openFile fp iomode)
hClose
action

withBinaryFile :: OsPath -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile fp iomode action = bracket
(openBinaryFile fp iomode)
hClose
action

-- | Run an action on a file.
--
-- The 'Handle' is not automatically closed to allow lazy IO. Use this
-- with caution.
withFile'
:: OsPath -> IOMode -> (Handle -> IO r) -> IO r
withFile' fp iomode action = do
h <- openFile fp iomode
action h

withBinaryFile'
:: OsPath -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile' fp iomode action = do
h <- openBinaryFile fp iomode
action h

-- | The 'readFile' function reads a file and returns the contents of the file
-- as a 'ByteString'. The file is read lazily, on demand.
readFile :: OsPath -> IO BSL.ByteString
readFile fp = withFile' fp ReadMode BSL.hGetContents

-- | The 'readFile'' function reads a file and returns the contents of the file
-- as a 'ByteString'. The file is fully read before being returned.
readFile'
:: OsPath -> IO BS.ByteString
readFile' fp = withFile fp ReadMode BS.hGetContents

-- | The computation 'writeFile' @file str@ function writes the lazy 'ByteString' @str@,
-- to the file @file@.
writeFile :: OsPath -> BSL.ByteString -> IO ()
writeFile fp contents = withFile fp WriteMode (`BSL.hPut` contents)

-- | The computation 'writeFile' @file str@ function writes the strict 'ByteString' @str@,
-- to the file @file@.
writeFile'
:: OsPath -> BS.ByteString -> IO ()
writeFile' fp contents = withFile fp WriteMode (`BS.hPut` contents)

-- | The computation 'appendFile' @file str@ function appends the lazy 'ByteString' @str@,
-- to the file @file@.
appendFile :: OsPath -> BSL.ByteString -> IO ()
appendFile fp contents = withFile fp AppendMode (`BSL.hPut` contents)

-- | The computation 'appendFile' @file str@ function appends the strict 'ByteString' @str@,
-- to the file @file@.
appendFile'
:: OsPath -> BS.ByteString -> IO ()
appendFile' fp contents = withFile fp AppendMode (`BS.hPut` contents)

-- | Open a file and return the 'Handle'.
openFile :: OsPath -> IOMode -> IO Handle
Expand Down
65 changes: 53 additions & 12 deletions System/File/PlatformPath.hs
Original file line number Diff line number Diff line change
@@ -1,24 +1,65 @@
{-# LANGUAGE CPP #-}

module System.File.PlatformPath where

import qualified System.File.Platform as P

import Control.Exception (bracket)
import System.IO (IOMode(..), Handle, hSetBinaryMode, hClose)
import System.IO (IOMode(..), Handle)
import System.OsPath.Types

import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL

#define FILE_PATH PlatformPath
#include "Common.hs"
import qualified System.File.OsPath as OsPath
import System.OsString.Internal.Types

import Data.Coerce (coerce)

-- | Same as `OsPath.openBinaryFile`, takes a `PlatformPath` instead of an `OsPath`.
openBinaryFile :: PlatformPath -> IOMode -> IO Handle
openBinaryFile = OsPath.openBinaryFile . coerce

-- | Same as `OsPath.withFile`, takes a `PlatformPath` instead of an `OsPath`.
withFile :: PlatformPath -> IOMode -> (Handle -> IO r) -> IO r
withFile = OsPath.withFile . coerce

-- | Same as `OsPath.withBinaryFile`, takes a `PlatformPath` instead of an `OsPath`.
withBinaryFile :: PlatformPath -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile = OsPath.withBinaryFile . coerce

-- | Same as `OsPath.withFile'`, takes a `PlatformPath` instead of an `OsPath`.
withFile' :: PlatformPath -> IOMode -> (Handle -> IO r) -> IO r
withFile' = OsPath.withFile' . coerce

-- | Same as `OsPath.withBinaryFile'`, takes a `PlatformPath` instead of an `OsPath`.
withBinaryFile' :: PlatformPath -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile' = OsPath.withBinaryFile' . coerce

-- | Open a file and return the 'Handle'.
-- | Same as `OsPath.readFile`, takes a `PlatformPath` instead of an `OsPath`.
readFile :: PlatformPath -> IO BSL.ByteString
readFile = OsPath.readFile . coerce

-- | Same as `OsPath.readFile'`, takes a `PlatformPath` instead of an `OsPath`.
readFile' :: PlatformPath -> IO BS.ByteString
readFile' = OsPath.readFile' . coerce

-- | Same as `OsPath.writeFile`, takes a `PlatformPath` instead of an `OsPath`.
writeFile :: PlatformPath -> BSL.ByteString -> IO ()
writeFile = OsPath.writeFile . coerce

-- | Same as `OsPath.writeFile'`, takes a `PlatformPath` instead of an `OsPath`.
writeFile' :: PlatformPath -> BS.ByteString -> IO ()
writeFile' = OsPath.writeFile' . coerce

-- | Same as `OsPath.appendFile`, takes a `PlatformPath` instead of an `OsPath`.
appendFile :: PlatformPath -> BSL.ByteString -> IO ()
appendFile = OsPath.appendFile . coerce

-- | Same as `OsPath.appendFile'`, takes a `PlatformPath` instead of an `OsPath`.
appendFile' :: PlatformPath -> BS.ByteString -> IO ()
appendFile' = OsPath.appendFile' . coerce

-- | Same as `OsPath.openFile`, takes a `PlatformPath` instead of an `OsPath`.
openFile :: PlatformPath -> IOMode -> IO Handle
openFile fp = P.openFile fp
openFile = OsPath.openFile . coerce

-- | Open an existing file and return the 'Handle'.
-- | Same as `OsPath.openExistingFile`, takes a `PlatformPath` instead of an `OsPath`.
openExistingFile :: PlatformPath -> IOMode -> IO Handle
openExistingFile fp = P.openExistingFile fp

openExistingFile = OsPath.openExistingFile . coerce

0 comments on commit 174705a

Please sign in to comment.