Skip to content

Commit

Permalink
Merge pull request #453 from AshleyYakeley/fixtests
Browse files Browse the repository at this point in the history
fix warnings and tests (#448)
  • Loading branch information
DanBurton authored Jun 2, 2020
2 parents d664413 + 291d45e commit 8814746
Show file tree
Hide file tree
Showing 5 changed files with 11 additions and 5 deletions.
2 changes: 2 additions & 0 deletions src/Language/Haskell/Exts/ParseMonad.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,9 @@ import Control.Applicative
import Control.Monad (when, liftM, ap)
import qualified Control.Monad.Fail as Fail
import Data.Monoid hiding ((<>))
#if !MIN_VERSION_base(4,13,0)
import Data.Semigroup (Semigroup(..))
#endif
-- To avoid import warnings for Control.Applicative, Data.Monoid, and Data.Semigroup
import Prelude

Expand Down
8 changes: 6 additions & 2 deletions src/Language/Haskell/Exts/SrcLoc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,10 @@ module Language.Haskell.Exts.SrcLoc where
import Data.Data
import GHC.Generics (Generic)

showInt :: Int -> String
showInt i | i < 0 = "(" ++ show i ++ ")"
showInt i = show i

-- | A single position in the source.
data SrcLoc = SrcLoc
{ srcFilename :: String
Expand All @@ -29,7 +33,7 @@ data SrcLoc = SrcLoc
instance Show SrcLoc where
showsPrec n (SrcLoc fn sl sc) =
showParen (n >= 11) $
showString $ "SrcLoc " ++ show fn ++ " " ++ unwords (map show [sl,sc])
showString $ "SrcLoc " ++ show fn ++ " " ++ unwords (map showInt [sl,sc])

noLoc :: SrcLoc
noLoc = SrcLoc "" (-1) (-1)
Expand All @@ -47,7 +51,7 @@ data SrcSpan = SrcSpan
instance Show SrcSpan where
showsPrec n (SrcSpan fn sl sc el ec) =
showParen (n >= 11) $
showString $ "SrcSpan " ++ show fn ++ " " ++ unwords (map show [sl,sc,el,ec])
showString $ "SrcSpan " ++ show fn ++ " " ++ unwords (map showInt [sl,sc,el,ec])


-- | Returns 'srcSpanStartLine' and 'srcSpanStartColumn' in a pair.
Expand Down
2 changes: 1 addition & 1 deletion tests/examples/AmbiguousFixities.hs.exactprinter.golden
Original file line number Diff line number Diff line change
@@ -1 +1 @@
ParseFailed (SrcLoc "" -1 -1) "Ambiguous infix expression"
ParseFailed (SrcLoc "" (-1) (-1)) "Ambiguous infix expression"
2 changes: 1 addition & 1 deletion tests/examples/AmbiguousFixities.hs.prettyparser.golden
Original file line number Diff line number Diff line change
@@ -1 +1 @@
ParseFailed (SrcLoc "" -1 -1) "Ambiguous infix expression"
ParseFailed (SrcLoc "" (-1) (-1)) "Ambiguous infix expression"
2 changes: 1 addition & 1 deletion tests/examples/AmbiguousFixities.hs.prettyprinter.golden
Original file line number Diff line number Diff line change
@@ -1 +1 @@
ParseFailed (SrcLoc "" -1 -1) "Ambiguous infix expression"
ParseFailed (SrcLoc "" (-1) (-1)) "Ambiguous infix expression"

0 comments on commit 8814746

Please sign in to comment.