From c109ef0af865ee2912408e4b6d959e65531ca52d Mon Sep 17 00:00:00 2001
From: Julian Ospald <hasufell@posteo.de>
Date: Sun, 26 Nov 2023 21:20:08 +0800
Subject: [PATCH] Support filepath >= 1.5.0.0 and os-string

---
 System/Posix/Env/PosixString.hsc     |  7 ++++++-
 System/Posix/PosixPath/FilePath.hsc  |  7 ++++++-
 System/Posix/Process/PosixString.hsc |  7 ++++++-
 System/Posix/Temp/PosixString.hsc    |  7 ++++++-
 tests/T13660.hs                      |  7 ++++++-
 unix.cabal                           | 23 ++++++++++++++++++++---
 6 files changed, 50 insertions(+), 8 deletions(-)

diff --git a/System/Posix/Env/PosixString.hsc b/System/Posix/Env/PosixString.hsc
index 3c435bd..30d549e 100644
--- a/System/Posix/Env/PosixString.hsc
+++ b/System/Posix/Env/PosixString.hsc
@@ -1,4 +1,5 @@
 {-# LANGUAGE CApiFFI #-}
+{-# LANGUAGE PackageImports #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -42,7 +43,11 @@ import GHC.IO.Encoding.Failure ( CodingFailureMode(..) )
 import System.Posix.Env ( clearEnv )
 import System.OsPath.Posix
 import System.OsString.Internal.Types
-import qualified System.OsPath.Data.ByteString.Short as B
+#if MIN_VERSION_filepath(1, 5, 0)
+import qualified "os-string" System.OsString.Data.ByteString.Short as B
+#else
+import qualified "filepath" System.OsPath.Data.ByteString.Short as B
+#endif
 import Data.ByteString.Short.Internal ( copyToPtr )
 
 import qualified System.Posix.Env.Internal as Internal
diff --git a/System/Posix/PosixPath/FilePath.hsc b/System/Posix/PosixPath/FilePath.hsc
index 55be067..1f07ee3 100644
--- a/System/Posix/PosixPath/FilePath.hsc
+++ b/System/Posix/PosixPath/FilePath.hsc
@@ -1,6 +1,7 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE TypeApplications #-}
 {-# LANGUAGE PatternSynonyms #-}
+{-# LANGUAGE PackageImports #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -45,7 +46,11 @@ import Data.ByteString.Internal (c_strlen)
 import Control.Monad
 import Control.Exception
 import System.OsPath.Posix as PS
-import System.OsPath.Data.ByteString.Short as BSS
+#if MIN_VERSION_filepath(1, 5, 0)
+import "os-string" System.OsString.Data.ByteString.Short as BSS
+#else
+import "filepath" System.OsPath.Data.ByteString.Short as BSS
+#endif
 import Prelude hiding (FilePath)
 import System.OsString.Internal.Types (PosixString(..), pattern PS)
 import GHC.IO.Exception
diff --git a/System/Posix/Process/PosixString.hsc b/System/Posix/Process/PosixString.hsc
index 7994bff..10b001c 100644
--- a/System/Posix/Process/PosixString.hsc
+++ b/System/Posix/Process/PosixString.hsc
@@ -1,3 +1,4 @@
+{-# LANGUAGE PackageImports #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  System.Posix.Process.PosixString
@@ -79,7 +80,11 @@ import Foreign.C hiding (
 
 import System.OsPath.Types
 import System.OsString.Internal.Types (PosixString(..))
-import qualified System.OsPath.Data.ByteString.Short as BC
+#if MIN_VERSION_filepath(1, 5, 0)
+import qualified "os-string" System.OsString.Data.ByteString.Short as BC
+#else
+import qualified "filepath" System.OsPath.Data.ByteString.Short as BC
+#endif
 
 import System.Posix.PosixPath.FilePath
 
diff --git a/System/Posix/Temp/PosixString.hsc b/System/Posix/Temp/PosixString.hsc
index c909381..88c7332 100644
--- a/System/Posix/Temp/PosixString.hsc
+++ b/System/Posix/Temp/PosixString.hsc
@@ -1,4 +1,5 @@
 {-# LANGUAGE CApiFFI #-}
+{-# LANGUAGE PackageImports #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  System.Posix.Temp.PosixString
@@ -20,7 +21,11 @@ module System.Posix.Temp.PosixString (
 
 #include "HsUnix.h"
 
-import qualified System.OsPath.Data.ByteString.Short as BC
+#if MIN_VERSION_filepath(1, 5, 0)
+import qualified "os-string" System.OsString.Data.ByteString.Short as BC
+#else
+import qualified "filepath" System.OsPath.Data.ByteString.Short as BC
+#endif
 import Data.Word
 
 import Foreign.C
diff --git a/tests/T13660.hs b/tests/T13660.hs
index d7867e9..32e2056 100644
--- a/tests/T13660.hs
+++ b/tests/T13660.hs
@@ -1,5 +1,6 @@
 {-# LANGUAGE CPP               #-}
 {-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE PackageImports #-}
 
 module Main where
 
@@ -15,7 +16,11 @@ import System.Posix.IO (defaultFileFlags, OpenFileFlags(..), OpenMode(..))
 import System.Posix.ByteString.FilePath
 
 import qualified Data.ByteString.Char8 as C
-import qualified System.OsPath.Data.ByteString.Short as SBS
+#if MIN_VERSION_filepath(1, 5, 0)
+import qualified "os-string" System.OsString.Data.ByteString.Short as SBS
+#else
+import qualified "filepath" System.OsPath.Data.ByteString.Short as SBS
+#endif
 import qualified System.Posix.Env.PosixString as PS
 import qualified System.Posix.IO.PosixString as PS
 import qualified System.Posix.IO.ByteString as BS
diff --git a/unix.cabal b/unix.cabal
index 380b72f..1394225 100644
--- a/unix.cabal
+++ b/unix.cabal
@@ -45,6 +45,11 @@ extra-tmp-files:
     include/HsUnixConfig.h
     unix.buildinfo
 
+flag os-string
+  description: Use the new os-string package
+  default: False
+  manual: False
+
 source-repository head
     type:     git
     location: https://github.com/haskell/unix.git
@@ -71,9 +76,13 @@ library
     build-depends:
         base        >= 4.12.0.0  && < 4.20,
         bytestring  >= 0.9.2     && < 0.13,
-        filepath    >= 1.4.100.0 && < 1.5,
         time        >= 1.9.1     && < 1.13
 
+    if flag(os-string)
+      build-depends: filepath >= 1.5.0.0, os-string >= 2.0.0
+    else
+      build-depends: filepath >= 1.4.100.0 && < 1.5.0.0
+
     exposed-modules:
         System.Posix
         System.Posix.ByteString
@@ -172,7 +181,11 @@ test-suite unix-tests
         Signals001
     type: exitcode-stdio-1.0
     default-language: Haskell2010
-    build-depends: base, bytestring, filepath, tasty, tasty-hunit, tasty-quickcheck, unix
+    build-depends: base, bytestring, tasty, tasty-hunit, tasty-quickcheck, unix
+    if flag(os-string)
+      build-depends: filepath >= 1.5.0.0, os-string >= 2.0.0
+    else
+      build-depends: filepath >= 1.4.100.0 && < 1.5.0.0
     ghc-options: -Wall -with-rtsopts=-V0
 
 test-suite FdReadBuf001
@@ -362,5 +375,9 @@ test-suite T13660
     main-is: T13660.hs
     type: exitcode-stdio-1.0
     default-language: Haskell2010
-    build-depends: base, unix, filepath >= 1.4.100.0 && < 1.5, bytestring
+    build-depends: base, unix, bytestring
+    if flag(os-string)
+      build-depends: filepath >= 1.5.0.0, os-string >= 2.0.0
+    else
+      build-depends: filepath >= 1.4.100.0 && < 1.5.0.0
     ghc-options: -Wall
-- 
GitLab