aboutsummaryrefslogtreecommitdiff
path: root/security/hs-cryptol/files
diff options
context:
space:
mode:
authorGleb Popov <arrowd@FreeBSD.org>2020-05-04 18:08:10 +0000
committerGleb Popov <arrowd@FreeBSD.org>2020-05-04 18:08:10 +0000
commit19c26acbf0b3412689187c066d994589e169f4ee (patch)
treeea6ceaad0e8295491cdee982afa383c2cb90cdbb /security/hs-cryptol/files
parentff6a5b09cf537befa21bb538dd62eccad35ce089 (diff)
downloadports-19c26acbf0b3412689187c066d994589e169f4ee.tar.gz
ports-19c26acbf0b3412689187c066d994589e169f4ee.zip
Notes
Diffstat (limited to 'security/hs-cryptol/files')
-rw-r--r--security/hs-cryptol/files/patch-src_Cryptol_Eval_Monad.hs23
-rw-r--r--security/hs-cryptol/files/patch-src_Cryptol_ModuleSystem_Monad.hs19
-rw-r--r--security/hs-cryptol/files/patch-src_Cryptol_Parser_NoInclude.hs10
-rw-r--r--security/hs-cryptol/files/patch-src_Cryptol_Parser_NoPat.hs10
-rw-r--r--security/hs-cryptol/files/patch-src_Cryptol_Parser_ParserUtils.hs10
-rw-r--r--security/hs-cryptol/files/patch-src_Cryptol_TypeCheck_Monad.hs18
-rw-r--r--security/hs-cryptol/files/patch-src_Cryptol_TypeCheck_Sanity.hs10
-rw-r--r--security/hs-cryptol/files/patch-src_Cryptol_Utils_Patterns.hs24
8 files changed, 124 insertions, 0 deletions
diff --git a/security/hs-cryptol/files/patch-src_Cryptol_Eval_Monad.hs b/security/hs-cryptol/files/patch-src_Cryptol_Eval_Monad.hs
new file mode 100644
index 000000000000..222f835ce74d
--- /dev/null
+++ b/security/hs-cryptol/files/patch-src_Cryptol_Eval_Monad.hs
@@ -0,0 +1,23 @@
+--- src/Cryptol/Eval/Monad.hs.orig 2001-09-09 01:46:40 UTC
++++ src/Cryptol/Eval/Monad.hs
+@@ -38,6 +38,7 @@ module Cryptol.Eval.Monad
+
+ import Control.DeepSeq
+ import Control.Monad
++import qualified Control.Monad.Fail as Fail
+ import Control.Monad.Fix
+ import Control.Monad.IO.Class
+ import Data.IORef
+@@ -164,9 +165,11 @@ instance Applicative Eval where
+ {-# INLINE pure #-}
+ {-# INLINE (<*>) #-}
+
++instance Fail.MonadFail Eval where
++ fail x = Thunk (\_ -> fail x)
++
+ instance Monad Eval where
+ return = Ready
+- fail x = Thunk (\_ -> fail x)
+ (>>=) = evalBind
+ {-# INLINE return #-}
+ {-# INLINE (>>=) #-}
diff --git a/security/hs-cryptol/files/patch-src_Cryptol_ModuleSystem_Monad.hs b/security/hs-cryptol/files/patch-src_Cryptol_ModuleSystem_Monad.hs
new file mode 100644
index 000000000000..da21eb9dfbe0
--- /dev/null
+++ b/security/hs-cryptol/files/patch-src_Cryptol_ModuleSystem_Monad.hs
@@ -0,0 +1,19 @@
+--- src/Cryptol/ModuleSystem/Monad.hs.orig 2020-03-17 19:06:11 UTC
++++ src/Cryptol/ModuleSystem/Monad.hs
+@@ -34,6 +34,7 @@ import Cryptol.Utils.Ident (interactiveName,
+ import Cryptol.Utils.PP
+ import Cryptol.Utils.Logger(Logger)
+
++import qualified Control.Monad.Fail as Fail
+ import Control.Monad.IO.Class
+ import Control.Exception (IOException)
+ import Data.Function (on)
+@@ -325,6 +326,8 @@ instance Monad m => Monad (ModuleT m) where
+
+ {-# INLINE (>>=) #-}
+ m >>= f = ModuleT (unModuleT m >>= unModuleT . f)
++
++instance Fail.MonadFail m => Fail.MonadFail (ModuleT m) where
+ {-# INLINE fail #-}
+ fail = ModuleT . raise . OtherFailure
+
diff --git a/security/hs-cryptol/files/patch-src_Cryptol_Parser_NoInclude.hs b/security/hs-cryptol/files/patch-src_Cryptol_Parser_NoInclude.hs
new file mode 100644
index 000000000000..324c97888105
--- /dev/null
+++ b/security/hs-cryptol/files/patch-src_Cryptol_Parser_NoInclude.hs
@@ -0,0 +1,10 @@
+--- src/Cryptol/Parser/NoInclude.hs.orig 2001-09-09 01:46:40 UTC
++++ src/Cryptol/Parser/NoInclude.hs
+@@ -104,7 +104,6 @@ instance A.Applicative NoIncM where
+ instance Monad NoIncM where
+ return x = M (return x)
+ m >>= f = M (unM m >>= unM . f)
+- fail x = M (fail x)
+
+ -- | Raise an 'IncludeFailed' error.
+ includeFailed :: Located FilePath -> NoIncM a
diff --git a/security/hs-cryptol/files/patch-src_Cryptol_Parser_NoPat.hs b/security/hs-cryptol/files/patch-src_Cryptol_Parser_NoPat.hs
new file mode 100644
index 000000000000..0079d982ce34
--- /dev/null
+++ b/security/hs-cryptol/files/patch-src_Cryptol_Parser_NoPat.hs
@@ -0,0 +1,10 @@
+--- src/Cryptol/Parser/NoPat.hs.orig 2001-09-09 01:46:40 UTC
++++ src/Cryptol/Parser/NoPat.hs
+@@ -542,7 +542,6 @@ instance Functor NoPatM where fmap = liftM
+ instance Applicative NoPatM where pure = return; (<*>) = ap
+ instance Monad NoPatM where
+ return x = M (return x)
+- fail x = M (fail x)
+ M x >>= k = M (x >>= unM . k)
+
+
diff --git a/security/hs-cryptol/files/patch-src_Cryptol_Parser_ParserUtils.hs b/security/hs-cryptol/files/patch-src_Cryptol_Parser_ParserUtils.hs
new file mode 100644
index 000000000000..edd906e876d7
--- /dev/null
+++ b/security/hs-cryptol/files/patch-src_Cryptol_Parser_ParserUtils.hs
@@ -0,0 +1,10 @@
+--- src/Cryptol/Parser/ParserUtils.hs.orig 2001-09-09 01:46:40 UTC
++++ src/Cryptol/Parser/ParserUtils.hs
+@@ -139,7 +139,6 @@ instance Applicative ParseM where
+
+ instance Monad ParseM where
+ return a = P (\_ _ s -> Right (a,s))
+- fail s = panic "[Parser] fail" [s]
+ m >>= k = P (\cfg p s1 -> case unP m cfg p s1 of
+ Left e -> Left e
+ Right (a,s2) -> unP (k a) cfg p s2)
diff --git a/security/hs-cryptol/files/patch-src_Cryptol_TypeCheck_Monad.hs b/security/hs-cryptol/files/patch-src_Cryptol_TypeCheck_Monad.hs
new file mode 100644
index 000000000000..dbfe3f2e1e55
--- /dev/null
+++ b/security/hs-cryptol/files/patch-src_Cryptol_TypeCheck_Monad.hs
@@ -0,0 +1,18 @@
+--- src/Cryptol/TypeCheck/Monad.hs.orig 2001-09-09 01:46:40 UTC
++++ src/Cryptol/TypeCheck/Monad.hs
+@@ -278,7 +278,6 @@ instance A.Applicative InferM where
+
+ instance Monad InferM where
+ return x = IM (return x)
+- fail x = IM (fail x)
+ IM m >>= f = IM (m >>= unIM . f)
+
+ instance MonadFix InferM where
+@@ -835,7 +834,6 @@ instance A.Applicative KindM where
+
+ instance Monad KindM where
+ return x = KM (return x)
+- fail x = KM (fail x)
+ KM m >>= k = KM (m >>= unKM . k)
+
+
diff --git a/security/hs-cryptol/files/patch-src_Cryptol_TypeCheck_Sanity.hs b/security/hs-cryptol/files/patch-src_Cryptol_TypeCheck_Sanity.hs
new file mode 100644
index 000000000000..f8fd1bcc6a9d
--- /dev/null
+++ b/security/hs-cryptol/files/patch-src_Cryptol_TypeCheck_Sanity.hs
@@ -0,0 +1,10 @@
+--- src/Cryptol/TypeCheck/Sanity.hs.orig 2001-09-09 01:46:40 UTC
++++ src/Cryptol/TypeCheck/Sanity.hs
+@@ -467,7 +467,6 @@ instance A.Applicative TcM where
+
+ instance Monad TcM where
+ return a = TcM (return a)
+- fail x = TcM (fail x)
+ TcM m >>= f = TcM (do a <- m
+ let TcM m1 = f a
+ m1)
diff --git a/security/hs-cryptol/files/patch-src_Cryptol_Utils_Patterns.hs b/security/hs-cryptol/files/patch-src_Cryptol_Utils_Patterns.hs
new file mode 100644
index 000000000000..d3879d7a4258
--- /dev/null
+++ b/security/hs-cryptol/files/patch-src_Cryptol_Utils_Patterns.hs
@@ -0,0 +1,24 @@
+--- src/Cryptol/Utils/Patterns.hs.orig 2001-09-09 01:46:40 UTC
++++ src/Cryptol/Utils/Patterns.hs
+@@ -5,6 +5,7 @@
+ module Cryptol.Utils.Patterns where
+
+ import Control.Monad(liftM,liftM2,ap,MonadPlus(..),guard)
++import qualified Control.Monad.Fail as Fail
+ import Control.Applicative(Alternative(..))
+
+ newtype Match b = Match (forall r. r -> (b -> r) -> r)
+@@ -17,10 +18,12 @@ instance Applicative Match where
+ (<*>) = ap
+
+ instance Monad Match where
+- fail _ = empty
+ Match m >>= f = Match $ \no yes -> m no $ \a ->
+ let Match n = f a in
+ n no yes
++
++instance Fail.MonadFail Match where
++ fail _ = empty
+
+ instance Alternative Match where
+ empty = Match $ \no _ -> no