Skip to content

Commit

Permalink
Restyled by hlint
Browse files Browse the repository at this point in the history
  • Loading branch information
restyled-commits authored and LeitMoth committed May 20, 2024
1 parent aac75ae commit 2c660d5
Show file tree
Hide file tree
Showing 2 changed files with 3 additions and 3 deletions.
2 changes: 1 addition & 1 deletion src/Polysemy/ConstraintAbsorber.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,6 @@ absorbWithSem ::
absorbWithSem d i m = R.reify d $ \(_ :: Proxy (s :: Type)) ->
m
\\ C.trans
(C.unsafeCoerceConstraint :: ((p (x m s) :- p m)))
(C.unsafeCoerceConstraint :: (p (x m s) :- p m))
i
{-# INLINEABLE absorbWithSem #-}
4 changes: 2 additions & 2 deletions src/Polysemy/ConstraintAbsorber/MonadCatch.hs
Original file line number Diff line number Diff line change
Expand Up @@ -77,7 +77,7 @@ absorbMonadThrow ::
-- 'Sem'. This might be something with type @'C.MonadCatch' e m => m a@.
(C.MonadThrow (Sem r) => Sem r a) ->
Sem r a
absorbMonadThrow main = absorbMonadCatch main
absorbMonadThrow = absorbMonadCatch
{-# INLINEABLE absorbMonadThrow #-}

------------------------------------------------------------------------------
Expand Down Expand Up @@ -122,7 +122,7 @@ instance
catch x f =
let catchF = catch_ (reflect $ Proxy @s')
in Action $
(action x) `catchF` \e -> case C.fromException e of
action x `catchF` \e -> case C.fromException e of
Just e' -> action $ f e'
_ -> throwM_ (reflect $ Proxy @s') (C.toException e)
{-# INLINEABLE catch #-}

0 comments on commit 2c660d5

Please sign in to comment.