{-
<TEST>
{- MISSING HASH #-} -- {-# MISSING HASH #-}
<COMMENT> {- INLINE X -}
{- INLINE Y -} -- {-# INLINE Y #-}
{- INLINE[~k] f -} -- {-# INLINE[~k] f #-}
{- NOINLINE Y -} -- {-# NOINLINE Y #-}
{- UNKNOWN Y -}
<COMMENT> INLINE X
</TEST>
-}


module Hint.Comment(commentHint) where

import Hint.Type
import Data.Char
import Data.List.Extra
import Refact.Types(Refactoring(ModifyComment))
import SrcLoc
import ApiAnnotation
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
commentHint :: ModuHint
commentHint Scope
_ ModuleEx
m = (Located AnnotationComment -> [Idea])
-> [Located AnnotationComment] -> [Idea]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Located AnnotationComment -> [Idea]
chk (ModuleEx -> [Located AnnotationComment]
ghcComments ModuleEx
m)
    where
        chk :: Located AnnotationComment -> [Idea]
        chk :: Located AnnotationComment -> [Idea]
chk Located AnnotationComment
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 -> Located AnnotationComment -> String -> Idea
grab String
"Fix pragma markup" Located AnnotationComment
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 -> Located AnnotationComment -> String -> Idea
grab String
"Use pragma syntax" Located AnnotationComment
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 = Located AnnotationComment -> Bool
isCommentMultiline Located AnnotationComment
comm
                 s :: String
s = Located AnnotationComment -> String
commentText Located AnnotationComment
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 Located AnnotationComment
_ = []

        grab :: String -> Located AnnotationComment -> String -> Idea
        grab :: String -> Located AnnotationComment -> String -> Idea
grab String
msg o :: Located AnnotationComment
o@(L SrcSpan
pos AnnotationComment
_) String
s2 =
          let s1 :: String
s1 = Located AnnotationComment -> String
commentText Located AnnotationComment
o in
          Severity
-> String
-> SrcSpan
-> String
-> Maybe String
-> [Note]
-> [Refactoring SrcSpan]
-> Idea
rawIdea Severity
Suggestion String
msg SrcSpan
pos (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) [] [Refactoring SrcSpan]
refact
            where f :: String -> String
f String
s = if Located AnnotationComment -> Bool
isCommentMultiline Located AnnotationComment
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 :: [Refactoring SrcSpan]
refact = [SrcSpan -> String -> Refactoring SrcSpan
forall a. a -> String -> Refactoring a
ModifyComment (SrcSpan -> SrcSpan
toRefactSrcSpan SrcSpan
pos) (String -> String
f String
s2)]