From a53e139025ce52687d22bfe8e2f9db797aee5995 Mon Sep 17 00:00:00 2001 From: Ryan Scott <ryan.gl.scott@gmail.com> Date: Tue, 5 Nov 2019 07:08:08 -0500 Subject: [PATCH] Remove some old patches for things that now compile with 8.8/HEAD Each of these libraries now has a newer Hackage release that compiles with GHC 8.8/HEAD. --- patches/FontyFruity-0.5.3.4.patch | 101 -------------------- patches/Yampa-0.13.patch | 33 ------- patches/diagrams-core-1.4.1.1.patch | 19 ---- patches/generic-lens-1.2.0.0.patch | 26 ----- patches/hpack-0.32.0.patch | 122 ------------------------ patches/persistent-2.10.1.patch | 34 ------- patches/persistent-template-2.7.2.patch | 69 -------------- patches/skylighting-core-0.8.2.1.patch | 19 ---- patches/texmath-0.11.2.3.patch | 13 --- patches/trifecta-2.patch | 45 --------- patches/vty-5.25.1.patch | 114 ---------------------- 11 files changed, 595 deletions(-) delete mode 100644 patches/FontyFruity-0.5.3.4.patch delete mode 100644 patches/Yampa-0.13.patch delete mode 100644 patches/diagrams-core-1.4.1.1.patch delete mode 100644 patches/generic-lens-1.2.0.0.patch delete mode 100644 patches/hpack-0.32.0.patch delete mode 100644 patches/persistent-2.10.1.patch delete mode 100644 patches/persistent-template-2.7.2.patch delete mode 100644 patches/skylighting-core-0.8.2.1.patch delete mode 100644 patches/texmath-0.11.2.3.patch delete mode 100644 patches/trifecta-2.patch delete mode 100644 patches/vty-5.25.1.patch diff --git a/patches/FontyFruity-0.5.3.4.patch b/patches/FontyFruity-0.5.3.4.patch deleted file mode 100644 index d90f5c73..00000000 --- a/patches/FontyFruity-0.5.3.4.patch +++ /dev/null @@ -1,101 +0,0 @@ -diff --git a/src/Graphics/Text/TrueType/CharacterMap.hs b/src/Graphics/Text/TrueType/CharacterMap.hs -index 2663806..75d2655 100644 ---- a/src/Graphics/Text/TrueType/CharacterMap.hs -+++ b/src/Graphics/Text/TrueType/CharacterMap.hs -@@ -102,7 +102,7 @@ instance NFData CharacterMaps where - rnf (CharacterMaps maps) = rnf maps `seq` () - - instance Binary CharacterMaps where -- put _ = fail "Unimplemented" -+ put _ = error "Unimplemented" - get = do - startIndex <- bytesRead - versionNumber <- getWord16be -@@ -192,7 +192,7 @@ instance Ord CharacterTable where - compare _ _ = GT - - instance Binary CharacterTable where -- put _ = fail "Binary.put CharacterTable - Unimplemented" -+ put _ = error "Binary.put CharacterTable - Unimplemented" - get = do - format <- getWord16be - case format of -@@ -305,7 +305,7 @@ instance CharMappeable Format0 where - langIdOfCharMap = _format0Language - - instance Binary Format0 where -- put _ = fail "Binary.Format0.put - unimplemented" -+ put _ = error "Binary.Format0.put - unimplemented" - get = do - tableSize <- getWord16be - when (tableSize /= 262) $ -@@ -347,7 +347,7 @@ instance Binary Format2SubHeader where - - - instance Binary Format2 where -- put _ = fail "Format2.put - unimplemented" -+ put _ = error "Format2.put - unimplemented" - get = do - _tableSize <- getWord16be - lang <- getWord16be -@@ -376,7 +376,7 @@ instance CharMappeable Format6 where - langIdOfCharMap = _format6Language - - instance Binary Format6 where -- put _ = fail "Format6.put - unimplemented" -+ put _ = error "Format6.put - unimplemented" - get = do - _length <- getWord16be - language <- getWord16be -diff --git a/src/Graphics/Text/TrueType/Glyph.hs b/src/Graphics/Text/TrueType/Glyph.hs -index 5209222..aa0c500 100644 ---- a/src/Graphics/Text/TrueType/Glyph.hs -+++ b/src/Graphics/Text/TrueType/Glyph.hs -@@ -313,7 +313,7 @@ getSimpleOutline counterCount = do - where breaker array ix = VU.splitAt (fromIntegral ix + 1) array - - instance Binary Glyph where -- put _ = fail "Glyph.put - unimplemented" -+ put _ = error "Glyph.put - unimplemented" - get = do - hdr <- get - case _glfNumberOfContours hdr of -diff --git a/src/Graphics/Text/TrueType/Header.hs b/src/Graphics/Text/TrueType/Header.hs -index 2c425e5..abd6589 100644 ---- a/src/Graphics/Text/TrueType/Header.hs -+++ b/src/Graphics/Text/TrueType/Header.hs -@@ -100,7 +100,7 @@ instance NFData FontHeader where - rnf (FontHeader {}) = () - - instance Binary FontHeader where -- put _ = fail "Unimplemented" -+ put _ = error "Unimplemented" - get = - FontHeader <$> get <*> get <*> g32 <*> g32 <*> get - <*> g16 <*> g64 <*> g64 <*> get <*> get -diff --git a/src/Graphics/Text/TrueType/MaxpTable.hs b/src/Graphics/Text/TrueType/MaxpTable.hs -index a0508c6..29c773c 100644 ---- a/src/Graphics/Text/TrueType/MaxpTable.hs -+++ b/src/Graphics/Text/TrueType/MaxpTable.hs -@@ -50,7 +50,7 @@ instance NFData MaxpTable where - rnf (MaxpTable {}) = () - - instance Binary MaxpTable where -- put _ = fail "Unimplemented" -+ put _ = error "Unimplemented" - get = MaxpTable - <$> get <*> g16 <*> g16 <*> g16 <*> g16 <*> g16 - <*> g16 <*> g16 <*> g16 <*> g16 <*> g16 <*> g16 -diff --git a/src/Graphics/Text/TrueType/Name.hs b/src/Graphics/Text/TrueType/Name.hs -index 8c23605..c05a55f 100644 ---- a/src/Graphics/Text/TrueType/Name.hs -+++ b/src/Graphics/Text/TrueType/Name.hs -@@ -35,7 +35,7 @@ instance NFData NameTable where - rnf (NameTable {}) = () - - instance Binary NameTable where -- put _ = fail "Binary.put NameTable - unimplemented" -+ put _ = error "Binary.put NameTable - unimplemented" - get = do - nameFormatId <- getWord16be - when (nameFormatId /= 0) $ diff --git a/patches/Yampa-0.13.patch b/patches/Yampa-0.13.patch deleted file mode 100644 index 58550188..00000000 --- a/patches/Yampa-0.13.patch +++ /dev/null @@ -1,33 +0,0 @@ -diff --git a/src/FRP/Yampa/Event.hs b/src/FRP/Yampa/Event.hs -index 804fe46..0639f3f 100644 ---- a/src/FRP/Yampa/Event.hs -+++ b/src/FRP/Yampa/Event.hs -@@ -1,3 +1,4 @@ -+{-# LANGUAGE CPP #-} - {-# OPTIONS_GHC -fno-warn-warnings-deprecations #-} - ----------------------------------------------------------------------------------------- - -- | -@@ -90,6 +91,7 @@ module FRP.Yampa.Event where - - import Control.Applicative - import Control.DeepSeq (NFData(..)) -+import qualified Control.Monad.Fail as Fail - - import FRP.Yampa.Diagnostics - -@@ -175,9 +177,14 @@ instance Monad Event where - - -- | See 'pure'. - return = pure -+#if !(MIN_VERSION_base(4,13,0)) - -- | Fail with 'NoEvent'. -- fail _ = NoEvent -+ fail = Fail.fail -+#endif - -+instance Fail.MonadFail Event where -+ -- | Fail with 'NoEvent'. -+ fail _ = NoEvent - - -- | Alternative instance - instance Alternative Event where diff --git a/patches/diagrams-core-1.4.1.1.patch b/patches/diagrams-core-1.4.1.1.patch deleted file mode 100644 index 66e6e635..00000000 --- a/patches/diagrams-core-1.4.1.1.patch +++ /dev/null @@ -1,19 +0,0 @@ -diff --git a/diagrams-core.cabal b/diagrams-core.cabal -index d9672bf..243ad05 100644 ---- a/diagrams-core.cabal -+++ b/diagrams-core.cabal -@@ -37,12 +37,12 @@ Library - Diagrams.Core.V - - Build-depends: base >= 4.2 && < 4.12, -- containers >= 0.4.2 && < 0.6, -+ containers >= 0.4.2 && < 0.7, - unordered-containers >= 0.2 && < 0.3, - semigroups >= 0.8.4 && < 0.19, - monoid-extras >= 0.3 && < 0.6, - dual-tree >= 0.2 && < 0.3, -- lens >= 4.0 && < 4.17, -+ lens >= 4.0 && < 4.19, - linear >= 1.11.3 && < 1.21, - adjunctions >= 4.0 && < 5.0, - distributive >=0.2.2 && < 1.0, diff --git a/patches/generic-lens-1.2.0.0.patch b/patches/generic-lens-1.2.0.0.patch deleted file mode 100644 index 3104b146..00000000 --- a/patches/generic-lens-1.2.0.0.patch +++ /dev/null @@ -1,26 +0,0 @@ -diff --git a/src/Data/Generics/Product/Any.hs b/src/Data/Generics/Product/Any.hs -index b41ba6b..12ea3bb 100644 ---- a/src/Data/Generics/Product/Any.hs -+++ b/src/Data/Generics/Product/Any.hs -@@ -53,7 +53,7 @@ import Data.Generics.Product.Typed - -- human = Human "Tunyasz" 50 "London" - -- :} - --class HasAny (sel :: k) s t a b | s sel k -> a where -+class HasAny sel s t a b | s sel -> a where - -- |A lens that focuses on a part of a product as identified by some - -- selector. Currently supported selectors are field names, positions and - -- unique types. Compatible with the lens package's 'Control.Lens.Lens' -diff --git a/src/Data/Generics/Sum/Any.hs b/src/Data/Generics/Sum/Any.hs -index 0a13328..ae1919b 100644 ---- a/src/Data/Generics/Sum/Any.hs -+++ b/src/Data/Generics/Sum/Any.hs -@@ -61,7 +61,7 @@ import Data.Generics.Internal.VL.Prism - -- :} - - -- |Sums that have generic prisms. --class AsAny (sel :: k) a s | s sel k -> a where -+class AsAny sel a s | s sel -> a where - -- |A prism that projects a sum as identified by some selector. Currently - -- supported selectors are constructor names and unique types. Compatible - -- with the lens package's 'Control.Lens.Prism' type. diff --git a/patches/hpack-0.32.0.patch b/patches/hpack-0.32.0.patch deleted file mode 100644 index 23db47c2..00000000 --- a/patches/hpack-0.32.0.patch +++ /dev/null @@ -1,122 +0,0 @@ -diff --git a/src/Data/Aeson/Config/Parser.hs b/src/Data/Aeson/Config/Parser.hs -index 5680bbd..e0a04c3 100644 ---- a/src/Data/Aeson/Config/Parser.hs -+++ b/src/Data/Aeson/Config/Parser.hs -@@ -31,6 +31,7 @@ module Data.Aeson.Config.Parser ( - - import Control.Monad - import Control.Applicative -+import qualified Control.Monad.Fail as Fail - import Control.Monad.Trans.Class - import Control.Monad.Trans.Writer - import Data.Monoid ((<>)) -@@ -61,7 +62,7 @@ fromAesonPathElement e = case e of - Aeson.Index n -> Index n - - newtype Parser a = Parser {unParser :: WriterT (Set JSONPath) Aeson.Parser a} -- deriving (Functor, Applicative, Alternative, Monad) -+ deriving (Functor, Applicative, Alternative, Monad, Fail.MonadFail) - - liftParser :: Aeson.Parser a -> Parser a - liftParser = Parser . lift -diff --git a/src/Hpack/Config.hs b/src/Hpack/Config.hs -index 5710b49..aba76b9 100644 ---- a/src/Hpack/Config.hs -+++ b/src/Hpack/Config.hs -@@ -5,6 +5,7 @@ - {-# LANGUAGE DeriveAnyClass #-} - {-# LANGUAGE FlexibleInstances #-} - {-# LANGUAGE LambdaCase #-} -+{-# LANGUAGE LiberalTypeSynonyms #-} - {-# LANGUAGE OverloadedStrings #-} - {-# LANGUAGE RecordWildCards #-} - {-# LANGUAGE CPP #-} -diff --git a/src/Hpack/Syntax/BuildTools.hs b/src/Hpack/Syntax/BuildTools.hs -index a27819e..df6d917 100644 ---- a/src/Hpack/Syntax/BuildTools.hs -+++ b/src/Hpack/Syntax/BuildTools.hs -@@ -7,6 +7,7 @@ module Hpack.Syntax.BuildTools ( - , SystemBuildTools(..) - ) where - -+import qualified Control.Monad.Fail as Fail - import Data.Text (Text) - import qualified Data.Text as T - import Data.Semigroup (Semigroup(..)) -@@ -53,7 +54,7 @@ instance FromValue BuildTools where - buildToolFromString :: Text -> Parser (ParseBuildTool, DependencyVersion) - buildToolFromString s = parseQualifiedBuildTool s <|> parseUnqualifiedBuildTool s - -- parseQualifiedBuildTool :: Monad m => Text -> m (ParseBuildTool, DependencyVersion) -+ parseQualifiedBuildTool :: Fail.MonadFail m => Text -> m (ParseBuildTool, DependencyVersion) - parseQualifiedBuildTool = fmap fromCabal . cabalParse "build tool" . T.unpack - where - fromCabal :: D.ExeDependency -> (ParseBuildTool, DependencyVersion) -@@ -62,7 +63,7 @@ instance FromValue BuildTools where - , DependencyVersion Nothing $ versionConstraintFromCabal version - ) - -- parseUnqualifiedBuildTool :: Monad m => Text -> m (ParseBuildTool, DependencyVersion) -+ parseUnqualifiedBuildTool :: Fail.MonadFail m => Text -> m (ParseBuildTool, DependencyVersion) - parseUnqualifiedBuildTool = fmap (first UnqualifiedBuildTool) . parseDependency "build tool" - - newtype SystemBuildTools = SystemBuildTools { -@@ -80,7 +81,7 @@ instance FromValue SystemBuildTools where - , parseName = T.unpack - } - -- parseSystemBuildTool :: Monad m => Text -> m (String, VersionConstraint) -+ parseSystemBuildTool :: Fail.MonadFail m => Text -> m (String, VersionConstraint) - parseSystemBuildTool = fmap fromCabal . cabalParse "system build tool" . T.unpack - where - fromCabal :: D.LegacyExeDependency -> (String, VersionConstraint) -diff --git a/src/Hpack/Syntax/Dependencies.hs b/src/Hpack/Syntax/Dependencies.hs -index 14c09f7..fdd6671 100644 ---- a/src/Hpack/Syntax/Dependencies.hs -+++ b/src/Hpack/Syntax/Dependencies.hs -@@ -7,6 +7,7 @@ module Hpack.Syntax.Dependencies ( - , parseDependency - ) where - -+import qualified Control.Monad.Fail as Fail - import Data.Text (Text) - import qualified Data.Text as T - import Data.Semigroup (Semigroup(..)) -@@ -59,7 +60,7 @@ objectDependencyInfo o = objectDependency o >>= addMixins o - dependencyInfo :: Value -> Parser DependencyInfo - dependencyInfo = withDependencyVersion (DependencyInfo []) addMixins - --parseDependency :: Monad m => String -> Text -> m (String, DependencyVersion) -+parseDependency :: Fail.MonadFail m => String -> Text -> m (String, DependencyVersion) - parseDependency subject = fmap fromCabal . cabalParse subject . T.unpack - where - fromCabal :: D.Dependency -> (String, DependencyVersion) -diff --git a/src/Hpack/Syntax/DependencyVersion.hs b/src/Hpack/Syntax/DependencyVersion.hs -index 381c3f8..d4e5bc2 100644 ---- a/src/Hpack/Syntax/DependencyVersion.hs -+++ b/src/Hpack/Syntax/DependencyVersion.hs -@@ -25,6 +25,7 @@ module Hpack.Syntax.DependencyVersion ( - ) where - - import Control.Applicative -+import qualified Control.Monad.Fail as Fail - import Data.Maybe - import Data.Scientific - import Data.Text (Text) -@@ -140,13 +141,13 @@ scientificToVersion n = version - | otherwise = 0 - e = base10Exponent n - --parseVersionRange :: Monad m => String -> m VersionConstraint -+parseVersionRange :: Fail.MonadFail m => String -> m VersionConstraint - parseVersionRange = fmap versionConstraintFromCabal . parseCabalVersionRange - --parseCabalVersionRange :: Monad m => String -> m D.VersionRange -+parseCabalVersionRange :: Fail.MonadFail m => String -> m D.VersionRange - parseCabalVersionRange = cabalParse "constraint" - --cabalParse :: (Monad m, D.Parsec a) => String -> String -> m a -+cabalParse :: (Fail.MonadFail m, D.Parsec a) => String -> String -> m a - cabalParse subject s = case D.eitherParsec s of - Right d -> return d - Left _ ->fail $ unwords ["invalid", subject, show s] diff --git a/patches/persistent-2.10.1.patch b/patches/persistent-2.10.1.patch deleted file mode 100644 index 16052742..00000000 --- a/patches/persistent-2.10.1.patch +++ /dev/null @@ -1,34 +0,0 @@ -diff --git a/Database/Persist/Types/Base.hs b/Database/Persist/Types/Base.hs -index 551ca79..6b43689 100644 ---- a/Database/Persist/Types/Base.hs -+++ b/Database/Persist/Types/Base.hs -@@ -4,6 +4,7 @@ module Database.Persist.Types.Base where - - import Control.Arrow (second) - import Control.Exception (Exception) -+import qualified Control.Monad.Fail as Fail - import Control.Monad.Trans.Error (Error (..)) - import qualified Data.Aeson as A - import Data.Bits (shiftL, shiftR) -@@ -433,10 +434,10 @@ instance A.FromJSON PersistValue where - parseJSON (A.String t0) = - case T.uncons t0 of - Nothing -> fail "Null string" -- Just ('p', t) -> either (fail "Invalid base64") (return . PersistDbSpecific) -+ Just ('p', t) -> either (\_ -> fail "Invalid base64") (return . PersistDbSpecific) - $ B64.decode $ TE.encodeUtf8 t - Just ('s', t) -> return $ PersistText t -- Just ('b', t) -> either (fail "Invalid base64") (return . PersistByteString) -+ Just ('b', t) -> either (\_ -> fail "Invalid base64") (return . PersistByteString) - $ B64.decode $ TE.encodeUtf8 t - Just ('t', t) -> fmap PersistTimeOfDay $ readMay t - Just ('u', t) -> fmap PersistUTCTime $ readMay t -@@ -448,7 +449,7 @@ instance A.FromJSON PersistValue where - where - headMay [] = Nothing - headMay (x:_) = Just x -- readMay :: (Read a, Monad m) => T.Text -> m a -+ readMay :: (Read a, Fail.MonadFail m) => T.Text -> m a - readMay t = - case reads $ T.unpack t of - (x, _):_ -> return x diff --git a/patches/persistent-template-2.7.2.patch b/patches/persistent-template-2.7.2.patch deleted file mode 100644 index 1dee2fef..00000000 --- a/patches/persistent-template-2.7.2.patch +++ /dev/null @@ -1,69 +0,0 @@ -diff --git a/Database/Persist/TH.hs b/Database/Persist/TH.hs -index 3474443..191e802 100644 ---- a/Database/Persist/TH.hs -+++ b/Database/Persist/TH.hs -@@ -518,8 +518,14 @@ sumConstrName mps t FieldDef {..} = mkName $ unpack $ concat - - uniqueTypeDec :: MkPersistSettings -> EntityDef -> Dec - uniqueTypeDec mps t = -- DataInstD [] ''Unique -+ DataInstD [] -+#if MIN_VERSION_template_haskell(2,15,0) -+ Nothing -+ (ConT ''Unique `AppT` genericDataType mps (entityHaskell t) backendT) -+#else -+ ''Unique - [genericDataType mps (entityHaskell t) backendT] -+#endif - Nothing - (map (mkUnique mps t) $ entityUniques t) - (derivClause $ entityUniques t) -@@ -781,7 +787,12 @@ mkKeyTypeDec mps t = do - bi <- backendKeyI - return (bi, allInstances) - --#if MIN_VERSION_template_haskell(2,12,0) -+#if MIN_VERSION_template_haskell(2,15,0) -+ cxti <- mapM conT i -+ let kd = if useNewtype -+ then NewtypeInstD [] Nothing (ConT k `AppT` recordType) Nothing dec [DerivClause Nothing cxti] -+ else DataInstD [] Nothing (ConT k `AppT` recordType) Nothing [dec] [DerivClause Nothing cxti] -+#elif MIN_VERSION_template_haskell(2,12,0) - cxti <- mapM conT i - let kd = if useNewtype - then NewtypeInstD [] k [recordType] Nothing dec [DerivClause Nothing cxti] -@@ -1068,19 +1079,34 @@ mkEntity entMap mps t = do - , puk - , DataInstD - [] -+#if MIN_VERSION_template_haskell(2,15,0) -+ Nothing -+ (ConT ''EntityField `AppT` -+ genDataType `AppT` -+ (VarT $ mkName "typ")) -+#else - ''EntityField - [ genDataType - , VarT $ mkName "typ" - ] -+#endif - Nothing - (map fst fields) - [] - , FunD 'persistFieldDef (map snd fields) -+#if MIN_VERSION_template_haskell(2,15,0) -+ , TySynInstD -+ (TySynEqn -+ Nothing -+ (ConT ''PersistEntityBackend `AppT` genDataType) -+ (backendDataType mps)) -+#else - , TySynInstD - ''PersistEntityBackend - (TySynEqn - [genDataType] - (backendDataType mps)) -+#endif - , FunD 'persistIdField [normalClause [] (ConE $ keyIdName t)] - , FunD 'fieldLens lensClauses - ] diff --git a/patches/skylighting-core-0.8.2.1.patch b/patches/skylighting-core-0.8.2.1.patch deleted file mode 100644 index af2d1d3e..00000000 --- a/patches/skylighting-core-0.8.2.1.patch +++ /dev/null @@ -1,19 +0,0 @@ -diff --git a/src/Skylighting/Regex.hs b/src/Skylighting/Regex.hs -index e9acd95..cb068e7 100644 ---- a/src/Skylighting/Regex.hs -+++ b/src/Skylighting/Regex.hs -@@ -12,6 +12,7 @@ module Skylighting.Regex ( - , convertOctalEscapes - ) where - -+import qualified Control.Monad.Fail as Fail - import qualified Control.Exception as E - import Data.Aeson - import Data.Binary (Binary) -@@ -103,5 +104,5 @@ matchRegex r s = case unsafePerformIO (regexec r s) of - encodeToText :: BS.ByteString -> Text.Text - encodeToText = TE.decodeUtf8 . Base64.encode - --decodeFromText :: (Monad m) => Text.Text -> m BS.ByteString -+decodeFromText :: (Fail.MonadFail m) => Text.Text -> m BS.ByteString - decodeFromText = either fail return . Base64.decode . TE.encodeUtf8 diff --git a/patches/texmath-0.11.2.3.patch b/patches/texmath-0.11.2.3.patch deleted file mode 100644 index be1a2d73..00000000 --- a/patches/texmath-0.11.2.3.patch +++ /dev/null @@ -1,13 +0,0 @@ -diff --git a/src/Text/TeXMath/Writers/TeX.hs b/src/Text/TeXMath/Writers/TeX.hs -index 262ece9..a0e5451 100644 ---- a/src/Text/TeXMath/Writers/TeX.hs -+++ b/src/Text/TeXMath/Writers/TeX.hs -@@ -93,7 +93,7 @@ writeBinom cmd x y = do - "\\brack" -> tellGenFrac "[" "]" - "\\brace" -> tellGenFrac "\\{" "\\}" - "\\bangle" -> tellGenFrac "\\langle" "\\rangle" -- _ -> fail "writeBinom: unknown cmd" -+ _ -> error "writeBinom: unknown cmd" - tellGroup $ writeExp x - tellGroup $ writeExp y - else tellGroup $ do diff --git a/patches/trifecta-2.patch b/patches/trifecta-2.patch deleted file mode 100644 index 930a0be3..00000000 --- a/patches/trifecta-2.patch +++ /dev/null @@ -1,45 +0,0 @@ -diff --git a/src/Text/Trifecta/Parser.hs b/src/Text/Trifecta/Parser.hs -index 26a5c1c..91695da 100644 ---- a/src/Text/Trifecta/Parser.hs -+++ b/src/Text/Trifecta/Parser.hs -@@ -177,8 +177,10 @@ instance Monad Parser where - {-# INLINE (>>=) #-} - (>>) = (*>) - {-# INLINE (>>) #-} -+#if !(MIN_VERSION_base(4,13,0)) - fail = Fail.fail - {-# INLINE fail #-} -+#endif - - instance Fail.MonadFail Parser where - fail s = Parser $ \ _ ee _ _ _ _ -> ee (failed s) -diff --git a/trifecta.cabal b/trifecta.cabal -index bfc897b..cda9eea 100644 ---- a/trifecta.cabal -+++ b/trifecta.cabal -@@ -1,6 +1,7 @@ - name: trifecta - category: Text, Parsing, Diagnostics, Pretty Printer, Logging - version: 2 -+x-revision: 2 - license: BSD3 - cabal-version: >= 1.10 - license-file: LICENSE -@@ -66,7 +67,7 @@ library - - build-depends: - ansi-wl-pprint >= 0.6.6 && < 0.7, -- ansi-terminal >= 0.6 && < 0.9, -+ ansi-terminal >= 0.6 && < 0.10, - array >= 0.3.0.2 && < 0.6, - base >= 4.4 && < 5, - blaze-builder >= 0.3.0.1 && < 0.5, -@@ -79,7 +80,7 @@ library - deepseq >= 1.2.0.1 && < 1.5, - fingertree >= 0.1 && < 0.2, - ghc-prim, -- hashable >= 1.2.1 && < 1.3, -+ hashable >= 1.2.1 && < 1.4, - lens >= 4.0 && < 5, - mtl >= 2.0.1 && < 2.3, - parsers >= 0.12.1 && < 1, diff --git a/patches/vty-5.25.1.patch b/patches/vty-5.25.1.patch deleted file mode 100644 index 8242ae0e..00000000 --- a/patches/vty-5.25.1.patch +++ /dev/null @@ -1,114 +0,0 @@ -diff --git a/src/Graphics/Vty/Output.hs b/src/Graphics/Vty/Output.hs -index 3886b88..318a228 100644 ---- a/src/Graphics/Vty/Output.hs -+++ b/src/Graphics/Vty/Output.hs -@@ -29,6 +29,7 @@ module Graphics.Vty.Output - where - - import Control.Monad (when) -+import qualified Control.Monad.Fail as Fail - - import Graphics.Vty.Config - import Graphics.Vty.Image (regionWidth, regionHeight) -@@ -84,7 +85,7 @@ outputForConfig config = (<> config) <$> standardIOConfig >>= outputForConfig - -- Currently, the only way to set the cursor position to a given - -- character coordinate is to specify the coordinate in the Picture - -- instance provided to 'outputPicture' or 'refresh'. --setCursorPos :: MonadIO m => Output -> Int -> Int -> m () -+setCursorPos :: (MonadIO m, Fail.MonadFail m) => Output -> Int -> Int -> m () - setCursorPos t x y = do - bounds <- displayBounds t - when (x >= 0 && x < regionWidth bounds && y >= 0 && y < regionHeight bounds) $ do -@@ -92,14 +93,14 @@ setCursorPos t x y = do - liftIO $ outputByteBuffer t $ writeToByteString $ writeMoveCursor dc x y - - -- | Hides the cursor. --hideCursor :: MonadIO m => Output -> m () -+hideCursor :: (MonadIO m, Fail.MonadFail m) => Output -> m () - hideCursor t = do - bounds <- displayBounds t - dc <- displayContext t bounds - liftIO $ outputByteBuffer t $ writeToByteString $ writeHideCursor dc - - -- | Shows the cursor. --showCursor :: MonadIO m => Output -> m () -+showCursor :: (MonadIO m, Fail.MonadFail m) => Output -> m () - showCursor t = do - bounds <- displayBounds t - dc <- displayContext t bounds -diff --git a/src/Graphics/Vty/Output/Interface.hs b/src/Graphics/Vty/Output/Interface.hs -index b3e13a9..b7e8bdd 100644 ---- a/src/Graphics/Vty/Output/Interface.hs -+++ b/src/Graphics/Vty/Output/Interface.hs -@@ -29,6 +29,7 @@ import Graphics.Vty.DisplayAttributes - import Blaze.ByteString.Builder (Write, writeToByteString) - import Blaze.ByteString.Builder.ByteString (writeByteString) - -+import qualified Control.Monad.Fail as Fail - import Control.Monad.Trans - - import qualified Data.ByteString as BS -@@ -76,7 +77,7 @@ data Output = Output - -- previous state then set the display state to the initial state. - , releaseDisplay :: forall m. MonadIO m => m () - -- | Returns the current display bounds. -- , displayBounds :: forall m. MonadIO m => m DisplayRegion -+ , displayBounds :: forall m. (MonadIO m, Fail.MonadFail m) => m DisplayRegion - -- | Output the bytestring to the terminal device. - , outputByteBuffer :: BS.ByteString -> IO () - -- | Specifies the maximum number of colors supported by the -diff --git a/src/Graphics/Vty/Output/TerminfoBased.hs b/src/Graphics/Vty/Output/TerminfoBased.hs -index 52ba2a3..9444295 100644 ---- a/src/Graphics/Vty/Output/TerminfoBased.hs -+++ b/src/Graphics/Vty/Output/TerminfoBased.hs -@@ -13,6 +13,7 @@ module Graphics.Vty.Output.TerminfoBased - where - - import Control.Monad (when) -+import qualified Control.Monad.Fail as Fail - import qualified Data.ByteString as BS - import Data.ByteString.Internal (toForeignPtr) - import Data.Terminfo.Parse -@@ -203,25 +204,25 @@ reserveTerminal termName outFd = liftIO $ do - maybeSendCap s = when (isJust $ s terminfoCaps) . sendCap (fromJust . s) - return t - --requireCap :: (Applicative m, MonadIO m) => Terminfo.Terminal -> String -> m CapExpression -+requireCap :: (Applicative m, MonadIO m, Fail.MonadFail m) => Terminfo.Terminal -> String -> m CapExpression - requireCap ti capName - = case Terminfo.getCapability ti (Terminfo.tiGetStr capName) of - Nothing -> fail $ "Terminal does not define required capability \"" ++ capName ++ "\"" - Just capStr -> parseCap capStr - --probeCap :: (Applicative m, MonadIO m) => Terminfo.Terminal -> String -> m (Maybe CapExpression) -+probeCap :: (Applicative m, MonadIO m, Fail.MonadFail m) => Terminfo.Terminal -> String -> m (Maybe CapExpression) - probeCap ti capName - = case Terminfo.getCapability ti (Terminfo.tiGetStr capName) of - Nothing -> return Nothing - Just capStr -> Just <$> parseCap capStr - --parseCap :: (Applicative m, MonadIO m) => String -> m CapExpression -+parseCap :: (Applicative m, MonadIO m, Fail.MonadFail m) => String -> m CapExpression - parseCap capStr = do - case parseCapExpression capStr of - Left e -> fail $ show e - Right cap -> return cap - --currentDisplayAttrCaps :: ( Applicative m, MonadIO m ) -+currentDisplayAttrCaps :: ( Applicative m, MonadIO m, Fail.MonadFail m ) - => Terminfo.Terminal - -> m DisplayAttrCaps - currentDisplayAttrCaps ti -diff --git a/vty.cabal b/vty.cabal -index 03258fb..a588847 100644 ---- a/vty.cabal -+++ b/vty.cabal -@@ -45,7 +45,7 @@ library - deepseq >= 1.1 && < 1.5, - directory, - filepath >= 1.0 && < 2.0, -- microlens < 0.4.11, -+ microlens < 0.4.12, - microlens-mtl, - microlens-th, - -- required for nice installation with yi -- GitLab