Skip to content

Commit

Permalink
build fix for ghc-9.10
Browse files Browse the repository at this point in the history
  • Loading branch information
Trevor L. McDonell committed Jun 16, 2024
1 parent 7aa043f commit 3fee937
Show file tree
Hide file tree
Showing 4 changed files with 17 additions and 5 deletions.
2 changes: 1 addition & 1 deletion accelerate.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -339,7 +339,7 @@ flag nofib

library
build-depends:
base >= 4.12 && < 4.20
base >= 4.12 && < 4.21
, ansi-terminal >= 0.6.2
, base-orphans >= 0.3
, bytestring >= 0.10.2
Expand Down
4 changes: 2 additions & 2 deletions src/Data/Array/Accelerate/Debug/Internal/Stats.hs
Original file line number Diff line number Diff line change
Expand Up @@ -208,11 +208,11 @@ pprTickCount counts =

pprTickGroup :: [(Tick,Int)] -> Doc
pprTickGroup [] = error "pprTickGroup"
pprTickGroup grp =
pprTickGroup grp@(g:_) =
hang 2 (vcat $ (pretty groupTotal <+> groupName)
: [ pretty n <+> pprTickCtx t | (t,n) <- sortBy (flip (comparing snd)) grp ])
where
groupName = tickToStr (fst (head grp))
groupName = tickToStr (fst g)
groupTotal = sum [n | (_,n) <- grp]

tickToTag :: Tick -> Int
Expand Down
14 changes: 13 additions & 1 deletion src/Data/Array/Accelerate/Pattern/TH.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
-- |
Expand Down Expand Up @@ -27,11 +28,14 @@ import Data.Array.Accelerate.Type
import Control.Monad
import Data.Bits
import Data.Char
import Data.List ( (\\), foldl' )
import Data.List ( (\\) )
import Language.Haskell.TH.Extra hiding ( Exp, Match, match )
import Numeric
import Text.Printf
import qualified Language.Haskell.TH.Extra as TH
#if __GLASGOW_HASKELL__ < 910
import Data.List ( foldl' )
#endif

import GHC.Stack

Expand Down Expand Up @@ -181,7 +185,11 @@ mkConP tn' tvs' con' = do
]
r' <- case mf of
Nothing -> return r
#if __GLASGOW_HASKELL__ < 910
Just f -> return (InfixD f pat : r)
#else
Just f -> return (InfixD f DataNamespaceSpecifier pat : r)
#endif
return (pat, r')
where
pat = mkName (':' : nameBase cn)
Expand Down Expand Up @@ -273,7 +281,11 @@ mkConS tn' tvs' prev' next' tag' con' = do
]
r' <- case mf of
Nothing -> return r
#if __GLASGOW_HASKELL__ < 910
Just f -> return (InfixD f pat : r)
#else
Just f -> return (InfixD f DataNamespaceSpecifier pat : r)
#endif
return r'
where
sig = forallT
Expand Down
2 changes: 1 addition & 1 deletion src/Data/BitSet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@
module Data.BitSet where

import Data.Bits
import Prelude hiding ( foldl, foldr )
import Prelude hiding ( foldl, foldl', foldr )
import qualified Data.List as List

import GHC.Exts ( IsList, build )
Expand Down

0 comments on commit 3fee937

Please sign in to comment.