Skip to content

Commit

Permalink
hlint
Browse files Browse the repository at this point in the history
  • Loading branch information
acl-cqc committed Jan 7, 2025
1 parent 06c454e commit 6b05fb6
Show file tree
Hide file tree
Showing 4 changed files with 4 additions and 6 deletions.
2 changes: 1 addition & 1 deletion brat/Brat/Checker/Helpers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -117,7 +117,7 @@ pullPorts :: forall a ty
-> Checking [a]
pullPorts toPort showFn to_pull types =
-- the "state" here is the things still available to be pulled
(\(pulled, rest) -> pulled ++ rest) <$> runStateT (mapM pull1Port to_pull) types
uncurry (++) <$> runStateT (mapM pull1Port to_pull) types
where
pull1Port :: PortName -> StateT [a] Checking a
pull1Port p = StateT $ \available -> case partition ((== p) . toPort) available of
Expand Down
4 changes: 2 additions & 2 deletions brat/Brat/Checker/SolveHoles.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ import Control.Monad (when)
import Data.Bifunctor (second)
import Data.Foldable (sequenceA_)
import Data.Functor
import Data.Maybe (catMaybes)
import Data.Maybe (mapMaybe)
import qualified Data.Map as M
import Data.Type.Equality (TestEquality(..), (:~:)(..))

Expand Down Expand Up @@ -78,7 +78,7 @@ typeEqEta _ (Zy :* _ :* _) hopes Nat exp act
typeEqEta tm stuff@(ny :* _ks :* _sems) hopes k exp act = do
exp <- quote ny exp
act <- quote ny act
let ends = catMaybes $ [exp,act] <&> getEnd
let ends = mapMaybe getEnd [exp,act]
-- sanity check: we've already dealt with either end being in the hopeset
when (or [M.member ie hopes | InEnd ie <- ends]) $ typeErr "ends were in hopeset"
case ends of
Expand Down
2 changes: 0 additions & 2 deletions brat/Brat/Checker/SolvePatterns.hs
Original file line number Diff line number Diff line change
Expand Up @@ -199,8 +199,6 @@ instantiateMeta e val = do
defineEnd e val


where

-- Need to keep track of which way we're solving - which side is known/unknown
-- Things which are dynamically unknown must be Tgts - information flows from Srcs
-- ...But we don't need to do any wiring here, right?
Expand Down
2 changes: 1 addition & 1 deletion brat/Brat/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -568,7 +568,7 @@ expr' p = choice $ (try . getParser <$> enumFrom p) ++ [atomExpr]
let firstPortFC = fcOf . fst <$> uncons ports
case ports of
[] -> juxtRhsWithPull
_ -> (\juxt@(WC juxtFC _) -> WC (maybe juxtFC (\fc -> spanFC fc juxtFC) firstPortFC) (FPull (unWC <$> ports) juxt)) <$> juxtRhsWithPull
_ -> (\juxt@(WC juxtFC _) -> WC (maybe juxtFC (`spanFC` juxtFC) firstPortFC) (FPull (unWC <$> ports) juxt)) <$> juxtRhsWithPull
where
portPull :: Parser (WC String)
portPull = do
Expand Down

0 comments on commit 6b05fb6

Please sign in to comment.