module Hint.Type(
DeclHint, ModuHint, CrossHint, Hint(..),
module Export
) where
import Data.Semigroup
import Config.Type
import GHC.All as Export
import Idea as Export
import Prelude
import Refact as Export
import GHC.Hs.Extension
import GHC.Hs.Decls
import GHC.Util.Scope
type DeclHint = Scope -> ModuleEx -> LHsDecl GhcPs -> [Idea]
type ModuHint = Scope -> ModuleEx -> [Idea]
type CrossHint = [(Scope, ModuleEx)] -> [Idea]
data Hint = Hint
{ Hint -> [Setting] -> [(Scope, ModuleEx)] -> [Idea]
hintModules :: [Setting] -> [(Scope, ModuleEx)] -> [Idea]
, Hint -> [Setting] -> Scope -> ModuleEx -> [Idea]
hintModule :: [Setting] -> Scope -> ModuleEx -> [Idea]
, Hint -> [Setting] -> Scope -> ModuleEx -> LHsDecl GhcPs -> [Idea]
hintDecl :: [Setting] -> Scope -> ModuleEx -> LHsDecl GhcPs -> [Idea]
}
instance Semigroup Hint where
Hint [Setting] -> [(Scope, ModuleEx)] -> [Idea]
x1 [Setting] -> Scope -> ModuleEx -> [Idea]
x2 [Setting] -> Scope -> ModuleEx -> LHsDecl GhcPs -> [Idea]
x3 <> :: Hint -> Hint -> Hint
<> Hint [Setting] -> [(Scope, ModuleEx)] -> [Idea]
y1 [Setting] -> Scope -> ModuleEx -> [Idea]
y2 [Setting] -> Scope -> ModuleEx -> LHsDecl GhcPs -> [Idea]
y3 = ([Setting] -> [(Scope, ModuleEx)] -> [Idea])
-> ([Setting] -> Scope -> ModuleEx -> [Idea])
-> ([Setting] -> Scope -> ModuleEx -> LHsDecl GhcPs -> [Idea])
-> Hint
Hint
(\[Setting]
a [(Scope, ModuleEx)]
b -> [Setting] -> [(Scope, ModuleEx)] -> [Idea]
x1 [Setting]
a [(Scope, ModuleEx)]
b [Idea] -> [Idea] -> [Idea]
forall a. [a] -> [a] -> [a]
++ [Setting] -> [(Scope, ModuleEx)] -> [Idea]
y1 [Setting]
a [(Scope, ModuleEx)]
b)
(\[Setting]
a Scope
b ModuleEx
c -> [Setting] -> Scope -> ModuleEx -> [Idea]
x2 [Setting]
a Scope
b ModuleEx
c [Idea] -> [Idea] -> [Idea]
forall a. [a] -> [a] -> [a]
++ [Setting] -> Scope -> ModuleEx -> [Idea]
y2 [Setting]
a Scope
b ModuleEx
c)
(\[Setting]
a Scope
b ModuleEx
c LHsDecl GhcPs
d -> [Setting] -> Scope -> ModuleEx -> LHsDecl GhcPs -> [Idea]
x3 [Setting]
a Scope
b ModuleEx
c LHsDecl GhcPs
d [Idea] -> [Idea] -> [Idea]
forall a. [a] -> [a] -> [a]
++ [Setting] -> Scope -> ModuleEx -> LHsDecl GhcPs -> [Idea]
y3 [Setting]
a Scope
b ModuleEx
c LHsDecl GhcPs
d)
instance Monoid Hint where
mempty :: Hint
mempty = ([Setting] -> [(Scope, ModuleEx)] -> [Idea])
-> ([Setting] -> Scope -> ModuleEx -> [Idea])
-> ([Setting] -> Scope -> ModuleEx -> LHsDecl GhcPs -> [Idea])
-> Hint
Hint (\[Setting]
_ [(Scope, ModuleEx)]
_ -> []) (\[Setting]
_ Scope
_ ModuleEx
_ -> []) (\[Setting]
_ Scope
_ ModuleEx
_ LHsDecl GhcPs
_ -> [])
mappend :: Hint -> Hint -> Hint
mappend = Hint -> Hint -> Hint
forall a. Semigroup a => a -> a -> a
(<>)