hls-tactics-plugin-1.4.0.0: Wingman plugin for Haskell Language Server
Safe HaskellNone
LanguageHaskell2010

Wingman.EmptyCase

Synopsis

Documentation

data EmptyCaseT Source #

Constructors

EmptyCaseT 

Instances

Instances details
IsTarget EmptyCaseT Source # 
Instance details

Defined in Wingman.EmptyCase

Associated Types

type TargetArgs EmptyCaseT Source #

IsContinuationSort EmptyCaseT Source # 
Instance details

Defined in Wingman.EmptyCase

type TargetArgs EmptyCaseT Source # 
Instance details

Defined in Wingman.EmptyCase

mkEmptyCaseLensDesc :: Type -> Text Source #

The description for the empty case lens.

hush :: Either e a -> Maybe a Source #

Silence an error.

graftMatchGroup :: SrcSpan -> Located [LMatch GhcPs (LHsExpr GhcPs)] -> Graft (Either String) ParsedSource Source #

Graft a RunTacticResults into the correct place in an AST. Correctly deals with top-level holes, in which we might need to fiddle with the Matchs that bind variables.

fromMaybeT :: Functor m => a -> MaybeT m a -> m a Source #

emptyCaseScrutinees :: IdeState -> NormalizedFilePath -> MaybeT IO [(Tracked 'Current RealSrcSpan, Type)] Source #

Find the last typechecked module, and find the most specific span, as well as the judgement at the given range.

data EmptyCaseSort a Source #

Constructors

EmptyCase a 
EmptyLamCase a 

Instances

Instances details
Functor EmptyCaseSort Source # 
Instance details

Defined in Wingman.EmptyCase

Methods

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

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

Foldable EmptyCaseSort Source # 
Instance details

Defined in Wingman.EmptyCase

Methods

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

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

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

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

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

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

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

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

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

toList :: EmptyCaseSort a -> [a] #

null :: EmptyCaseSort a -> Bool #

length :: EmptyCaseSort a -> Int #

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

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

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

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

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

Traversable EmptyCaseSort Source # 
Instance details

Defined in Wingman.EmptyCase

Methods

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

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

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

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

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

Defined in Wingman.EmptyCase

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

Defined in Wingman.EmptyCase

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

Defined in Wingman.EmptyCase

emptyCaseQ :: GenericQ [(SrcSpan, EmptyCaseSort (HsExpr GhcTc))] Source #

Get the SrcSpan and scrutinee of every empty case.