diff --git a/app/ghcup/GHCup/OptParse/Compile.hs b/app/ghcup/GHCup/OptParse/Compile.hs
index 28e150629d75f7cb67d75415944ce1d86056cf9a..ca7867b39fafe6d578c6100a297876524b68abf7 100644
--- a/app/ghcup/GHCup/OptParse/Compile.hs
+++ b/app/ghcup/GHCup/OptParse/Compile.hs
@@ -212,7 +212,7 @@ ghcCompileOpts =
             (fmap Left $ option
               str
               (short 'p' <> long "patchdir" <> metavar "PATCH_DIR" <> help
-                "Absolute path to patch directory (applies all .patch and .diff files in order using -p1)"
+                "Absolute path to patch directory (applies all .patch and .diff files in order using -p1. This order is determined by a quilt series file if it exists, or the patches are lexicographically ordered)"
               )
             )
           )
diff --git a/lib/GHCup/Utils.hs b/lib/GHCup/Utils.hs
index a95d6854f919fb44ac02fe532e4798074ec3db4a..fb6212f709905faafaf79016bbb94d390d74637d 100644
--- a/lib/GHCup/Utils.hs
+++ b/lib/GHCup/Utils.hs
@@ -879,20 +879,28 @@ makeOut args workdir = do
   executeOut mymake args workdir
 
 
--- | Try to apply patches in order. Fails with 'PatchFailed'
--- on first failure.
+-- | Try to apply patches in order. The order is determined by
+-- a quilt series file (in the patch directory) if one exists,
+-- else the patches are applied in lexicographical order.
+-- Fails with 'PatchFailed' on first failure.
 applyPatches :: (MonadReader env m, HasDirs env, HasLog env, MonadIO m)
              => FilePath   -- ^ dir containing patches
              -> FilePath   -- ^ dir to apply patches in
              -> Excepts '[PatchFailed] m ()
 applyPatches pdir ddir = do
-  patches <- (fmap . fmap) (pdir </>) $ liftIO $ findFiles
-      pdir
-      (makeRegexOpts compExtended
-                     execBlank
-                     ([s|.+\.(patch|diff)$|] :: ByteString)
-      )
-  forM_ (sort patches) $ \patch' -> applyPatch patch' ddir
+  let lexicographical = (fmap . fmap) (pdir </>) $ sort <$> findFiles
+        pdir
+        (makeRegexOpts compExtended
+                       execBlank
+                       ([s|.+\.(patch|diff)$|] :: ByteString)
+        )
+  let quilt = map (pdir </>) . lines <$> readFile (pdir </> "series")
+
+  patches <- liftIO $ quilt `catchIO` (\e ->
+    if isDoesNotExistError e || isPermissionError e then
+      lexicographical 
+    else throwIO e)
+  forM_ patches $ \patch' -> applyPatch patch' ddir
 
 
 applyPatch :: (MonadReader env m, HasDirs env, HasLog env, MonadIO m)