|
3 | 3 | {-# LANGUAGE GADTs #-}
|
4 | 4 | {-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
5 | 5 | {-# LANGUAGE MultiParamTypeClasses #-}
|
| 6 | +{-# LANGUAGE OverloadedStrings #-} |
6 | 7 | {-# LANGUAGE RankNTypes #-}
|
7 | 8 | {-# LANGUAGE TupleSections #-}
|
8 | 9 | {-# LANGUAGE TypeApplications #-}
|
@@ -110,18 +111,18 @@ printExcSet src e = for_ (zip [0..] (Source.lines src)) $ \ (i, line) -> do
|
110 | 111 | let es = exceptionsForLine i e
|
111 | 112 | fvs = freeVariablesForLine i e
|
112 | 113 | 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 |
115 | 116 | ( formatFreeVariables fvs
|
116 |
| - <> formatExceptions es ) <> Text.pack "}" <> reset) |
| 117 | + <> formatExceptions es ) <> "}" <> reset) |
117 | 118 | Text.putStrLn mempty
|
118 | 119 | 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) |
123 | 124 | formatExceptions excs = map (Text.pack . show . formatName . exceptionName) (Set.toList excs)
|
124 |
| - reset = Text.pack "\ESC[0m" |
| 125 | + reset = "\ESC[0m" |
125 | 126 |
|
126 | 127 | refLines :: Reference -> IntSet.IntSet
|
127 | 128 | refLines (Reference _ (Span (Pos startLine _) (Pos endLine _))) = IntSet.fromAscList [startLine..endLine]
|
@@ -166,7 +167,7 @@ runFile eval file = traverse run file where
|
166 | 167 | let set = Foldable.fold sets
|
167 | 168 | imports = Set.fromList (map extractImport msgs)
|
168 | 169 | 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)) |
170 | 171 |
|
171 | 172 | newtype ExcC m a = ExcC { runExcC :: m a }
|
172 | 173 | deriving (Alternative, Applicative, Functor, Monad)
|
|
0 commit comments