diff --git a/patches/monad-validate-1.2.0.0.patch b/patches/monad-validate-1.2.0.0.patch
deleted file mode 100644
index 0685a81955e053d9f2be0521beb3fd8509bc4be3..0000000000000000000000000000000000000000
--- a/patches/monad-validate-1.2.0.0.patch
+++ /dev/null
@@ -1,13 +0,0 @@
-diff --git a/src/Control/Monad/Validate/Internal.hs b/src/Control/Monad/Validate/Internal.hs
-index cfb1d6b..96aee8e 100644
---- a/src/Control/Monad/Validate/Internal.hs
-+++ b/src/Control/Monad/Validate/Internal.hs
-@@ -296,7 +296,7 @@ instance (Monad m) => Applicative (ValidateT e m) where
-   {-# INLINABLE (<*>) #-}
- 
- instance (Monad m) => Monad (ValidateT e m) where
--  ValidateT x >>= f = ValidateT (x >>= (getValidateT . f))
-+  ValidateT x >>= f = ValidateT (x >>= (\a -> getValidateT (f a)))
-   {-# INLINE (>>=) #-}
- 
- instance MonadTrans (ValidateT e) where