Skip to content

Commit

Permalink
chore: changes in preparation for hlint 3.6 (#1092)
Browse files Browse the repository at this point in the history
  • Loading branch information
brprice authored Jul 11, 2023
2 parents d78113e + a4d5d28 commit 7871d12
Show file tree
Hide file tree
Showing 6 changed files with 27 additions and 12 deletions.
5 changes: 4 additions & 1 deletion primer/gen/Primer/Gen/Core/Typed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -272,7 +272,10 @@ genSyns ty = do
Just . (APP () s aTy,) <$> substTy a aTy instTy
_ -> pure Nothing
genPrimCon' = do
genPrimCon <&> map (bimap (fmap $ PrimCon ()) (TCon ())) <&> filter (consistentTypes ty . snd) <&> \case
consistentCons <-
filter (consistentTypes ty . snd) . map (bimap (fmap $ PrimCon ()) (TCon ()))
<$> genPrimCon
pure $ case consistentCons of
[] -> Nothing
gens -> Just $ Gen.choice $ (\(g, t) -> (,t) <$> g) <$> gens
genLet =
Expand Down
2 changes: 1 addition & 1 deletion primer/src/Primer/Action.hs
Original file line number Diff line number Diff line change
Expand Up @@ -737,7 +737,7 @@ conInfo ::
m (Either Text (TC.Type, Int))
conInfo c =
asks (flip lookupConstructor c . TC.typeDefs) <&> \case
Just (vc, tc, td) -> Right (valConType tc td vc, length $ vc.valConArgs)
Just (vc, tc, td) -> Right (valConType tc td vc, length vc.valConArgs)
Nothing -> Left $ "Could not find constructor " <> show c

getTypeCache :: MonadError ActionError m => Expr -> m TypeCache
Expand Down
11 changes: 9 additions & 2 deletions primer/src/Primer/Action/Available.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,11 @@ import Data.Tuple.Extra (
uncurry3,
)
import Optics (
Field2 (_2),
afailing,
elemOf,
folded,
getting,
to,
view,
(%),
Expand Down Expand Up @@ -85,7 +89,7 @@ import Primer.Core (
_typeMetaLens,
)
import Primer.Core.Transform (decomposeTAppCon)
import Primer.Core.Utils (forgetTypeMetadata, freeVars, freeVarsTy)
import Primer.Core.Utils (forgetTypeMetadata, freeVars, _freeVarsTy)
import Primer.Def (
ASTDef (..),
DefMap,
Expand Down Expand Up @@ -385,7 +389,10 @@ forTypeDefParamNode paramName l Editable tydefs defs tdName td =
( l == Expert
&& not
( typeInUse tdName td tydefs defs
|| any (elem paramName . freeVarsTy) (concatMap valConArgs $ astTypeDefConstructors td)
|| elemOf
(to astTypeDefConstructors % folded % to valConArgs % folded % getting _freeVarsTy % _2)
paramName
td
)
)
[NoInput DeleteTypeParam]
Expand Down
17 changes: 11 additions & 6 deletions primer/src/Primer/App.hs
Original file line number Diff line number Diff line change
Expand Up @@ -85,6 +85,7 @@ import Optics (
ReversibleOptic (re),
elemOf,
folded,
getting,
ifoldMap,
mapped,
over,
Expand Down Expand Up @@ -171,7 +172,7 @@ import Primer.Core (
import Primer.Core.DSL (S, create, emptyHole, tEmptyHole)
import Primer.Core.DSL qualified as DSL
import Primer.Core.Transform (renameTyVar, renameVar, unfoldTApp)
import Primer.Core.Utils (freeVars, freeVarsTy, generateTypeIDs, regenerateExprIDs, regenerateTypeIDs, _freeTmVars, _freeTyVars, _freeVarsTy)
import Primer.Core.Utils (freeVars, generateTypeIDs, regenerateExprIDs, regenerateTypeIDs, _freeTmVars, _freeTyVars, _freeVarsTy)
import Primer.Def (
ASTDef (..),
Def (..),
Expand Down Expand Up @@ -799,8 +800,8 @@ applyProgAction prog = \case
traverseOf
#astTypeDefConstructors
( \cons -> do
when
(vcName `notElem` map valConName cons)
unless
(vcName `elem` map valConName cons)
(throwError $ ConNotFound vcName)
pure $ filter ((/= vcName) . valConName) cons
)
Expand Down Expand Up @@ -907,13 +908,17 @@ applyProgAction prog = \case
( \td -> do
checkTypeNotInUse tdName td $ m : ms
when
(any (elem paramName . freeVarsTy) $ concatMap valConArgs $ astTypeDefConstructors td)
( elemOf
(to astTypeDefConstructors % folded % to valConArgs % folded % getting _freeVarsTy % _2)
paramName
td
)
(throwError $ TypeParamInUse tdName paramName)
traverseOf
#astTypeDefParameters
( \ps -> do
when
(paramName `notElem` map fst ps)
unless
(paramName `elem` map fst ps)
(throwError $ ParamNotFound paramName)
pure $ filter ((/= paramName) . fst) ps
)
Expand Down
2 changes: 1 addition & 1 deletion primer/src/Primer/TypeDef.hs
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ data ValCon b = ValCon
valConType :: TyConName -> ASTTypeDef () -> ValCon () -> Type' ()
valConType tc td vc =
let ret = mkTAppCon tc (TVar () . fst <$> astTypeDefParameters td)
args = foldr (TFun ()) ret (forgetTypeMetadata <$> valConArgs vc)
args = foldr (TFun () . forgetTypeMetadata) ret (valConArgs vc)
foralls = foldr (\(n, k) t -> TForall () n k t) args (astTypeDefParameters td)
in foralls

Expand Down
2 changes: 1 addition & 1 deletion primer/src/Primer/Zipper.hs
Original file line number Diff line number Diff line change
Expand Up @@ -342,7 +342,7 @@ focusOn' i = fmap snd . search matchesID
-- If the target has an embedded type, search the type for a match.
-- If the target is a case expression with bindings, search each binding for a match.
| otherwise =
let inType = focusType z >>= search (guarded (== i) . getID . target) <&> fst <&> InType
let inType = focusType z >>= search (guarded (== i) . getID . target) <&> InType . fst
inCaseBinds = findInCaseBinds i z
in inType <|> inCaseBinds

Expand Down

1 comment on commit 7871d12

@github-actions
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

⚠️ Performance Alert ⚠️

Possible performance regression was detected for benchmark 'Primer benchmarks'.
Benchmark result of this commit is worse than the previous benchmark result exceeding threshold 2.

Benchmark suite Current: 7871d12 Previous: d78113e Ratio
evalTestM/pure logs/mapEven 1: outlier variance 0.22560383341456142 outlier variance 0.024983563445101848 outlier variance 9.03

This comment was automatically generated by workflow using github-action-benchmark.

CC: @dhess

Please sign in to comment.