diff --git a/.github/workflows/tests.yml b/.github/workflows/tests.yml
index 97c08095b3318d86e091a4fa20ef6cf1bd7a8f22..b763fe53e8e886be265b1ee5bb48650d601a4a30 100644
--- a/.github/workflows/tests.yml
+++ b/.github/workflows/tests.yml
@@ -29,15 +29,8 @@ jobs:
           - '8.10'
           - '8.8'
           - '8.6'
-          - '8.4'
-          - '8.2'
 
         exclude:
-          # Exclude GHC 8.2 on Windows (GHC bug: undefined reference to `__stdio_common_vswprintf_s')
-          - platform:
-              os: windows-latest
-            ghc-version: '8.2'
-
           # Only allow ARM jobs with GHC >= 9.2
           # (It's tedious to not be able to use matrix.ghc-version >= 9.2 as a conditional here.)
           - platform:
@@ -52,12 +45,6 @@ jobs:
           - platform:
               arch: arm
             ghc-version: '8.6'
-          - platform:
-              arch: arm
-            ghc-version: '8.4'
-          - platform:
-              arch: arm
-            ghc-version: '8.2'
 
     steps:
       - uses: actions/checkout@v4
diff --git a/System/Process/Environment/OsString.hs b/System/Process/Environment/OsString.hs
new file mode 100644
index 0000000000000000000000000000000000000000..5b42e014d6efa9e71936e0e084c4a74d9ceb8a28
--- /dev/null
+++ b/System/Process/Environment/OsString.hs
@@ -0,0 +1,41 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE PackageImports #-}
+
+-- | Miscellaneous information about the system environment, for 'OsString'.
+--
+-- @since X.Y.Z
+module System.Process.Environment.OsString (
+    getArgs,
+    getEnv,
+    getEnvironment,
+    ) where
+
+import Data.Coerce (coerce)
+#if MIN_VERSION_filepath(1, 5, 0)
+import "os-string" System.OsString.Internal.Types (OsString(OsString))
+#else
+import "filepath" System.OsString.Internal.Types (OsString(OsString))
+#endif
+#if defined(mingw32_HOST_OS)
+import qualified System.Win32.WindowsString.Console as Platform
+#else
+import qualified System.Posix.Env.PosixString as Platform
+#endif
+
+-- | 'System.Environment.getArgs' for 'OsString'.
+--
+-- @since X.Y.Z
+getArgs :: IO [OsString]
+getArgs = coerce Platform.getArgs
+
+-- | 'System.Environment.getEnv' for 'OsString'.
+--
+-- @since X.Y.Z
+getEnv :: OsString -> IO (Maybe OsString)
+getEnv = coerce Platform.getEnv
+
+-- | 'System.Environment.getEnvironment' for 'OsString'.
+--
+-- @since X.Y.Z
+getEnvironment :: IO [(OsString, OsString)]
+getEnvironment = coerce Platform.getEnvironment
diff --git a/changelog.md b/changelog.md
index e01843ee4a8e84c52dad807cb3a2a718edcf6885..63620c21fe63489f11925b0e32ba45151b9301d3 100644
--- a/changelog.md
+++ b/changelog.md
@@ -1,5 +1,12 @@
 # Changelog for [`process` package](http://hackage.haskell.org/package/process)
 
+## X.Y.Z
+
+* Add `System.Process.Environment.OsString`.
+* Bumps `base >= 4.12.0.0` (GHC 8.6+), `filepath >= 1.4.100.0`,
+  `unix >= 2.8.0.0`, and `Win32 >= 2.14.1.0`.
+* Drops support for GHC < 8.6.
+
 ## 1.6.25.0 *September 2024*
 
 * Fix build with Javascript backend ([#327](https://github.com/haskell/process/issues/327))
diff --git a/process.cabal b/process.cabal
index 333597ecc587400db936b05d10e2f0c098fc9b4f..aba6affd8dcbe1ae1be4db78187ef08725136a50 100644
--- a/process.cabal
+++ b/process.cabal
@@ -41,6 +41,11 @@ source-repository head
     type:     git
     location: https://github.com/haskell/process.git
 
+flag os-string
+    description: Use the new os-string package
+    default: False
+    manual: False
+
 library
     default-language: Haskell2010
     other-extensions:
@@ -56,19 +61,20 @@ library
         System.Process
         System.Process.CommunicationHandle
         System.Process.CommunicationHandle.Internal
+        System.Process.Environment.OsString
         System.Process.Internals
     other-modules: System.Process.Common
     if os(windows)
         c-sources:
             cbits/win32/runProcess.c
         other-modules: System.Process.Windows
-        build-depends: Win32 >=2.4 && < 2.15
+        build-depends: Win32 >= 2.14.1.0 && < 2.15
         -- ole32 and rpcrt4 are needed to create GUIDs for unique named pipes
         -- for process.
         extra-libraries: kernel32, ole32, rpcrt4
         cpp-options: -DWINDOWS
     else
-        build-depends: unix >= 2.5 && < 2.9
+        build-depends: unix >= 2.8.0.0 && < 2.9
         if arch(javascript)
             js-sources:
                 jsbits/process.js
@@ -88,7 +94,12 @@ library
 
     ghc-options: -Wall
 
-    build-depends: base      >= 4.10 && < 4.22,
+    build-depends: base      >= 4.12.0.0 && < 4.22,
                    directory >= 1.1 && < 1.4,
-                   filepath  >= 1.2 && < 1.6,
                    deepseq   >= 1.1 && < 1.6
+
+    if flag(os-string)
+        build-depends: filepath >= 1.5.0.0 && < 1.6,
+                       os-string >= 2.0.0 && < 2.1
+    else
+        build-depends: filepath >= 1.4.100.0 && < 1.5.0.0