Skip to content

Commit 0f36370

Browse files
committed
OverloadedStrings.
1 parent c225412 commit 0f36370

File tree

1 file changed

+10
-9
lines changed

1 file changed

+10
-9
lines changed

semantic-analysis/src/Analysis/Analysis/Exception.hs

Lines changed: 10 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
{-# LANGUAGE GADTs #-}
44
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
55
{-# LANGUAGE MultiParamTypeClasses #-}
6+
{-# LANGUAGE OverloadedStrings #-}
67
{-# LANGUAGE RankNTypes #-}
78
{-# LANGUAGE TupleSections #-}
89
{-# LANGUAGE TypeApplications #-}
@@ -110,18 +111,18 @@ printExcSet src e = for_ (zip [0..] (Source.lines src)) $ \ (i, line) -> do
110111
let es = exceptionsForLine i e
111112
fvs = freeVariablesForLine i e
112113
unless (null es && null fvs) $ do
113-
Text.putStr (Text.pack " \ESC[30;1m# ")
114-
Text.putStr (Text.pack "{" <> union
114+
Text.putStr " \ESC[30;1m# "
115+
Text.putStr ("{" <> union
115116
( formatFreeVariables fvs
116-
<> formatExceptions es ) <> Text.pack "}" <> reset)
117+
<> formatExceptions es ) <> "}" <> reset)
117118
Text.putStrLn mempty
118119
where
119-
keyword k s = Text.intercalate (Text.pack "\ESC[34;1m" <> k <> reset) (Text.splitOn k s)
120-
keywords = keyword (Text.pack "raise") . keyword (Text.pack "import") . keyword (Text.pack "def") . keyword (Text.pack "pass")
121-
union = Text.intercalate (Text.pack ", ")
122-
formatFreeVariables fvs = map (\ fv -> Text.pack "?" <> formatName (freeVariableName fv)) (Set.toList fvs)
120+
keyword k s = Text.intercalate ("\ESC[34;1m" <> k <> reset) (Text.splitOn k s)
121+
keywords = keyword "raise" . keyword "import" . keyword "def" . keyword "pass"
122+
union = Text.intercalate ", "
123+
formatFreeVariables fvs = map (\ fv -> "?" <> formatName (freeVariableName fv)) (Set.toList fvs)
123124
formatExceptions excs = map (Text.pack . show . formatName . exceptionName) (Set.toList excs)
124-
reset = Text.pack "\ESC[0m"
125+
reset = "\ESC[0m"
125126

126127
refLines :: Reference -> IntSet.IntSet
127128
refLines (Reference _ (Span (Pos startLine _) (Pos endLine _))) = IntSet.fromAscList [startLine..endLine]
@@ -166,7 +167,7 @@ runFile eval file = traverse run file where
166167
let set = Foldable.fold sets
167168
imports = Set.fromList (map extractImport msgs)
168169
pure (Module (Foldable.foldl' (flip (uncurry subst)) set . Map.toList) imports exports (Set.map freeVariableName (freeVariables set)))
169-
extractImport (A.Import components) = name (Text.intercalate (Text.pack ".") (Foldable.toList components))
170+
extractImport (A.Import components) = name (Text.intercalate "." (Foldable.toList components))
170171

171172
newtype ExcC m a = ExcC { runExcC :: m a }
172173
deriving (Alternative, Applicative, Functor, Monad)

0 commit comments

Comments
 (0)