weeder-2.8.0: Detect dead code
Safe HaskellSafe-Inferred
LanguageHaskell2010

Weeder.Config

Synopsis

Config

type Config = ConfigType Regex Source #

Configuration for Weeder analysis.

type ConfigParsed = ConfigType String Source #

Configuration that has been parsed from TOML (and can still be converted back), but not yet compiled to a Config.

data ConfigType a Source #

Underlying type for Config and ConfigParsed.

Constructors

Config 

Fields

  • rootPatterns :: [a]

    Any declarations matching these regular expressions will be added to the root set.

  • typeClassRoots :: Bool

    If True, consider all declarations in a type class as part of the root set. Overrides root-instances.

  • rootInstances :: [InstancePattern a]

    All matching instances will be added to the root set. An absent field will always match.

  • unusedTypes :: Bool

    Toggle to look for and output unused types. Type family instances will be marked as implicit roots.

Instances

Instances details
DecodeTOML Config Source # 
Instance details

Defined in Weeder.Config

DecodeTOML ConfigParsed Source # 
Instance details

Defined in Weeder.Config

Show a => Show (ConfigType a) Source # 
Instance details

Defined in Weeder.Config

Eq a => Eq (ConfigType a) Source # 
Instance details

Defined in Weeder.Config

Methods

(==) :: ConfigType a -> ConfigType a -> Bool #

(/=) :: ConfigType a -> ConfigType a -> Bool #

Marking instances as roots

data InstancePattern a Source #

Construct via InstanceOnly, ClassOnly or ModuleOnly, and combine with the Semigroup instance. The Semigroup instance ignores duplicate fields, prioritising the left argument.

Instances

Instances details
Foldable InstancePattern Source # 
Instance details

Defined in Weeder.Config

Methods

fold :: Monoid m => InstancePattern m -> m #

foldMap :: Monoid m => (a -> m) -> InstancePattern a -> m #

foldMap' :: Monoid m => (a -> m) -> InstancePattern a -> m #

foldr :: (a -> b -> b) -> b -> InstancePattern a -> b #

foldr' :: (a -> b -> b) -> b -> InstancePattern a -> b #

foldl :: (b -> a -> b) -> b -> InstancePattern a -> b #

foldl' :: (b -> a -> b) -> b -> InstancePattern a -> b #

foldr1 :: (a -> a -> a) -> InstancePattern a -> a #

foldl1 :: (a -> a -> a) -> InstancePattern a -> a #

toList :: InstancePattern a -> [a] #

null :: InstancePattern a -> Bool #

length :: InstancePattern a -> Int #

elem :: Eq a => a -> InstancePattern a -> Bool #

maximum :: Ord a => InstancePattern a -> a #

minimum :: Ord a => InstancePattern a -> a #

sum :: Num a => InstancePattern a -> a #

product :: Num a => InstancePattern a -> a #

Traversable InstancePattern Source # 
Instance details

Defined in Weeder.Config

Methods

traverse :: Applicative f => (a -> f b) -> InstancePattern a -> f (InstancePattern b) #

sequenceA :: Applicative f => InstancePattern (f a) -> f (InstancePattern a) #

mapM :: Monad m => (a -> m b) -> InstancePattern a -> m (InstancePattern b) #

sequence :: Monad m => InstancePattern (m a) -> m (InstancePattern a) #

Functor InstancePattern Source # 
Instance details

Defined in Weeder.Config

Methods

fmap :: (a -> b) -> InstancePattern a -> InstancePattern b #

(<$) :: a -> InstancePattern b -> InstancePattern a #

Semigroup (InstancePattern a) Source # 
Instance details

Defined in Weeder.Config

Show a => Show (InstancePattern a) Source # 
Instance details

Defined in Weeder.Config

Eq a => Eq (InstancePattern a) Source # 
Instance details

Defined in Weeder.Config

Ord a => Ord (InstancePattern a) Source # 
Instance details

Defined in Weeder.Config

DecodeTOML (InstancePattern String) Source # 
Instance details

Defined in Weeder.Config

pattern ClassOnly :: a -> InstancePattern a Source #