module Hint.Comment(commentHint) where
import Hint.Type
import Data.Char
import Data.List.Extra
import Refact.Types(Refactoring(ModifyComment))
import GHC.Types.SrcLoc
import GHC.Parser.Annotation
import GHC.Util
directives :: [String]
directives :: [String]
directives = String -> [String]
words (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$
String
"LANGUAGE OPTIONS_GHC INCLUDE WARNING DEPRECATED MINIMAL INLINE NOINLINE INLINABLE " String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"CONLIKE LINE SPECIALIZE SPECIALISE UNPACK NOUNPACK SOURCE"
commentHint :: ModuHint
Scope
_ ModuleEx
m = (LEpaComment -> [Idea]) -> [LEpaComment] -> [Idea]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap LEpaComment -> [Idea]
chk (ModuleEx -> [LEpaComment]
ghcComments ModuleEx
m)
where
chk :: LEpaComment -> [Idea]
chk :: LEpaComment -> [Idea]
chk LEpaComment
comm
| Bool
isMultiline, String
"#" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
s Bool -> Bool -> Bool
&& Bool -> Bool
not (String
"#" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
s) = [String -> LEpaComment -> String -> Idea
grab String
"Fix pragma markup" LEpaComment
comm (String -> Idea) -> String -> Idea
forall a b. (a -> b) -> a -> b
$ Char
'#'Char -> String -> String
forall a. a -> [a] -> [a]
:String
s]
| Bool
isMultiline, String
name String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
directives = [String -> LEpaComment -> String -> Idea
grab String
"Use pragma syntax" LEpaComment
comm (String -> Idea) -> String -> Idea
forall a b. (a -> b) -> a -> b
$ String
"# " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
trim String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" #"]
where
isMultiline :: Bool
isMultiline = LEpaComment -> Bool
isCommentMultiline LEpaComment
comm
s :: String
s = LEpaComment -> String
commentText LEpaComment
comm
name :: String
name = (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (\Char
x -> Char -> Bool
isAlphaNum Char
x Bool -> Bool -> Bool
|| Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_') (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String -> String
trimStart String
s
chk LEpaComment
_ = []
grab :: String -> LEpaComment -> String -> Idea
grab :: String -> LEpaComment -> String -> Idea
grab String
msg o :: LEpaComment
o@(L Anchor
pos EpaComment
_) String
s2 =
let s1 :: String
s1 = LEpaComment -> String
commentText LEpaComment
o
loc :: SrcSpan
loc = RealSrcSpan -> Maybe BufSpan -> SrcSpan
RealSrcSpan (Anchor -> RealSrcSpan
anchor Anchor
pos) Maybe BufSpan
forall a. Maybe a
Nothing
in
Severity
-> String
-> SrcSpan
-> String
-> Maybe String
-> [Note]
-> [Refactoring SrcSpan]
-> Idea
rawIdea Severity
Suggestion String
msg SrcSpan
loc (String -> String
f String
s1) (String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ String -> String
f String
s2) [] (SrcSpan -> [Refactoring SrcSpan]
refact SrcSpan
loc)
where f :: String -> String
f String
s = if LEpaComment -> Bool
isCommentMultiline LEpaComment
o then String
"{-" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"-}" else String
"--" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
refact :: SrcSpan -> [Refactoring SrcSpan]
refact SrcSpan
loc = [SrcSpan -> String -> Refactoring SrcSpan
forall a. a -> String -> Refactoring a
ModifyComment (SrcSpan -> SrcSpan
toRefactSrcSpan SrcSpan
loc) (String -> String
f String
s2)]