Skip to content
Snippets Groups Projects
Commit a5c4468a authored by Ryan Scott's avatar Ryan Scott
Browse files

Update futhark patch in light of ghc!7050

parent 6973ae5c
No related branches found
No related tags found
No related merge requests found
......@@ -472,6 +472,63 @@ index 2dd5ada..062fe29 100644
import Data.List (foldl', sortOn, transpose)
import Data.Map.Strict qualified as M
import Futhark.Builder
diff --git a/src/Futhark/IR/Aliases.hs b/src/Futhark/IR/Aliases.hs
index 3528279..a185cbb 100644
--- a/src/Futhark/IR/Aliases.hs
+++ b/src/Futhark/IR/Aliases.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
@@ -104,7 +105,12 @@ type ConsumedInExp = AliasDec
-- consumed inside of it.
type BodyAliasing = ([VarAliases], ConsumedInExp)
-instance (RepTypes rep, CanBeAliased (Op rep)) => RepTypes (Aliases rep) where
+instance ( RepTypes rep
+#if __GLASGOW_HASKELL__ >= 906
+ , ASTConstraints (OpWithAliases (Op rep))
+#endif
+ , CanBeAliased (Op rep)
+ ) => RepTypes (Aliases rep) where
type LetDec (Aliases rep) = (VarAliases, LetDec rep)
type ExpDec (Aliases rep) = (ConsumedInExp, ExpDec rep)
type BodyDec (Aliases rep) = (BodyAliasing, BodyDec rep)
@@ -127,15 +133,30 @@ withoutAliases m = do
scope <- asksScope removeScopeAliases
runReaderT m scope
-instance (ASTRep rep, CanBeAliased (Op rep)) => ASTRep (Aliases rep) where
+instance ( ASTRep rep
+#if __GLASGOW_HASKELL__ >= 906
+ , IsOp (OpWithAliases (Op rep))
+#endif
+ , CanBeAliased (Op rep)
+ ) => ASTRep (Aliases rep) where
expTypesFromPat =
withoutAliases . expTypesFromPat . removePatAliases
-instance (ASTRep rep, CanBeAliased (Op rep)) => Aliased (Aliases rep) where
+instance ( ASTRep rep
+#if __GLASGOW_HASKELL__ >= 906
+ , AliasedOp (OpWithAliases (Op rep))
+#endif
+ , CanBeAliased (Op rep)
+ ) => Aliased (Aliases rep) where
bodyAliases = map unAliases . fst . fst . bodyDec
consumedInBody = unAliases . snd . fst . bodyDec
-instance (ASTRep rep, CanBeAliased (Op rep)) => PrettyRep (Aliases rep) where
+instance ( ASTRep rep
+#if __GLASGOW_HASKELL__ >= 906
+ , Pretty (OpWithAliases (Op rep))
+#endif
+ , CanBeAliased (Op rep)
+ ) => PrettyRep (Aliases rep) where
ppExpDec (consumed, inner) e =
maybeComment . catMaybes $
[exp_dec, merge_dec, ppExpDec inner $ removeExpAliases e]
diff --git a/src/Futhark/IR/Mem.hs b/src/Futhark/IR/Mem.hs
index ee7bc74..cc2b3c8 100644
--- a/src/Futhark/IR/Mem.hs
......@@ -1028,6 +1085,68 @@ index e092289..b44a665 100644
import Data.Either
import Data.List (find, foldl', inits, mapAccumL)
import Data.Map qualified as M
diff --git a/src/Futhark/Optimise/Simplify/Rep.hs b/src/Futhark/Optimise/Simplify/Rep.hs
index 6e238d6..4f22408 100644
--- a/src/Futhark/Optimise/Simplify/Rep.hs
+++ b/src/Futhark/Optimise/Simplify/Rep.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
@@ -118,7 +119,12 @@ instance FreeIn BodyWisdom where
instance FreeDec BodyWisdom where
precomputed = const . fvNames . unAliases . bodyWisdomFree
-instance (RepTypes rep, CanBeWise (Op rep)) => RepTypes (Wise rep) where
+instance ( RepTypes rep
+#if __GLASGOW_HASKELL__ >= 906
+ , ASTConstraints (OpWithWisdom (Op rep))
+#endif
+ , CanBeWise (Op rep)
+ ) => RepTypes (Wise rep) where
type LetDec (Wise rep) = (VarWisdom, LetDec rep)
type ExpDec (Wise rep) = (ExpWisdom, ExpDec rep)
type BodyDec (Wise rep) = (BodyWisdom, BodyDec rep)
@@ -136,20 +142,35 @@ withoutWisdom m = do
scope <- asksScope removeScopeWisdom
runReaderT m scope
-instance (ASTRep rep, CanBeWise (Op rep)) => ASTRep (Wise rep) where
+instance ( ASTRep rep
+#if __GLASGOW_HASKELL__ >= 906
+ , IsOp (OpWithWisdom (Op rep))
+#endif
+ , CanBeWise (Op rep)
+ ) => ASTRep (Wise rep) where
expTypesFromPat =
withoutWisdom . expTypesFromPat . removePatWisdom
instance Pretty VarWisdom where
pretty _ = pretty ()
-instance (PrettyRep rep, CanBeWise (Op rep)) => PrettyRep (Wise rep) where
+instance ( PrettyRep rep
+#if __GLASGOW_HASKELL__ >= 906
+ , Pretty (OpWithWisdom (Op rep))
+#endif
+ , CanBeWise (Op rep)
+ ) => PrettyRep (Wise rep) where
ppExpDec (_, dec) = ppExpDec dec . removeExpWisdom
instance AliasesOf (VarWisdom, dec) where
aliasesOf = unAliases . varWisdomAliases . fst
-instance (ASTRep rep, CanBeWise (Op rep)) => Aliased (Wise rep) where
+instance ( ASTRep rep
+#if __GLASGOW_HASKELL__ >= 906
+ , AliasedOp (OpWithWisdom (Op rep))
+#endif
+ , CanBeWise (Op rep)
+ ) => Aliased (Wise rep) where
bodyAliases = map unAliases . bodyWisdomAliases . fst . bodyDec
consumedInBody = unAliases . bodyWisdomConsumed . fst . bodyDec
diff --git a/src/Futhark/Optimise/Simplify/Rules.hs b/src/Futhark/Optimise/Simplify/Rules.hs
index 0fe9e30..ad2e21e 100644
--- a/src/Futhark/Optimise/Simplify/Rules.hs
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment