{-# LANGUAGE ViewPatterns #-}
module Hint.Bracket(bracketHint) where
import Hint.Type
bracketHint :: DeclHint
bracketHint _ _ x =
concatMap (\x -> bracket True x ++ dollar x) (childrenBi (descendBi annotations x) :: [Exp_]) ++
concatMap (bracket False) (childrenBi x :: [Type_]) ++
concatMap (bracket False) (childrenBi x :: [Pat_]) ++
concatMap fieldDecl (childrenBi x)
where
annotations :: Annotation S -> Annotation S
annotations = descendBi $ \x -> case (x :: Exp_) of
Paren _ x -> x
x -> x
bracket :: (Annotated a, Uniplate (a S), ExactP a, Pretty (a S), Brackets (a S)) => Bool -> a S -> [Idea]
bracket bad = f Nothing
where
msg = "Redundant bracket"
f :: (Annotated a, Uniplate (a S), ExactP a, Pretty (a S), Brackets (a S)) => Maybe (Int,a S,a S -> a S) -> a S -> [Idea]
f Just{} o@(remParen -> Just x) | isAtom x = err msg o x : g x
f Nothing o@(remParen -> Just x) | bad = warn msg o x : g x
f (Just (i,o,gen)) (remParen -> Just x) | not $ needBracket i o x = warn msg o (gen x) : g x
f _ x = g x
g :: (Annotated a, Uniplate (a S), ExactP a, Pretty (a S), Brackets (a S)) => a S -> [Idea]
g o = concat [f (Just (i,o,gen)) x | (i,(x,gen)) <- zip [0..] $ holes o]
fieldDecl :: FieldDecl S -> [Idea]
fieldDecl o@(FieldDecl a b (UnBangedTy c (TyParen _ d)))
= [warn "Redundant bracket" o (FieldDecl a b (UnBangedTy c d))]
fieldDecl _ = []
dollar :: Exp_ -> [Idea]
dollar = concatMap f . universe
where
msg = warn "Redundant $"
f x = [msg x y | InfixApp _ a d b <- [x], opExp d ~= "$"
,let y = App an a b, not $ needBracket 0 y a, not $ needBracket 1 y b]
++
[msg x (t y) |(t, Paren _ (InfixApp _ a1 op1 a2)) <- splitInfix x
,opExp op1 ~= "$", isVar a1 || isApp a1 || isParen a1, not $ isAtom a2
,let y = App an a1 (Paren an a2)]
splitInfix :: Exp_ -> [(Exp_ -> Exp_, Exp_)]
splitInfix (InfixApp s a b c) = [(InfixApp s a b, c), (\a -> InfixApp s a b c, a)]
splitInfix _ = []