Skip to content

Commit e284526

Browse files
committed
Fix warnings from upgrading GHC to 9.2.x.
Fix warnings, namely -Wstar-is-type. Many -Wincomplete-uni-patterns warnings are not yet fixed.
1 parent 8f0ec1e commit e284526

21 files changed

+90
-98
lines changed

makefile

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -118,7 +118,7 @@ ifneq (,$(DEX_CI))
118118
STACK_FLAGS := $(STACK_FLAGS) --flag dex:debug
119119
endif
120120

121-
possible-clang-locations := clang++-9 clang++-10 clang++-11 clang++-12 clang++-15 clang++
121+
possible-clang-locations := clang++-15 clang++
122122

123123
CLANG := clang++
124124

@@ -133,11 +133,11 @@ CLANG := $(shell for clangversion in $(possible-clang-locations) ; do \
133133
if [[ $$(command -v "$$clangversion" 2>/dev/null) ]]; \
134134
then echo "$$clangversion" ; break ; fi ; done)
135135
ifeq (,$(CLANG))
136-
$(error "Please install clang++-12")
136+
$(error "Please install clang++-15")
137137
endif
138-
clang-version-compatible := $(shell $(CLANG) -dumpversion | awk '{ print(gsub(/^((9\.)|(10\.)|(11\.)|(12\.)|(15\.)).*$$/, "")) }')
138+
clang-version-compatible := $(shell $(CLANG) -dumpversion | awk '{ print(gsub(/^((15\.)).*$$/, "")) }')
139139
ifneq (1,$(clang-version-compatible))
140-
$(error "Please install clang++-12")
140+
$(error "Please install clang++-15")
141141
endif
142142
endif
143143

src/lib/Builder.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ import Control.Monad
1414
import Control.Monad.Reader
1515
import Control.Monad.Writer.Strict hiding (Alt)
1616
import Control.Monad.State.Strict (MonadState (..), StateT (..), runStateT)
17+
import qualified Data.Kind as K
1718
import qualified Data.Map.Strict as M
1819
import Data.Graph (graphFromEdges, topSort)
1920
import Data.Text.Prettyprint.Doc (Pretty (..), group, line, nest)
@@ -135,7 +136,7 @@ liftTopBuilderAndEmit
135136
liftTopBuilderAndEmit cont = do
136137
liftTopBuilderHoisted cont >>= emitHoistedEnv
137138

138-
newtype DoubleBuilderT (r::IR) (topEmissions::B) (m::MonadKind) (n::S) (a:: *) =
139+
newtype DoubleBuilderT (r::IR) (topEmissions::B) (m::MonadKind) (n::S) (a::K.Type) =
139140
DoubleBuilderT { runDoubleBuilderT' :: DoubleInplaceT Env topEmissions (BuilderEmissions r) m n a }
140141
deriving ( Functor, Applicative, Monad, MonadFail, Fallible
141142
, CtxReader, MonadIO, Catchable, MonadReader r')
@@ -342,7 +343,7 @@ lookupPtrName v = lookupEnv v >>= \case
342343
getCache :: EnvReader m => m n (Cache n)
343344
getCache = withEnv $ envCache . topEnv
344345

345-
newtype TopBuilderT (m::MonadKind) (n::S) (a:: *) =
346+
newtype TopBuilderT (m::MonadKind) (n::S) (a::K.Type) =
346347
TopBuilderT { runTopBuilderT' :: InplaceT Env TopEnvFrag m n a }
347348
deriving ( Functor, Applicative, Monad, MonadFail, Fallible
348349
, CtxReader, ScopeReader, MonadTrans1, MonadReader r
@@ -417,7 +418,7 @@ instance (SinkableE e, HoistableState e, TopBuilder m) => TopBuilder (StateT1 e
417418

418419
type BuilderEmissions r = RNest (Decl r)
419420

420-
newtype BuilderT (r::IR) (m::MonadKind) (n::S) (a:: *) =
421+
newtype BuilderT (r::IR) (m::MonadKind) (n::S) (a::K.Type) =
421422
BuilderT { runBuilderT' :: InplaceT Env (BuilderEmissions r) m n a }
422423
deriving ( Functor, Applicative, Monad, MonadTrans1, MonadFail, Fallible
423424
, Catchable, CtxReader, ScopeReader, Alternative, Searcher

src/lib/CheapReduction.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,8 @@ import Control.Monad.Reader
2626
import Data.Foldable (toList)
2727
import Data.Functor.Identity
2828
import Data.Functor ((<&>))
29-
import qualified Data.List.NonEmpty as NE
29+
import qualified Data.Kind as K
30+
import qualified Data.List.NonEmpty as NE
3031
import qualified Data.Map.Strict as M
3132

3233
import Subst
@@ -81,7 +82,7 @@ cheapNormalize a = cheapReduce a >>= \case
8182

8283
-- === internal ===
8384

84-
newtype CheapReducerM (r::IR) (i :: S) (o :: S) (a :: *) =
85+
newtype CheapReducerM (r::IR) (i :: S) (o :: S) (a :: K.Type) =
8586
CheapReducerM
8687
(SubstReaderT AtomSubstVal
8788
(MaybeT1

src/lib/CheckType.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,7 @@ import Control.Monad.State.Class
2020
import Data.Maybe (isJust)
2121
import Data.Foldable (toList)
2222
import Data.Functor
23+
import qualified Data.Kind as K
2324

2425
import CheapReduction
2526
import Core
@@ -63,7 +64,7 @@ class ( Monad2 m, Fallible2 m, SubstReader Name m
6364
affineUsed :: AtomName r o -> m i o ()
6465
parallelAffines_ :: [m i o ()] -> m i o ()
6566

66-
newtype TyperT (m::MonadKind) (r::IR) (i::S) (o::S) (a :: *) =
67+
newtype TyperT (m::MonadKind) (r::IR) (i::S) (o::S) (a::K.Type) =
6768
TyperT { runTyperT' :: SubstReaderT Name (StateT1 (NameMap (AtomNameC r) Int) (EnvReaderT m)) i o a }
6869
deriving ( Functor, Applicative, Monad
6970
, SubstReader Name

src/lib/Core.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,8 @@ import Control.Monad.Reader
3030
import Control.Monad.Writer.Strict hiding (Alt)
3131
import Control.Monad.State
3232
import qualified Control.Monad.State.Strict as SS
33-
import qualified Data.Map.Strict as M
33+
import qualified Data.Map.Strict as M
34+
import qualified Data.Kind as K
3435

3536
import Name
3637
import Err
@@ -76,7 +77,7 @@ type EnvExtender2 (m::MonadKind2) = forall (n::S). EnvExtender (m n)
7677

7778
-- === EnvReader monad ===
7879

79-
newtype EnvReaderT (m::MonadKind) (n::S) (a:: *) =
80+
newtype EnvReaderT (m::MonadKind) (n::S) (a::K.Type) =
8081
EnvReaderT {runEnvReaderT' :: ReaderT (DistinctEvidence n, Env n) m a }
8182
deriving ( Functor, Applicative, Monad, MonadFail
8283
, MonadWriter w, Fallible, Searcher, Alternative)

src/lib/Err.hs

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -158,14 +158,12 @@ instance Functor Except where
158158
{-# INLINE fmap #-}
159159

160160
instance Applicative Except where
161-
pure = return
161+
pure = Success
162162
{-# INLINE pure #-}
163163
liftA2 = liftM2
164164
{-# INLINE liftA2 #-}
165165

166166
instance Monad Except where
167-
return = Success
168-
{-# INLINE return #-}
169167
Failure errs >>= _ = Failure errs
170168
Success x >>= f = f x
171169
{-# INLINE (>>=) #-}
@@ -211,8 +209,6 @@ instance Applicative HardFailM where
211209
instance Monad HardFailM where
212210
(HardFailM (Identity x)) >>= k = k x
213211
{-# INLINE (>>=) #-}
214-
return = HardFailM . Identity
215-
{-# INLINE return #-}
216212

217213
runHardFail :: HardFailM a -> a
218214
runHardFail m = runIdentity $ runHardFail' m

src/lib/Export.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ module Export (
1414

1515
import Control.Category ((>>>))
1616
import Data.List (intercalate)
17+
import qualified Data.Kind as K
1718
import Foreign.Storable
1819
import Foreign.C.String
1920
import Foreign.Ptr
@@ -87,7 +88,7 @@ instance SinkableV (Rename r)
8788
instance FromName (Rename r) where
8889
fromName = JustRefer
8990

90-
newtype ExportSigM (r::IR) (i::S) (o::S) (a:: *) = ExportSigM {
91+
newtype ExportSigM (r::IR) (i::S) (o::S) (a::K.Type) = ExportSigM {
9192
runExportSigM :: SubstReaderT (Rename r) (EnvReaderT FallibleM) i o a }
9293
deriving ( Functor, Applicative, Monad, ScopeReader, EnvExtender, Fallible
9394
, EnvReader, SubstReader (Rename r), MonadFail)

src/lib/Imp.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ import Data.Functor
2323
import Data.Foldable (toList)
2424
import Data.Maybe (fromJust, isJust)
2525
import Data.Text.Prettyprint.Doc
26+
import qualified Data.Kind as K
2627
import Control.Category
2728
import Control.Monad.Identity
2829
import Control.Monad.Reader
@@ -171,12 +172,12 @@ instance ExtOutFrag ImpBuilderEmissions ImpDeclEmission where
171172
extendOutFrag ems (ImpDeclEmission d) = RNest ems d
172173
{-# INLINE extendOutFrag #-}
173174

174-
newtype ImpM (n::S) (a:: *) =
175+
newtype ImpM (n::S) (a::K.Type) =
175176
ImpM { runImpM' :: WriterT1 (ListE IExpr)
176177
(InplaceT Env ImpBuilderEmissions HardFailM) n a }
177178
deriving ( Functor, Applicative, Monad, ScopeReader, Fallible, MonadFail)
178179

179-
type SubstImpM = SubstReaderT AtomSubstVal ImpM :: S -> S -> * -> *
180+
type SubstImpM = SubstReaderT AtomSubstVal ImpM :: S -> S -> K.Type -> K.Type
180181

181182
instance ExtOutMap Env ImpBuilderEmissions where
182183
extendOutMap bindings emissions =

src/lib/Inference.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,7 @@ import Data.List (sortOn)
2626
import Data.Maybe (fromJust, fromMaybe, catMaybes)
2727
import Data.Text.Prettyprint.Doc (Pretty (..), (<+>), vcat)
2828
import Data.Word
29+
import qualified Data.Kind as K
2930
import qualified Data.HashMap.Strict as HM
3031
import qualified Data.Map.Strict as M
3132
import qualified Data.Set as S
@@ -393,7 +394,7 @@ extendOutMapWithConstraints env us ss (Constraints allCs) = case tryUnsnoc allCs
393394
let ss''' = SolverSubst $ ss'' <> s
394395
(env'', us'', ss''')
395396

396-
newtype InfererM (i::S) (o::S) (a:: *) = InfererM
397+
newtype InfererM (i::S) (o::S) (a::K.Type) = InfererM
397398
{ runInfererM' :: SubstReaderT Name (InplaceT InfOutMap InfOutFrag FallibleM) i o a }
398399
deriving (Functor, Applicative, Monad, MonadFail,
399400
ScopeReader, Fallible, Catchable, CtxReader, SubstReader Name)
@@ -2224,7 +2225,7 @@ instance ExtOutMap InfOutMap SolverOutFrag where
22242225
extendOutMap infOutMap outFrag =
22252226
extendOutMap infOutMap $ liftSolverOutFrag outFrag
22262227

2227-
newtype SolverM (n::S) (a:: *) =
2228+
newtype SolverM (n::S) (a::K.Type) =
22282229
SolverM { runSolverM' :: InplaceT SolverOutMap SolverOutFrag SearcherM n a }
22292230
deriving (Functor, Applicative, Monad, MonadFail, Alternative, Searcher,
22302231
ScopeReader, Fallible, CtxReader)
@@ -2713,7 +2714,7 @@ class (Alternative1 m, Searcher1 m, EnvReader m, EnvExtender m)
27132714
getGivens :: m n (Givens n)
27142715
withGivens :: Givens n -> m n a -> m n a
27152716

2716-
newtype SyntherM (n::S) (a:: *) = SyntherM
2717+
newtype SyntherM (n::S) (a::K.Type) = SyntherM
27172718
{ runSyntherM' :: OutReaderT Givens (EnvReaderT []) n a }
27182719
deriving ( Functor, Applicative, Monad, EnvReader, EnvExtender
27192720
, ScopeReader, MonadFail

src/lib/Inline.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66

77
module Inline (inlineBindings) where
88

9+
import qualified Data.Kind as K
910
import Data.List.NonEmpty qualified as NE
1011

1112
import Builder
@@ -53,7 +54,7 @@ instance SinkableE (InlineExpr r) where
5354

5455
type InlineSubstVal = SubstVal InlineExpr
5556

56-
newtype InlineM (i::S) (o::S) (a:: *) = InlineM
57+
newtype InlineM (i::S) (o::S) (a::K.Type) = InlineM
5758
{ runInlineM :: SubstReaderT InlineSubstVal (BuilderM SimpIR) i o a }
5859
deriving ( Functor, Applicative, Monad, MonadFail, Fallible, ScopeReader
5960
, EnvExtender, EnvReader, SubstReader InlineSubstVal, (Builder SimpIR)

0 commit comments

Comments
 (0)