Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- locate :: Loc [a] -> [Loc a]
- locate0 :: [a] -> [Loc a]
- data Test
- isProperty :: Test -> Bool
- data Format
- = SingleLine
- | MultiLine Range
- data Language
- data Section = Section {
- sectionName :: Txt
- sectionTests :: [Test]
- sectionLanguage :: Language
- sectionFormat :: Format
- data Sections = Sections {
- nonSetupSections :: [Section]
- setupSections :: [Section]
- hasTests :: Section -> Bool
- hasPropertyTest :: Section -> Bool
- splitSections :: [Section] -> ([Section], [Section])
- type Loc = Located Line
- data Located l a = Located {}
- data Comments = Comments {
- lineComments :: Map Range RawLineComment
- blockComments :: Map Range RawBlockComment
- newtype RawBlockComment = RawBlockComment {}
- newtype RawLineComment = RawLineComment {}
- unLoc :: Located l a -> a
- type Txt = String
- data EvalParams = EvalParams {}
- data GetEvalComments = GetEvalComments
- data IsEvaluating = IsEvaluating
- nullComments :: Comments -> Bool
Documentation
Instances
isProperty :: Test -> Bool Source #
SingleLine | |
MultiLine Range |
|
Instances
FromJSON Format Source # | |
Defined in Ide.Plugin.Eval.Types | |
ToJSON Format Source # | |
Generic Format Source # | |
Show Format Source # | |
NFData Format Source # | |
Defined in Ide.Plugin.Eval.Types | |
Eq Format Source # | |
Ord Format Source # | |
type Rep Format Source # | |
Defined in Ide.Plugin.Eval.Types type Rep Format = D1 ('MetaData "Format" "Ide.Plugin.Eval.Types" "haskell-language-server-2.7.0.0-2oUnW5nYLZr1ZEP5BrOqIa-hls-eval-plugin" 'False) (C1 ('MetaCons "SingleLine" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiLine" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))) |
Instances
FromJSON Language Source # | |
Defined in Ide.Plugin.Eval.Types | |
ToJSON Language Source # | |
Generic Language Source # | |
Show Language Source # | |
NFData Language Source # | |
Defined in Ide.Plugin.Eval.Types | |
Eq Language Source # | |
Ord Language Source # | |
Defined in Ide.Plugin.Eval.Types | |
type Rep Language Source # | |
Defined in Ide.Plugin.Eval.Types |
Section | |
|
Instances
FromJSON Section Source # | |
Defined in Ide.Plugin.Eval.Types | |
ToJSON Section Source # | |
Generic Section Source # | |
Show Section Source # | |
NFData Section Source # | |
Defined in Ide.Plugin.Eval.Types | |
Eq Section Source # | |
type Rep Section Source # | |
Defined in Ide.Plugin.Eval.Types type Rep Section = D1 ('MetaData "Section" "Ide.Plugin.Eval.Types" "haskell-language-server-2.7.0.0-2oUnW5nYLZr1ZEP5BrOqIa-hls-eval-plugin" 'False) (C1 ('MetaCons "Section" 'PrefixI 'True) ((S1 ('MetaSel ('Just "sectionName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Txt) :*: S1 ('MetaSel ('Just "sectionTests") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Test])) :*: (S1 ('MetaSel ('Just "sectionLanguage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Language) :*: S1 ('MetaSel ('Just "sectionFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Format)))) |
Sections | |
|
Instances
Generic Sections Source # | |
Show Sections Source # | |
Eq Sections Source # | |
type Rep Sections Source # | |
Defined in Ide.Plugin.Eval.Types type Rep Sections = D1 ('MetaData "Sections" "Ide.Plugin.Eval.Types" "haskell-language-server-2.7.0.0-2oUnW5nYLZr1ZEP5BrOqIa-hls-eval-plugin" 'False) (C1 ('MetaCons "Sections" 'PrefixI 'True) (S1 ('MetaSel ('Just "nonSetupSections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Section]) :*: S1 ('MetaSel ('Just "setupSections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Section]))) |
hasPropertyTest :: Section -> Bool Source #
A thing with a location attached.
Instances
Functor (Located l) Source # | |
(FromJSON l, FromJSON a) => FromJSON (Located l a) Source # | |
Defined in Ide.Plugin.Eval.Types | |
(ToJSON a, ToJSON l) => ToJSON (Located l a) Source # | |
Generic (Located l a) Source # | |
(Show l, Show a) => Show (Located l a) Source # | |
(NFData l, NFData a) => NFData (Located l a) Source # | |
Defined in Ide.Plugin.Eval.Types | |
(Eq l, Eq a) => Eq (Located l a) Source # | |
(Ord l, Ord a) => Ord (Located l a) Source # | |
Defined in Ide.Plugin.Eval.Types | |
type Rep (Located l a) Source # | |
Defined in Ide.Plugin.Eval.Types type Rep (Located l a) = D1 ('MetaData "Located" "Ide.Plugin.Eval.Types" "haskell-language-server-2.7.0.0-2oUnW5nYLZr1ZEP5BrOqIa-hls-eval-plugin" 'False) (C1 ('MetaCons "Located" 'PrefixI 'True) (S1 ('MetaSel ('Just "location") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Just "located") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) |
Comments | |
|
Instances
Monoid Comments Source # | |
Semigroup Comments Source # | |
Generic Comments Source # | |
Show Comments Source # | |
NFData Comments Source # | |
Defined in Ide.Plugin.Eval.Types | |
Eq Comments Source # | |
Ord Comments Source # | |
Defined in Ide.Plugin.Eval.Types | |
type Rep Comments Source # | |
Defined in Ide.Plugin.Eval.Types type Rep Comments = D1 ('MetaData "Comments" "Ide.Plugin.Eval.Types" "haskell-language-server-2.7.0.0-2oUnW5nYLZr1ZEP5BrOqIa-hls-eval-plugin" 'False) (C1 ('MetaCons "Comments" 'PrefixI 'True) (S1 ('MetaSel ('Just "lineComments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Range RawLineComment)) :*: S1 ('MetaSel ('Just "blockComments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Range RawBlockComment)))) |
newtype RawBlockComment Source #
Instances
newtype RawLineComment Source #
Instances
data EvalParams Source #
Specify the test section to execute
Instances
FromJSON EvalParams Source # | |
Defined in Ide.Plugin.Eval.Types parseJSON :: Value -> Parser EvalParams # parseJSONList :: Value -> Parser [EvalParams] # | |
ToJSON EvalParams Source # | |
Defined in Ide.Plugin.Eval.Types toJSON :: EvalParams -> Value # toEncoding :: EvalParams -> Encoding # toJSONList :: [EvalParams] -> Value # toEncodingList :: [EvalParams] -> Encoding # omitField :: EvalParams -> Bool # | |
Generic EvalParams Source # | |
Defined in Ide.Plugin.Eval.Types type Rep EvalParams :: Type -> Type # from :: EvalParams -> Rep EvalParams x # to :: Rep EvalParams x -> EvalParams # | |
Show EvalParams Source # | |
Defined in Ide.Plugin.Eval.Types showsPrec :: Int -> EvalParams -> ShowS # show :: EvalParams -> String # showList :: [EvalParams] -> ShowS # | |
Eq EvalParams Source # | |
Defined in Ide.Plugin.Eval.Types (==) :: EvalParams -> EvalParams -> Bool # (/=) :: EvalParams -> EvalParams -> Bool # | |
type Rep EvalParams Source # | |
Defined in Ide.Plugin.Eval.Types |
data GetEvalComments Source #
Instances
Generic GetEvalComments Source # | |
Defined in Ide.Plugin.Eval.Types type Rep GetEvalComments :: Type -> Type # from :: GetEvalComments -> Rep GetEvalComments x # to :: Rep GetEvalComments x -> GetEvalComments # | |
Show GetEvalComments Source # | |
Defined in Ide.Plugin.Eval.Types showsPrec :: Int -> GetEvalComments -> ShowS # show :: GetEvalComments -> String # showList :: [GetEvalComments] -> ShowS # | |
NFData GetEvalComments Source # | |
Defined in Ide.Plugin.Eval.Types rnf :: GetEvalComments -> () # | |
Eq GetEvalComments Source # | |
Defined in Ide.Plugin.Eval.Types (==) :: GetEvalComments -> GetEvalComments -> Bool # (/=) :: GetEvalComments -> GetEvalComments -> Bool # | |
Hashable GetEvalComments Source # | |
Defined in Ide.Plugin.Eval.Types hashWithSalt :: Int -> GetEvalComments -> Int # hash :: GetEvalComments -> Int # | |
type Rep GetEvalComments Source # | |
type RuleResult GetEvalComments Source # | |
Defined in Ide.Plugin.Eval.Types |
data IsEvaluating Source #
Instances
Generic IsEvaluating Source # | |
Defined in Ide.Plugin.Eval.Types type Rep IsEvaluating :: Type -> Type # from :: IsEvaluating -> Rep IsEvaluating x # to :: Rep IsEvaluating x -> IsEvaluating # | |
Show IsEvaluating Source # | |
Defined in Ide.Plugin.Eval.Types showsPrec :: Int -> IsEvaluating -> ShowS # show :: IsEvaluating -> String # showList :: [IsEvaluating] -> ShowS # | |
NFData IsEvaluating Source # | |
Defined in Ide.Plugin.Eval.Types rnf :: IsEvaluating -> () # | |
Eq IsEvaluating Source # | |
Defined in Ide.Plugin.Eval.Types (==) :: IsEvaluating -> IsEvaluating -> Bool # (/=) :: IsEvaluating -> IsEvaluating -> Bool # | |
Hashable IsEvaluating Source # | |
Defined in Ide.Plugin.Eval.Types hashWithSalt :: Int -> IsEvaluating -> Int # hash :: IsEvaluating -> Int # | |
type Rep IsEvaluating Source # | |
type RuleResult IsEvaluating Source # | |
Defined in Ide.Plugin.Eval.Types |
nullComments :: Comments -> Bool Source #