diff --git a/patches/doctest-0.16.2.patch b/patches/doctest-0.16.3.patch
similarity index 71%
rename from patches/doctest-0.16.2.patch
rename to patches/doctest-0.16.3.patch
index fe958de4eed712c677e2b9a0a260ade3d52b8a20..d35e7e65b5399fb7facf0d6db002c4c525844c4e 100644
--- a/patches/doctest-0.16.2.patch
+++ b/patches/doctest-0.16.3.patch
@@ -1,5 +1,5 @@
 diff --git a/src/Extract.hs b/src/Extract.hs
-index a5604b4..1cff8b5 100644
+index 81ed5a9..1cff8b5 100644
 --- a/src/Extract.hs
 +++ b/src/Extract.hs
 @@ -21,7 +21,11 @@ import           GHC hiding (flags, Module, Located)
@@ -25,19 +25,6 @@ index a5604b4..1cff8b5 100644
  import           DynamicLoading (initializePlugins)
  #endif
  
-@@ -118,9 +124,11 @@ parse args = withGhc args $ \modules_ -> withTempOutputDir $ do
-     enableCompilation modGraph = do
- #if __GLASGOW_HASKELL__ < 707
-       let enableComp d = d { hscTarget = defaultObjectTarget }
--#else
-+#elif __GLASGOW_HASKELL__ < 809
-       let enableComp d = let platform = targetPlatform d
-                          in d { hscTarget = defaultObjectTarget platform }
-+#else
-+      let enableComp d = d { hscTarget = defaultObjectTarget d }
- #endif
-       modifySessionDynFlags enableComp
-       -- We need to update the DynFlags of the ModSummaries as well.
 diff --git a/src/GhcUtil.hs b/src/GhcUtil.hs
 index 52e965e..23d058e 100644
 --- a/src/GhcUtil.hs
@@ -55,17 +42,31 @@ index 52e965e..23d058e 100644
  import           Panic (throwGhcException)
  
 diff --git a/src/Location.hs b/src/Location.hs
-index e005fe5..f01ae41 100644
+index e005fe5..54e63cf 100644
 --- a/src/Location.hs
 +++ b/src/Location.hs
-@@ -63,5 +63,9 @@ toLocation loc
+@@ -2,8 +2,13 @@
+ module Location where
+ 
+ import           Control.DeepSeq (deepseq, NFData(rnf))
++#if __GLASGOW_HASKELL__ >= 811
++import           GHC.Types.SrcLoc hiding (Located)
++import qualified GHC.Types.SrcLoc as GHC
++#else
+ import           SrcLoc hiding (Located)
+ import qualified SrcLoc as GHC
++#endif
+ import           FastString (unpackFS)
+ 
+ #if __GLASGOW_HASKELL__ < 702
+@@ -63,5 +68,9 @@ toLocation loc
  #else
  toLocation loc = case loc of
    UnhelpfulSpan str -> UnhelpfulLocation (unpackFS str)
 -  RealSrcSpan sp    -> Location (unpackFS . srcSpanFile $ sp) (srcSpanStartLine sp)
 +  RealSrcSpan sp
-+#if __GLASGOW_HASKELL__ >= 811
++# if __GLASGOW_HASKELL__ >= 811
 +                 _
-+#endif
++# endif
 +                    -> Location (unpackFS . srcSpanFile $ sp) (srcSpanStartLine sp)
  #endif