Skip to content

Commit

Permalink
Apply review suggestions
Browse files Browse the repository at this point in the history
  • Loading branch information
hasufell committed Jul 24, 2024
1 parent f733c80 commit 030e3af
Show file tree
Hide file tree
Showing 3 changed files with 15 additions and 57 deletions.
40 changes: 5 additions & 35 deletions System/File/OsPath/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ module System.File.OsPath.Internal where

import qualified System.File.Platform as P

import Prelude ((.), ($), String, IO, ioError, pure, either, const, flip, Maybe(..), fmap, (<$>), id, Bool(..), FilePath, (++), return, show, (>>=), (==), otherwise, errorWithoutStackTrace, userError, mempty)
import Prelude ((.), ($), String, IO, ioError, pure, either, const, flip, Maybe(..), fmap, (<$>), id, Bool(..), FilePath, (++), return, show, (>>=), (==), otherwise, userError)
import GHC.IO (catchException)
import GHC.IO.Exception (IOException(..))
import GHC.IO.Handle (hClose_help)
Expand All @@ -26,9 +26,10 @@ import System.OsString.Internal.Types

import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import qualified System.OsString as OSS
import System.Posix.Types (CMode)
#if !MIN_VERSION_filepath(1, 5, 0)
#if MIN_VERSION_filepath(1, 5, 0)
import qualified System.OsString as OSS
#else
import Data.Coerce
#endif

Expand Down Expand Up @@ -245,46 +246,15 @@ openTempFile' loc (OsString tmp_dir) template@(OsString tmpl) binary mode
-- We split off the last extension, so we can use .foo.ext files
-- for temporary files (hidden on Unix OSes). Unfortunately we're
-- below filepath in the hierarchy here.
(OsString prefix, OsString suffix) =
case break_ (== OSS.unsafeFromChar '.') $ reverse_ template of
-- First case: template contains no '.'s. Just re-reverse it.
(rev_suffix, xs)
| xs == mempty -> (reverse_ rev_suffix, mempty)
-- Second case: template contains at least one '.'. Strip the
-- dot from the prefix and prepend it to the suffix (if we don't
-- do this, the unique number will get added after the '.' and
-- thus be part of the extension, which is wrong.)
(rev_suffix, xs)
| (h:rest) <- OSS.unpack xs
, h == unsafeFromChar '.' -> (reverse_ (OSS.pack rest), cons_ (unsafeFromChar '.') $ reverse_ rev_suffix)
-- Otherwise, something is wrong, because (break (== '.')) should
-- always return a pair with either the empty string or a string
-- beginning with '.' as the second component.
_ -> errorWithoutStackTrace "bug in System.IO.openTempFile"
(OsString prefix, OsString suffix) = OSP.splitExtension template

#if MIN_VERSION_filepath(1, 5, 0)
any_ :: (OsChar -> Bool) -> OsString -> Bool
any_ = OSS.any

cons_ :: OsChar -> OsString -> OsString
cons_ = OSS.cons

break_ :: (OsChar -> Bool) -> OsString -> (OsString, OsString)
break_ = OSS.break

reverse_ :: OsString -> OsString
reverse_ = OSS.reverse
#else
any_ :: (OsChar -> Bool) -> OsString -> Bool
any_ = coerce P.any_

cons_ :: OsChar -> OsString -> OsString
cons_ = coerce P.cons_

break_ :: (OsChar -> Bool) -> OsString -> (OsString, OsString)
break_ = coerce P.break_

reverse_ :: OsString -> OsString
reverse_ = coerce P.reverse_
#endif

16 changes: 5 additions & 11 deletions posix/System/File/Platform.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,8 @@ import Data.Coerce (coerce)
import "filepath" System.OsString.Internal.Types (PosixString(..), PosixChar(..))
import qualified "filepath" System.OsPath.Data.ByteString.Short as BC
#endif
import System.CPUTime (cpuTimePrecision, getCPUTime)
import Text.Printf (printf)

-- | Open a file and return the 'Handle'.
openFile :: PosixPath -> IOMode -> IO Handle
Expand Down Expand Up @@ -110,9 +112,10 @@ tempCounter = unsafePerformIO $ newIORef 0
-- build large digit-alike number
rand_string :: IO PosixString
rand_string = do
r1 <- c_getpid
r1 <- fromIntegral @_ @Int <$> c_getpid
(r2, _) <- atomicModifyIORef'_ tempCounter (+1)
return $ PS.pack $ fmap (PS.unsafeFromChar) (show r1 ++ "-" ++ show r2)
r3 <- (`quot` cpuTimePrecision) <$> getCPUTime
return $ PS.pack $ fmap (PS.unsafeFromChar) (printf "%x-%x-%x" r1 r2 r3)

lenientDecode :: PosixString -> String
lenientDecode ps = let utf8' = PS.decodeWith utf8 ps
Expand All @@ -124,17 +127,8 @@ lenientDecode ps = let utf8' = PS.decodeWith utf8 ps

#if !MIN_VERSION_filepath(1, 5, 0)

break_ :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString)
break_ = coerce BC.break

reverse_ :: PosixString -> PosixString
reverse_ = coerce BC.reverse

any_ :: (PosixChar -> Bool) -> PosixString -> Bool
any_ = coerce BC.any

cons_ :: PosixChar -> PosixString -> PosixString
cons_ = coerce BC.cons

#endif

16 changes: 5 additions & 11 deletions windows/System/File/Platform.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -35,9 +35,11 @@ import Foreign.Ptr
import Foreign.Marshal.Alloc
import Foreign.Marshal.Utils (with)
import Foreign.Storable
import System.CPUTime (cpuTimePrecision, getCPUTime)
import System.Posix.Types (CMode)
import System.IO.Unsafe (unsafePerformIO)
import System.Posix.Internals (c_getpid, o_EXCL)
import Text.Printf (printf)

#if MIN_VERSION_filepath(1, 5, 0)
import System.OsString.Encoding
Expand Down Expand Up @@ -193,9 +195,10 @@ tempCounter = unsafePerformIO $ newIORef 0
-- build large digit-alike number
rand_string :: IO WindowsPath
rand_string = do
r1 <- c_getpid
r1 <- fromIntegral @_ @Int <$> c_getpid
(r2, _) <- atomicModifyIORef'_ tempCounter (+1)
return $ WS.pack $ fmap (WS.unsafeFromChar) (show r1 ++ "-" ++ show r2)
r3 <- (`quot` cpuTimePrecision) <$> getCPUTime
return $ WS.pack $ fmap (WS.unsafeFromChar) (printf "%x-%x-%x" r1 r2 r3)

lenientDecode :: WindowsString -> String
lenientDecode ws = let utf16le' = WS.decodeWith utf16le_b ws
Expand All @@ -221,17 +224,8 @@ toHandle fp iomode h = (`onException` Win32.closeHandle h) $ do

#if !MIN_VERSION_filepath(1, 5, 0)

break_ :: (WindowsChar -> Bool) -> WindowsString -> (WindowsString, WindowsString)
break_ = coerce BC.break

reverse_ :: WindowsString -> WindowsString
reverse_ = coerce BC.reverse

any_ :: (WindowsChar -> Bool) -> WindowsString -> Bool
any_ = coerce BC.any

cons_ :: WindowsChar -> WindowsString -> WindowsString
cons_ = coerce BC.cons

#endif

0 comments on commit 030e3af

Please sign in to comment.