Skip to content

Commit

Permalink
cleanup warns
Browse files Browse the repository at this point in the history
  • Loading branch information
parsonsmatt committed Jun 11, 2024
1 parent 58a9bf4 commit 1283a7e
Showing 1 changed file with 7 additions and 6 deletions.
13 changes: 7 additions & 6 deletions src/Control/Exception/Annotated.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
Expand Down Expand Up @@ -118,7 +119,7 @@ instance (Exception exception) => Exception (AnnotatedException exception) where
=
Nothing

displayException annE@(AnnotatedException annotations exception) =
displayException (AnnotatedException {..}) =
unlines
[ "! AnnotatedException !"
, "Underlying exception type: " <> show (typeOf exception)
Expand Down Expand Up @@ -292,13 +293,13 @@ flatten (AnnotatedException a (AnnotatedException b c)) = AnnotatedException (go
addCallStackToAnnotations cs bs
Nothing ->
bs
go mcallstack (a : as) bs =
case castAnnotation a of
go mcallstack (ann : anns) bs =
case castAnnotation ann of
Just cs ->
let newAcc = fmap (mergeCallStack cs) mcallstack <|> Just cs
in go newAcc as bs
in go newAcc anns bs
Nothing ->
a : go mcallstack as bs
ann : go mcallstack anns bs

tryFlatten :: SomeException -> SomeException
tryFlatten exn =
Expand Down Expand Up @@ -399,7 +400,7 @@ addCallStackToException cs (AnnotatedException anns e) =
AnnotatedException (addCallStackToAnnotations cs anns) e

addCallStackToAnnotations :: CallStack -> [Annotation] -> [Annotation]
addCallStackToAnnotations cs anns = go anns
addCallStackToAnnotations cs = go
where
-- not a huge fan of the direct recursion, but it seems easier than trying
-- to finagle a `foldr` or something
Expand Down

0 comments on commit 1283a7e

Please sign in to comment.