hls-eval-plugin-1.1.0.0: Eval plugin for Haskell Language Server
Safe HaskellNone
LanguageHaskell2010

Ide.Plugin.Eval.Types

Synopsis

Documentation

locate :: Loc [a] -> [Loc a] Source #

locate0 :: [a] -> [Loc a] Source #

data Test Source #

Constructors

Example 
Property 

Fields

Instances

Instances details
Eq Test Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Methods

(==) :: Test -> Test -> Bool #

(/=) :: Test -> Test -> Bool #

Show Test Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Methods

showsPrec :: Int -> Test -> ShowS #

show :: Test -> String #

showList :: [Test] -> ShowS #

Generic Test Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Associated Types

type Rep Test :: Type -> Type #

Methods

from :: Test -> Rep Test x #

to :: Rep Test x -> Test #

ToJSON Test Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

FromJSON Test Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

NFData Test Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Methods

rnf :: Test -> () #

type Rep Test Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

type Rep Test = D1 ('MetaData "Test" "Ide.Plugin.Eval.Types" "hls-eval-plugin-1.1.0.0-43E0Dbls0ww9Dxeum0NBZ7" 'False) (C1 ('MetaCons "Example" 'PrefixI 'True) (S1 ('MetaSel ('Just "testLines") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Txt)) :*: (S1 ('MetaSel ('Just "testOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Txt]) :*: S1 ('MetaSel ('Just "testRange") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))) :+: C1 ('MetaCons "Property" 'PrefixI 'True) (S1 ('MetaSel ('Just "testline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Txt) :*: (S1 ('MetaSel ('Just "testOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Txt]) :*: S1 ('MetaSel ('Just "testRange") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))))

data Format Source #

Constructors

SingleLine 
MultiLine Range

Range is that of surrounding entire block comment, not section. Used for detecting no-newline test commands.

Instances

Instances details
Eq Format Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Methods

(==) :: Format -> Format -> Bool #

(/=) :: Format -> Format -> Bool #

Ord Format Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Show Format Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Generic Format Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Associated Types

type Rep Format :: Type -> Type #

Methods

from :: Format -> Rep Format x #

to :: Rep Format x -> Format #

ToJSON Format Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

FromJSON Format Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

NFData Format Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Methods

rnf :: Format -> () #

type Rep Format Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

type Rep Format = D1 ('MetaData "Format" "Ide.Plugin.Eval.Types" "hls-eval-plugin-1.1.0.0-43E0Dbls0ww9Dxeum0NBZ7" 'False) (C1 ('MetaCons "SingleLine" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiLine" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)))

data Language Source #

Constructors

Plain 
Haddock 

Instances

Instances details
Eq Language Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Ord Language Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Show Language Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Generic Language Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Associated Types

type Rep Language :: Type -> Type #

Methods

from :: Language -> Rep Language x #

to :: Rep Language x -> Language #

ToJSON Language Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

FromJSON Language Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

NFData Language Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Methods

rnf :: Language -> () #

type Rep Language Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

type Rep Language = D1 ('MetaData "Language" "Ide.Plugin.Eval.Types" "hls-eval-plugin-1.1.0.0-43E0Dbls0ww9Dxeum0NBZ7" 'False) (C1 ('MetaCons "Plain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Haddock" 'PrefixI 'False) (U1 :: Type -> Type))

data Section Source #

Instances

Instances details
Eq Section Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Methods

(==) :: Section -> Section -> Bool #

(/=) :: Section -> Section -> Bool #

Show Section Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Generic Section Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Associated Types

type Rep Section :: Type -> Type #

Methods

from :: Section -> Rep Section x #

to :: Rep Section x -> Section #

ToJSON Section Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

FromJSON Section Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

NFData Section Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Methods

rnf :: Section -> () #

type Rep Section Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

type Rep Section = D1 ('MetaData "Section" "Ide.Plugin.Eval.Types" "hls-eval-plugin-1.1.0.0-43E0Dbls0ww9Dxeum0NBZ7" '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))))

data Sections Source #

Constructors

Sections 

Instances

Instances details
Eq Sections Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Show Sections Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Generic Sections Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Associated Types

type Rep Sections :: Type -> Type #

Methods

from :: Sections -> Rep Sections x #

to :: Rep Sections x -> Sections #

type Rep Sections Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

type Rep Sections = D1 ('MetaData "Sections" "Ide.Plugin.Eval.Types" "hls-eval-plugin-1.1.0.0-43E0Dbls0ww9Dxeum0NBZ7" 'False) (C1 ('MetaCons "Sections" 'PrefixI 'True) (S1 ('MetaSel ('Just "nonSetupSections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Section]) :*: S1 ('MetaSel ('Just "setupSections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Section])))

splitSections :: [Section] -> ([Section], [Section]) Source #

Split setup and normal sections

type Loc = Located Line Source #

data Located l a Source #

A thing with a location attached.

Constructors

Located 

Fields

Instances

Instances details
Functor (Located l) Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Methods

fmap :: (a -> b) -> Located l a -> Located l b #

(<$) :: a -> Located l b -> Located l a #

(Eq l, Eq a) => Eq (Located l a) Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Methods

(==) :: Located l a -> Located l a -> Bool #

(/=) :: Located l a -> Located l a -> Bool #

(Ord l, Ord a) => Ord (Located l a) Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Methods

compare :: Located l a -> Located l a -> Ordering #

(<) :: Located l a -> Located l a -> Bool #

(<=) :: Located l a -> Located l a -> Bool #

(>) :: Located l a -> Located l a -> Bool #

(>=) :: Located l a -> Located l a -> Bool #

max :: Located l a -> Located l a -> Located l a #

min :: Located l a -> Located l a -> Located l a #

(Show l, Show a) => Show (Located l a) Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Methods

showsPrec :: Int -> Located l a -> ShowS #

show :: Located l a -> String #

showList :: [Located l a] -> ShowS #

Generic (Located l a) Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Associated Types

type Rep (Located l a) :: Type -> Type #

Methods

from :: Located l a -> Rep (Located l a) x #

to :: Rep (Located l a) x -> Located l a #

(ToJSON a, ToJSON l) => ToJSON (Located l a) Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

(FromJSON l, FromJSON a) => FromJSON (Located l a) Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

(NFData l, NFData a) => NFData (Located l a) Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Methods

rnf :: Located l a -> () #

type Rep (Located l a) Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

type Rep (Located l a) = D1 ('MetaData "Located" "Ide.Plugin.Eval.Types" "hls-eval-plugin-1.1.0.0-43E0Dbls0ww9Dxeum0NBZ7" 'False) (C1 ('MetaCons "Located" 'PrefixI 'True) (S1 ('MetaSel ('Just "location") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Just "located") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data Comments Source #

Instances

Instances details
Eq Comments Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Ord Comments Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Show Comments Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Generic Comments Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Associated Types

type Rep Comments :: Type -> Type #

Methods

from :: Comments -> Rep Comments x #

to :: Rep Comments x -> Comments #

Semigroup Comments Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Monoid Comments Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

type Rep Comments Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

type Rep Comments = D1 ('MetaData "Comments" "Ide.Plugin.Eval.Types" "hls-eval-plugin-1.1.0.0-43E0Dbls0ww9Dxeum0NBZ7" '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 #

Constructors

RawBlockComment 

Instances

Instances details
Eq RawBlockComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Ord RawBlockComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Show RawBlockComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

IsString RawBlockComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Semigroup RawBlockComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Monoid RawBlockComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Stream RawBlockComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Associated Types

type Token RawBlockComment #

type Tokens RawBlockComment #

VisualStream RawBlockComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

TraversableStream RawBlockComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

type Tokens RawBlockComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

type Token RawBlockComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

newtype RawLineComment Source #

Constructors

RawLineComment 

Instances

Instances details
Eq RawLineComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Ord RawLineComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Show RawLineComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

IsString RawLineComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Semigroup RawLineComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Monoid RawLineComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Stream RawLineComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Associated Types

type Token RawLineComment #

type Tokens RawLineComment #

VisualStream RawLineComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

TraversableStream RawLineComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

type Tokens RawLineComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

type Token RawLineComment Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

unLoc :: Located l a -> a Source #

Discard location information.

data EvalParams Source #

Specify the test section to execute

Constructors

EvalParams 

Fields

Instances

Instances details
Eq EvalParams Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Show EvalParams Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Generic EvalParams Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

Associated Types

type Rep EvalParams :: Type -> Type #

ToJSON EvalParams Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

FromJSON EvalParams Source # 
Instance details

Defined in Ide.Plugin.Eval.Types

type Rep EvalParams Source # 
Instance details

Defined in Ide.Plugin.Eval.Types