{-# LANGUAGE DeriveAnyClass             #-}
{-# LANGUAGE DeriveFunctor              #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE DerivingStrategies         #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies               #-}
{-# LANGUAGE UndecidableInstances       #-}
{-# OPTIONS_GHC -Wwarn #-}
{-# LANGUAGE RecordWildCards            #-}

module Ide.Plugin.Eval.Types
    ( locate,
      locate0,
      Test (..),
      isProperty,
      Format (..),
      Language (..),
      Section (..),
      Sections (..),
      hasTests,
      hasPropertyTest,
      splitSections,
      Loc,
      Located (..),
      Comments (..),
      RawBlockComment (..),
      RawLineComment (..),
      unLoc,
      Txt,
      EvalParams(..),
      GetEvalComments(..),
      IsEvaluating(..),
      nullComments)
where

import           Control.DeepSeq               (deepseq)
import           Data.Aeson                    (FromJSON, ToJSON)
import           Data.List                     (partition)
import           Data.List.NonEmpty            (NonEmpty)
import           Data.Map.Strict               (Map)
import           Data.String                   (IsString (..))
import           Development.IDE               (Range, RuleResult)
import           Development.IDE.Graph.Classes
import           GHC.Generics                  (Generic)
import           Language.LSP.Protocol.Types   (TextDocumentIdentifier)
import qualified Text.Megaparsec               as P

-- | A thing with a location attached.
data Located l a = Located {forall l a. Located l a -> l
location :: l, forall l a. Located l a -> a
located :: a}
    deriving (Located l a -> Located l a -> Bool
(Located l a -> Located l a -> Bool)
-> (Located l a -> Located l a -> Bool) -> Eq (Located l a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall l a. (Eq l, Eq a) => Located l a -> Located l a -> Bool
$c== :: forall l a. (Eq l, Eq a) => Located l a -> Located l a -> Bool
== :: Located l a -> Located l a -> Bool
$c/= :: forall l a. (Eq l, Eq a) => Located l a -> Located l a -> Bool
/= :: Located l a -> Located l a -> Bool
Eq, Int -> Located l a -> ShowS
[Located l a] -> ShowS
Located l a -> String
(Int -> Located l a -> ShowS)
-> (Located l a -> String)
-> ([Located l a] -> ShowS)
-> Show (Located l a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall l a. (Show l, Show a) => Int -> Located l a -> ShowS
forall l a. (Show l, Show a) => [Located l a] -> ShowS
forall l a. (Show l, Show a) => Located l a -> String
$cshowsPrec :: forall l a. (Show l, Show a) => Int -> Located l a -> ShowS
showsPrec :: Int -> Located l a -> ShowS
$cshow :: forall l a. (Show l, Show a) => Located l a -> String
show :: Located l a -> String
$cshowList :: forall l a. (Show l, Show a) => [Located l a] -> ShowS
showList :: [Located l a] -> ShowS
Show, Eq (Located l a)
Eq (Located l a) =>
(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)
-> (Located l a -> Located l a -> Located l a)
-> (Located l a -> Located l a -> Located l a)
-> Ord (Located l a)
Located l a -> Located l a -> Bool
Located l a -> Located l a -> Ordering
Located l a -> Located l a -> Located l a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall l a. (Ord l, Ord a) => Eq (Located l a)
forall l a. (Ord l, Ord a) => Located l a -> Located l a -> Bool
forall l a.
(Ord l, Ord a) =>
Located l a -> Located l a -> Ordering
forall l a.
(Ord l, Ord a) =>
Located l a -> Located l a -> Located l a
$ccompare :: forall l a.
(Ord l, Ord a) =>
Located l a -> Located l a -> Ordering
compare :: Located l a -> Located l a -> Ordering
$c< :: forall l a. (Ord l, Ord a) => Located l a -> Located l a -> Bool
< :: Located l a -> Located l a -> Bool
$c<= :: forall l a. (Ord l, Ord a) => Located l a -> Located l a -> Bool
<= :: Located l a -> Located l a -> Bool
$c> :: forall l a. (Ord l, Ord a) => Located l a -> Located l a -> Bool
> :: Located l a -> Located l a -> Bool
$c>= :: forall l a. (Ord l, Ord a) => Located l a -> Located l a -> Bool
>= :: Located l a -> Located l a -> Bool
$cmax :: forall l a.
(Ord l, Ord a) =>
Located l a -> Located l a -> Located l a
max :: Located l a -> Located l a -> Located l a
$cmin :: forall l a.
(Ord l, Ord a) =>
Located l a -> Located l a -> Located l a
min :: Located l a -> Located l a -> Located l a
Ord, (forall a b. (a -> b) -> Located l a -> Located l b)
-> (forall a b. a -> Located l b -> Located l a)
-> Functor (Located l)
forall a b. a -> Located l b -> Located l a
forall a b. (a -> b) -> Located l a -> Located l b
forall l a b. a -> Located l b -> Located l a
forall l a b. (a -> b) -> Located l a -> Located l b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall l a b. (a -> b) -> Located l a -> Located l b
fmap :: forall a b. (a -> b) -> Located l a -> Located l b
$c<$ :: forall l a b. a -> Located l b -> Located l a
<$ :: forall a b. a -> Located l b -> Located l a
Functor, (forall x. Located l a -> Rep (Located l a) x)
-> (forall x. Rep (Located l a) x -> Located l a)
-> Generic (Located l a)
forall x. Rep (Located l a) x -> Located l a
forall x. Located l a -> Rep (Located l a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall l a x. Rep (Located l a) x -> Located l a
forall l a x. Located l a -> Rep (Located l a) x
$cfrom :: forall l a x. Located l a -> Rep (Located l a) x
from :: forall x. Located l a -> Rep (Located l a) x
$cto :: forall l a x. Rep (Located l a) x -> Located l a
to :: forall x. Rep (Located l a) x -> Located l a
Generic, Maybe (Located l a)
Value -> Parser [Located l a]
Value -> Parser (Located l a)
(Value -> Parser (Located l a))
-> (Value -> Parser [Located l a])
-> Maybe (Located l a)
-> FromJSON (Located l a)
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
forall l a. (FromJSON l, FromJSON a) => Maybe (Located l a)
forall l a.
(FromJSON l, FromJSON a) =>
Value -> Parser [Located l a]
forall l a.
(FromJSON l, FromJSON a) =>
Value -> Parser (Located l a)
$cparseJSON :: forall l a.
(FromJSON l, FromJSON a) =>
Value -> Parser (Located l a)
parseJSON :: Value -> Parser (Located l a)
$cparseJSONList :: forall l a.
(FromJSON l, FromJSON a) =>
Value -> Parser [Located l a]
parseJSONList :: Value -> Parser [Located l a]
$comittedField :: forall l a. (FromJSON l, FromJSON a) => Maybe (Located l a)
omittedField :: Maybe (Located l a)
FromJSON, [Located l a] -> Value
[Located l a] -> Encoding
Located l a -> Bool
Located l a -> Value
Located l a -> Encoding
(Located l a -> Value)
-> (Located l a -> Encoding)
-> ([Located l a] -> Value)
-> ([Located l a] -> Encoding)
-> (Located l a -> Bool)
-> ToJSON (Located l a)
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
forall l a. (ToJSON a, ToJSON l) => [Located l a] -> Value
forall l a. (ToJSON a, ToJSON l) => [Located l a] -> Encoding
forall l a. (ToJSON a, ToJSON l) => Located l a -> Bool
forall l a. (ToJSON a, ToJSON l) => Located l a -> Value
forall l a. (ToJSON a, ToJSON l) => Located l a -> Encoding
$ctoJSON :: forall l a. (ToJSON a, ToJSON l) => Located l a -> Value
toJSON :: Located l a -> Value
$ctoEncoding :: forall l a. (ToJSON a, ToJSON l) => Located l a -> Encoding
toEncoding :: Located l a -> Encoding
$ctoJSONList :: forall l a. (ToJSON a, ToJSON l) => [Located l a] -> Value
toJSONList :: [Located l a] -> Value
$ctoEncodingList :: forall l a. (ToJSON a, ToJSON l) => [Located l a] -> Encoding
toEncodingList :: [Located l a] -> Encoding
$comitField :: forall l a. (ToJSON a, ToJSON l) => Located l a -> Bool
omitField :: Located l a -> Bool
ToJSON)

-- | Discard location information.
unLoc :: Located l a -> a
unLoc :: forall l a. Located l a -> a
unLoc (Located l
_ a
a) = a
a

instance (NFData l, NFData a) => NFData (Located l a) where
    rnf :: Located l a -> ()
rnf (Located l
loc a
a) = l
loc l -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` a
a a -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()

type Loc = Located Line

type Line = Int

locate :: Loc [a] -> [Loc a]
locate :: forall a. Loc [a] -> [Loc a]
locate (Located Int
l [a]
tst) = (Int -> a -> Loc a) -> [Int] -> [a] -> [Loc a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> a -> Loc a
forall l a. l -> a -> Located l a
Located [Int
l ..] [a]
tst

locate0 :: [a] -> [Loc a]
locate0 :: forall a. [a] -> [Loc a]
locate0 = Loc [a] -> [Loc a]
forall a. Loc [a] -> [Loc a]
locate (Loc [a] -> [Loc a]) -> ([a] -> Loc [a]) -> [a] -> [Loc a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [a] -> Loc [a]
forall l a. l -> a -> Located l a
Located Int
0

type Txt = String

data Sections = Sections
    { Sections -> [Section]
nonSetupSections :: [Section]
    , Sections -> [Section]
setupSections    :: [Section]
    }
    deriving (Int -> Sections -> ShowS
[Sections] -> ShowS
Sections -> String
(Int -> Sections -> ShowS)
-> (Sections -> String) -> ([Sections] -> ShowS) -> Show Sections
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Sections -> ShowS
showsPrec :: Int -> Sections -> ShowS
$cshow :: Sections -> String
show :: Sections -> String
$cshowList :: [Sections] -> ShowS
showList :: [Sections] -> ShowS
Show, Sections -> Sections -> Bool
(Sections -> Sections -> Bool)
-> (Sections -> Sections -> Bool) -> Eq Sections
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Sections -> Sections -> Bool
== :: Sections -> Sections -> Bool
$c/= :: Sections -> Sections -> Bool
/= :: Sections -> Sections -> Bool
Eq, (forall x. Sections -> Rep Sections x)
-> (forall x. Rep Sections x -> Sections) -> Generic Sections
forall x. Rep Sections x -> Sections
forall x. Sections -> Rep Sections x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Sections -> Rep Sections x
from :: forall x. Sections -> Rep Sections x
$cto :: forall x. Rep Sections x -> Sections
to :: forall x. Rep Sections x -> Sections
Generic)

data Section = Section
    { Section -> String
sectionName     :: Txt
    , Section -> [Test]
sectionTests    :: [Test]
    , Section -> Language
sectionLanguage :: Language
    , Section -> Format
sectionFormat   :: Format
    }
    deriving (Section -> Section -> Bool
(Section -> Section -> Bool)
-> (Section -> Section -> Bool) -> Eq Section
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Section -> Section -> Bool
== :: Section -> Section -> Bool
$c/= :: Section -> Section -> Bool
/= :: Section -> Section -> Bool
Eq, Int -> Section -> ShowS
[Section] -> ShowS
Section -> String
(Int -> Section -> ShowS)
-> (Section -> String) -> ([Section] -> ShowS) -> Show Section
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Section -> ShowS
showsPrec :: Int -> Section -> ShowS
$cshow :: Section -> String
show :: Section -> String
$cshowList :: [Section] -> ShowS
showList :: [Section] -> ShowS
Show, (forall x. Section -> Rep Section x)
-> (forall x. Rep Section x -> Section) -> Generic Section
forall x. Rep Section x -> Section
forall x. Section -> Rep Section x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Section -> Rep Section x
from :: forall x. Section -> Rep Section x
$cto :: forall x. Rep Section x -> Section
to :: forall x. Rep Section x -> Section
Generic, Maybe Section
Value -> Parser [Section]
Value -> Parser Section
(Value -> Parser Section)
-> (Value -> Parser [Section]) -> Maybe Section -> FromJSON Section
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Section
parseJSON :: Value -> Parser Section
$cparseJSONList :: Value -> Parser [Section]
parseJSONList :: Value -> Parser [Section]
$comittedField :: Maybe Section
omittedField :: Maybe Section
FromJSON, [Section] -> Value
[Section] -> Encoding
Section -> Bool
Section -> Value
Section -> Encoding
(Section -> Value)
-> (Section -> Encoding)
-> ([Section] -> Value)
-> ([Section] -> Encoding)
-> (Section -> Bool)
-> ToJSON Section
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Section -> Value
toJSON :: Section -> Value
$ctoEncoding :: Section -> Encoding
toEncoding :: Section -> Encoding
$ctoJSONList :: [Section] -> Value
toJSONList :: [Section] -> Value
$ctoEncodingList :: [Section] -> Encoding
toEncodingList :: [Section] -> Encoding
$comitField :: Section -> Bool
omitField :: Section -> Bool
ToJSON, Section -> ()
(Section -> ()) -> NFData Section
forall a. (a -> ()) -> NFData a
$crnf :: Section -> ()
rnf :: Section -> ()
NFData)

hasTests :: Section -> Bool
hasTests :: Section -> Bool
hasTests = Bool -> Bool
not (Bool -> Bool) -> (Section -> Bool) -> Section -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Test] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Test] -> Bool) -> (Section -> [Test]) -> Section -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Section -> [Test]
sectionTests

hasPropertyTest :: Section -> Bool
hasPropertyTest :: Section -> Bool
hasPropertyTest = (Test -> Bool) -> [Test] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Test -> Bool
isProperty ([Test] -> Bool) -> (Section -> [Test]) -> Section -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Section -> [Test]
sectionTests

-- |Split setup and normal sections
splitSections :: [Section] -> ([Section], [Section])
splitSections :: [Section] -> ([Section], [Section])
splitSections = (Section -> Bool) -> [Section] -> ([Section], [Section])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition ((String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"setup") (String -> Bool) -> (Section -> String) -> Section -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Section -> String
sectionName)

data Test
    = Example {Test -> NonEmpty String
testLines :: NonEmpty Txt, Test -> [String]
testOutput :: [Txt], Test -> Range
testRange :: Range}
    | Property {Test -> String
testline :: Txt, testOutput :: [Txt], testRange :: Range}
    deriving (Test -> Test -> Bool
(Test -> Test -> Bool) -> (Test -> Test -> Bool) -> Eq Test
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Test -> Test -> Bool
== :: Test -> Test -> Bool
$c/= :: Test -> Test -> Bool
/= :: Test -> Test -> Bool
Eq, Int -> Test -> ShowS
[Test] -> ShowS
Test -> String
(Int -> Test -> ShowS)
-> (Test -> String) -> ([Test] -> ShowS) -> Show Test
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Test -> ShowS
showsPrec :: Int -> Test -> ShowS
$cshow :: Test -> String
show :: Test -> String
$cshowList :: [Test] -> ShowS
showList :: [Test] -> ShowS
Show, (forall x. Test -> Rep Test x)
-> (forall x. Rep Test x -> Test) -> Generic Test
forall x. Rep Test x -> Test
forall x. Test -> Rep Test x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Test -> Rep Test x
from :: forall x. Test -> Rep Test x
$cto :: forall x. Rep Test x -> Test
to :: forall x. Rep Test x -> Test
Generic, Maybe Test
Value -> Parser [Test]
Value -> Parser Test
(Value -> Parser Test)
-> (Value -> Parser [Test]) -> Maybe Test -> FromJSON Test
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Test
parseJSON :: Value -> Parser Test
$cparseJSONList :: Value -> Parser [Test]
parseJSONList :: Value -> Parser [Test]
$comittedField :: Maybe Test
omittedField :: Maybe Test
FromJSON, [Test] -> Value
[Test] -> Encoding
Test -> Bool
Test -> Value
Test -> Encoding
(Test -> Value)
-> (Test -> Encoding)
-> ([Test] -> Value)
-> ([Test] -> Encoding)
-> (Test -> Bool)
-> ToJSON Test
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Test -> Value
toJSON :: Test -> Value
$ctoEncoding :: Test -> Encoding
toEncoding :: Test -> Encoding
$ctoJSONList :: [Test] -> Value
toJSONList :: [Test] -> Value
$ctoEncodingList :: [Test] -> Encoding
toEncodingList :: [Test] -> Encoding
$comitField :: Test -> Bool
omitField :: Test -> Bool
ToJSON, Test -> ()
(Test -> ()) -> NFData Test
forall a. (a -> ()) -> NFData a
$crnf :: Test -> ()
rnf :: Test -> ()
NFData)

data IsEvaluating = IsEvaluating
    deriving (IsEvaluating -> IsEvaluating -> Bool
(IsEvaluating -> IsEvaluating -> Bool)
-> (IsEvaluating -> IsEvaluating -> Bool) -> Eq IsEvaluating
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IsEvaluating -> IsEvaluating -> Bool
== :: IsEvaluating -> IsEvaluating -> Bool
$c/= :: IsEvaluating -> IsEvaluating -> Bool
/= :: IsEvaluating -> IsEvaluating -> Bool
Eq, Int -> IsEvaluating -> ShowS
[IsEvaluating] -> ShowS
IsEvaluating -> String
(Int -> IsEvaluating -> ShowS)
-> (IsEvaluating -> String)
-> ([IsEvaluating] -> ShowS)
-> Show IsEvaluating
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IsEvaluating -> ShowS
showsPrec :: Int -> IsEvaluating -> ShowS
$cshow :: IsEvaluating -> String
show :: IsEvaluating -> String
$cshowList :: [IsEvaluating] -> ShowS
showList :: [IsEvaluating] -> ShowS
Show, Typeable, (forall x. IsEvaluating -> Rep IsEvaluating x)
-> (forall x. Rep IsEvaluating x -> IsEvaluating)
-> Generic IsEvaluating
forall x. Rep IsEvaluating x -> IsEvaluating
forall x. IsEvaluating -> Rep IsEvaluating x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. IsEvaluating -> Rep IsEvaluating x
from :: forall x. IsEvaluating -> Rep IsEvaluating x
$cto :: forall x. Rep IsEvaluating x -> IsEvaluating
to :: forall x. Rep IsEvaluating x -> IsEvaluating
Generic)
instance Hashable IsEvaluating
instance NFData   IsEvaluating

type instance RuleResult IsEvaluating = Bool

data GetEvalComments = GetEvalComments
    deriving (GetEvalComments -> GetEvalComments -> Bool
(GetEvalComments -> GetEvalComments -> Bool)
-> (GetEvalComments -> GetEvalComments -> Bool)
-> Eq GetEvalComments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetEvalComments -> GetEvalComments -> Bool
== :: GetEvalComments -> GetEvalComments -> Bool
$c/= :: GetEvalComments -> GetEvalComments -> Bool
/= :: GetEvalComments -> GetEvalComments -> Bool
Eq, Int -> GetEvalComments -> ShowS
[GetEvalComments] -> ShowS
GetEvalComments -> String
(Int -> GetEvalComments -> ShowS)
-> (GetEvalComments -> String)
-> ([GetEvalComments] -> ShowS)
-> Show GetEvalComments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetEvalComments -> ShowS
showsPrec :: Int -> GetEvalComments -> ShowS
$cshow :: GetEvalComments -> String
show :: GetEvalComments -> String
$cshowList :: [GetEvalComments] -> ShowS
showList :: [GetEvalComments] -> ShowS
Show, Typeable, (forall x. GetEvalComments -> Rep GetEvalComments x)
-> (forall x. Rep GetEvalComments x -> GetEvalComments)
-> Generic GetEvalComments
forall x. Rep GetEvalComments x -> GetEvalComments
forall x. GetEvalComments -> Rep GetEvalComments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GetEvalComments -> Rep GetEvalComments x
from :: forall x. GetEvalComments -> Rep GetEvalComments x
$cto :: forall x. Rep GetEvalComments x -> GetEvalComments
to :: forall x. Rep GetEvalComments x -> GetEvalComments
Generic)
instance Hashable GetEvalComments
instance NFData   GetEvalComments

type instance RuleResult GetEvalComments = Comments
data Comments = Comments
    { Comments -> Map Range RawLineComment
lineComments  :: Map Range RawLineComment
    , Comments -> Map Range RawBlockComment
blockComments :: Map Range RawBlockComment
    }
    deriving (Int -> Comments -> ShowS
[Comments] -> ShowS
Comments -> String
(Int -> Comments -> ShowS)
-> (Comments -> String) -> ([Comments] -> ShowS) -> Show Comments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Comments -> ShowS
showsPrec :: Int -> Comments -> ShowS
$cshow :: Comments -> String
show :: Comments -> String
$cshowList :: [Comments] -> ShowS
showList :: [Comments] -> ShowS
Show, Comments -> Comments -> Bool
(Comments -> Comments -> Bool)
-> (Comments -> Comments -> Bool) -> Eq Comments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Comments -> Comments -> Bool
== :: Comments -> Comments -> Bool
$c/= :: Comments -> Comments -> Bool
/= :: Comments -> Comments -> Bool
Eq, Eq Comments
Eq Comments =>
(Comments -> Comments -> Ordering)
-> (Comments -> Comments -> Bool)
-> (Comments -> Comments -> Bool)
-> (Comments -> Comments -> Bool)
-> (Comments -> Comments -> Bool)
-> (Comments -> Comments -> Comments)
-> (Comments -> Comments -> Comments)
-> Ord Comments
Comments -> Comments -> Bool
Comments -> Comments -> Ordering
Comments -> Comments -> Comments
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Comments -> Comments -> Ordering
compare :: Comments -> Comments -> Ordering
$c< :: Comments -> Comments -> Bool
< :: Comments -> Comments -> Bool
$c<= :: Comments -> Comments -> Bool
<= :: Comments -> Comments -> Bool
$c> :: Comments -> Comments -> Bool
> :: Comments -> Comments -> Bool
$c>= :: Comments -> Comments -> Bool
>= :: Comments -> Comments -> Bool
$cmax :: Comments -> Comments -> Comments
max :: Comments -> Comments -> Comments
$cmin :: Comments -> Comments -> Comments
min :: Comments -> Comments -> Comments
Ord, (forall x. Comments -> Rep Comments x)
-> (forall x. Rep Comments x -> Comments) -> Generic Comments
forall x. Rep Comments x -> Comments
forall x. Comments -> Rep Comments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Comments -> Rep Comments x
from :: forall x. Comments -> Rep Comments x
$cto :: forall x. Rep Comments x -> Comments
to :: forall x. Rep Comments x -> Comments
Generic)

nullComments :: Comments -> Bool
nullComments :: Comments -> Bool
nullComments Comments{Map Range RawLineComment
Map Range RawBlockComment
lineComments :: Comments -> Map Range RawLineComment
blockComments :: Comments -> Map Range RawBlockComment
lineComments :: Map Range RawLineComment
blockComments :: Map Range RawBlockComment
..} = Map Range RawLineComment -> Bool
forall a. Map Range a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Map Range RawLineComment
lineComments Bool -> Bool -> Bool
&& Map Range RawBlockComment -> Bool
forall a. Map Range a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Map Range RawBlockComment
blockComments

instance NFData Comments

newtype RawBlockComment = RawBlockComment {RawBlockComment -> String
getRawBlockComment :: String}
    deriving (Int -> RawBlockComment -> ShowS
[RawBlockComment] -> ShowS
RawBlockComment -> String
(Int -> RawBlockComment -> ShowS)
-> (RawBlockComment -> String)
-> ([RawBlockComment] -> ShowS)
-> Show RawBlockComment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RawBlockComment -> ShowS
showsPrec :: Int -> RawBlockComment -> ShowS
$cshow :: RawBlockComment -> String
show :: RawBlockComment -> String
$cshowList :: [RawBlockComment] -> ShowS
showList :: [RawBlockComment] -> ShowS
Show, RawBlockComment -> RawBlockComment -> Bool
(RawBlockComment -> RawBlockComment -> Bool)
-> (RawBlockComment -> RawBlockComment -> Bool)
-> Eq RawBlockComment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RawBlockComment -> RawBlockComment -> Bool
== :: RawBlockComment -> RawBlockComment -> Bool
$c/= :: RawBlockComment -> RawBlockComment -> Bool
/= :: RawBlockComment -> RawBlockComment -> Bool
Eq, Eq RawBlockComment
Eq RawBlockComment =>
(RawBlockComment -> RawBlockComment -> Ordering)
-> (RawBlockComment -> RawBlockComment -> Bool)
-> (RawBlockComment -> RawBlockComment -> Bool)
-> (RawBlockComment -> RawBlockComment -> Bool)
-> (RawBlockComment -> RawBlockComment -> Bool)
-> (RawBlockComment -> RawBlockComment -> RawBlockComment)
-> (RawBlockComment -> RawBlockComment -> RawBlockComment)
-> Ord RawBlockComment
RawBlockComment -> RawBlockComment -> Bool
RawBlockComment -> RawBlockComment -> Ordering
RawBlockComment -> RawBlockComment -> RawBlockComment
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RawBlockComment -> RawBlockComment -> Ordering
compare :: RawBlockComment -> RawBlockComment -> Ordering
$c< :: RawBlockComment -> RawBlockComment -> Bool
< :: RawBlockComment -> RawBlockComment -> Bool
$c<= :: RawBlockComment -> RawBlockComment -> Bool
<= :: RawBlockComment -> RawBlockComment -> Bool
$c> :: RawBlockComment -> RawBlockComment -> Bool
> :: RawBlockComment -> RawBlockComment -> Bool
$c>= :: RawBlockComment -> RawBlockComment -> Bool
>= :: RawBlockComment -> RawBlockComment -> Bool
$cmax :: RawBlockComment -> RawBlockComment -> RawBlockComment
max :: RawBlockComment -> RawBlockComment -> RawBlockComment
$cmin :: RawBlockComment -> RawBlockComment -> RawBlockComment
min :: RawBlockComment -> RawBlockComment -> RawBlockComment
Ord)
    deriving newtype
        ( String -> RawBlockComment
(String -> RawBlockComment) -> IsString RawBlockComment
forall a. (String -> a) -> IsString a
$cfromString :: String -> RawBlockComment
fromString :: String -> RawBlockComment
IsString
        , Ord (Token RawBlockComment)
Ord (Tokens RawBlockComment)
(Ord (Token RawBlockComment), Ord (Tokens RawBlockComment)) =>
(Proxy RawBlockComment
 -> Token RawBlockComment -> Tokens RawBlockComment)
-> (Proxy RawBlockComment
    -> [Token RawBlockComment] -> Tokens RawBlockComment)
-> (Proxy RawBlockComment
    -> Tokens RawBlockComment -> [Token RawBlockComment])
-> (Proxy RawBlockComment -> Tokens RawBlockComment -> Int)
-> (Proxy RawBlockComment -> Tokens RawBlockComment -> Bool)
-> (RawBlockComment
    -> Maybe (Token RawBlockComment, RawBlockComment))
-> (Int
    -> RawBlockComment
    -> Maybe (Tokens RawBlockComment, RawBlockComment))
-> ((Token RawBlockComment -> Bool)
    -> RawBlockComment -> (Tokens RawBlockComment, RawBlockComment))
-> Stream RawBlockComment
Int
-> RawBlockComment
-> Maybe (Tokens RawBlockComment, RawBlockComment)
Proxy RawBlockComment
-> [Token RawBlockComment] -> Tokens RawBlockComment
Proxy RawBlockComment
-> Token RawBlockComment -> Tokens RawBlockComment
Proxy RawBlockComment -> Tokens RawBlockComment -> Bool
Proxy RawBlockComment -> Tokens RawBlockComment -> Int
Proxy RawBlockComment
-> Tokens RawBlockComment -> [Token RawBlockComment]
RawBlockComment -> Maybe (Token RawBlockComment, RawBlockComment)
(Token RawBlockComment -> Bool)
-> RawBlockComment -> (Tokens RawBlockComment, RawBlockComment)
forall s.
(Ord (Token s), Ord (Tokens s)) =>
(Proxy s -> Token s -> Tokens s)
-> (Proxy s -> [Token s] -> Tokens s)
-> (Proxy s -> Tokens s -> [Token s])
-> (Proxy s -> Tokens s -> Int)
-> (Proxy s -> Tokens s -> Bool)
-> (s -> Maybe (Token s, s))
-> (Int -> s -> Maybe (Tokens s, s))
-> ((Token s -> Bool) -> s -> (Tokens s, s))
-> Stream s
$ctokenToChunk :: Proxy RawBlockComment
-> Token RawBlockComment -> Tokens RawBlockComment
tokenToChunk :: Proxy RawBlockComment
-> Token RawBlockComment -> Tokens RawBlockComment
$ctokensToChunk :: Proxy RawBlockComment
-> [Token RawBlockComment] -> Tokens RawBlockComment
tokensToChunk :: Proxy RawBlockComment
-> [Token RawBlockComment] -> Tokens RawBlockComment
$cchunkToTokens :: Proxy RawBlockComment
-> Tokens RawBlockComment -> [Token RawBlockComment]
chunkToTokens :: Proxy RawBlockComment
-> Tokens RawBlockComment -> [Token RawBlockComment]
$cchunkLength :: Proxy RawBlockComment -> Tokens RawBlockComment -> Int
chunkLength :: Proxy RawBlockComment -> Tokens RawBlockComment -> Int
$cchunkEmpty :: Proxy RawBlockComment -> Tokens RawBlockComment -> Bool
chunkEmpty :: Proxy RawBlockComment -> Tokens RawBlockComment -> Bool
$ctake1_ :: RawBlockComment -> Maybe (Token RawBlockComment, RawBlockComment)
take1_ :: RawBlockComment -> Maybe (Token RawBlockComment, RawBlockComment)
$ctakeN_ :: Int
-> RawBlockComment
-> Maybe (Tokens RawBlockComment, RawBlockComment)
takeN_ :: Int
-> RawBlockComment
-> Maybe (Tokens RawBlockComment, RawBlockComment)
$ctakeWhile_ :: (Token RawBlockComment -> Bool)
-> RawBlockComment -> (Tokens RawBlockComment, RawBlockComment)
takeWhile_ :: (Token RawBlockComment -> Bool)
-> RawBlockComment -> (Tokens RawBlockComment, RawBlockComment)
P.Stream
        , Stream RawBlockComment
Int
-> PosState RawBlockComment
-> (Maybe String, PosState RawBlockComment)
Int -> PosState RawBlockComment -> PosState RawBlockComment
Stream RawBlockComment =>
(Int
 -> PosState RawBlockComment
 -> (Maybe String, PosState RawBlockComment))
-> (Int -> PosState RawBlockComment -> PosState RawBlockComment)
-> TraversableStream RawBlockComment
forall s.
Stream s =>
(Int -> PosState s -> (Maybe String, PosState s))
-> (Int -> PosState s -> PosState s) -> TraversableStream s
$creachOffset :: Int
-> PosState RawBlockComment
-> (Maybe String, PosState RawBlockComment)
reachOffset :: Int
-> PosState RawBlockComment
-> (Maybe String, PosState RawBlockComment)
$creachOffsetNoLine :: Int -> PosState RawBlockComment -> PosState RawBlockComment
reachOffsetNoLine :: Int -> PosState RawBlockComment -> PosState RawBlockComment
P.TraversableStream
        , Stream RawBlockComment
Proxy RawBlockComment -> NonEmpty (Token RawBlockComment) -> Int
Proxy RawBlockComment -> NonEmpty (Token RawBlockComment) -> String
Stream RawBlockComment =>
(Proxy RawBlockComment
 -> NonEmpty (Token RawBlockComment) -> String)
-> (Proxy RawBlockComment
    -> NonEmpty (Token RawBlockComment) -> Int)
-> VisualStream RawBlockComment
forall s.
Stream s =>
(Proxy s -> NonEmpty (Token s) -> String)
-> (Proxy s -> NonEmpty (Token s) -> Int) -> VisualStream s
$cshowTokens :: Proxy RawBlockComment -> NonEmpty (Token RawBlockComment) -> String
showTokens :: Proxy RawBlockComment -> NonEmpty (Token RawBlockComment) -> String
$ctokensLength :: Proxy RawBlockComment -> NonEmpty (Token RawBlockComment) -> Int
tokensLength :: Proxy RawBlockComment -> NonEmpty (Token RawBlockComment) -> Int
P.VisualStream
        , NonEmpty RawBlockComment -> RawBlockComment
RawBlockComment -> RawBlockComment -> RawBlockComment
(RawBlockComment -> RawBlockComment -> RawBlockComment)
-> (NonEmpty RawBlockComment -> RawBlockComment)
-> (forall b.
    Integral b =>
    b -> RawBlockComment -> RawBlockComment)
-> Semigroup RawBlockComment
forall b. Integral b => b -> RawBlockComment -> RawBlockComment
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: RawBlockComment -> RawBlockComment -> RawBlockComment
<> :: RawBlockComment -> RawBlockComment -> RawBlockComment
$csconcat :: NonEmpty RawBlockComment -> RawBlockComment
sconcat :: NonEmpty RawBlockComment -> RawBlockComment
$cstimes :: forall b. Integral b => b -> RawBlockComment -> RawBlockComment
stimes :: forall b. Integral b => b -> RawBlockComment -> RawBlockComment
Semigroup
        , Semigroup RawBlockComment
RawBlockComment
Semigroup RawBlockComment =>
RawBlockComment
-> (RawBlockComment -> RawBlockComment -> RawBlockComment)
-> ([RawBlockComment] -> RawBlockComment)
-> Monoid RawBlockComment
[RawBlockComment] -> RawBlockComment
RawBlockComment -> RawBlockComment -> RawBlockComment
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: RawBlockComment
mempty :: RawBlockComment
$cmappend :: RawBlockComment -> RawBlockComment -> RawBlockComment
mappend :: RawBlockComment -> RawBlockComment -> RawBlockComment
$cmconcat :: [RawBlockComment] -> RawBlockComment
mconcat :: [RawBlockComment] -> RawBlockComment
Monoid
        , RawBlockComment -> ()
(RawBlockComment -> ()) -> NFData RawBlockComment
forall a. (a -> ()) -> NFData a
$crnf :: RawBlockComment -> ()
rnf :: RawBlockComment -> ()
NFData
        )

newtype RawLineComment = RawLineComment {RawLineComment -> String
getRawLineComment :: String}
    deriving (Int -> RawLineComment -> ShowS
[RawLineComment] -> ShowS
RawLineComment -> String
(Int -> RawLineComment -> ShowS)
-> (RawLineComment -> String)
-> ([RawLineComment] -> ShowS)
-> Show RawLineComment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RawLineComment -> ShowS
showsPrec :: Int -> RawLineComment -> ShowS
$cshow :: RawLineComment -> String
show :: RawLineComment -> String
$cshowList :: [RawLineComment] -> ShowS
showList :: [RawLineComment] -> ShowS
Show, RawLineComment -> RawLineComment -> Bool
(RawLineComment -> RawLineComment -> Bool)
-> (RawLineComment -> RawLineComment -> Bool) -> Eq RawLineComment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RawLineComment -> RawLineComment -> Bool
== :: RawLineComment -> RawLineComment -> Bool
$c/= :: RawLineComment -> RawLineComment -> Bool
/= :: RawLineComment -> RawLineComment -> Bool
Eq, Eq RawLineComment
Eq RawLineComment =>
(RawLineComment -> RawLineComment -> Ordering)
-> (RawLineComment -> RawLineComment -> Bool)
-> (RawLineComment -> RawLineComment -> Bool)
-> (RawLineComment -> RawLineComment -> Bool)
-> (RawLineComment -> RawLineComment -> Bool)
-> (RawLineComment -> RawLineComment -> RawLineComment)
-> (RawLineComment -> RawLineComment -> RawLineComment)
-> Ord RawLineComment
RawLineComment -> RawLineComment -> Bool
RawLineComment -> RawLineComment -> Ordering
RawLineComment -> RawLineComment -> RawLineComment
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RawLineComment -> RawLineComment -> Ordering
compare :: RawLineComment -> RawLineComment -> Ordering
$c< :: RawLineComment -> RawLineComment -> Bool
< :: RawLineComment -> RawLineComment -> Bool
$c<= :: RawLineComment -> RawLineComment -> Bool
<= :: RawLineComment -> RawLineComment -> Bool
$c> :: RawLineComment -> RawLineComment -> Bool
> :: RawLineComment -> RawLineComment -> Bool
$c>= :: RawLineComment -> RawLineComment -> Bool
>= :: RawLineComment -> RawLineComment -> Bool
$cmax :: RawLineComment -> RawLineComment -> RawLineComment
max :: RawLineComment -> RawLineComment -> RawLineComment
$cmin :: RawLineComment -> RawLineComment -> RawLineComment
min :: RawLineComment -> RawLineComment -> RawLineComment
Ord)
    deriving newtype
        ( String -> RawLineComment
(String -> RawLineComment) -> IsString RawLineComment
forall a. (String -> a) -> IsString a
$cfromString :: String -> RawLineComment
fromString :: String -> RawLineComment
IsString
        , Ord (Token RawLineComment)
Ord (Tokens RawLineComment)
(Ord (Token RawLineComment), Ord (Tokens RawLineComment)) =>
(Proxy RawLineComment
 -> Token RawLineComment -> Tokens RawLineComment)
-> (Proxy RawLineComment
    -> [Token RawLineComment] -> Tokens RawLineComment)
-> (Proxy RawLineComment
    -> Tokens RawLineComment -> [Token RawLineComment])
-> (Proxy RawLineComment -> Tokens RawLineComment -> Int)
-> (Proxy RawLineComment -> Tokens RawLineComment -> Bool)
-> (RawLineComment -> Maybe (Token RawLineComment, RawLineComment))
-> (Int
    -> RawLineComment -> Maybe (Tokens RawLineComment, RawLineComment))
-> ((Token RawLineComment -> Bool)
    -> RawLineComment -> (Tokens RawLineComment, RawLineComment))
-> Stream RawLineComment
Int
-> RawLineComment -> Maybe (Tokens RawLineComment, RawLineComment)
Proxy RawLineComment
-> [Token RawLineComment] -> Tokens RawLineComment
Proxy RawLineComment
-> Token RawLineComment -> Tokens RawLineComment
Proxy RawLineComment -> Tokens RawLineComment -> Bool
Proxy RawLineComment -> Tokens RawLineComment -> Int
Proxy RawLineComment
-> Tokens RawLineComment -> [Token RawLineComment]
RawLineComment -> Maybe (Token RawLineComment, RawLineComment)
(Token RawLineComment -> Bool)
-> RawLineComment -> (Tokens RawLineComment, RawLineComment)
forall s.
(Ord (Token s), Ord (Tokens s)) =>
(Proxy s -> Token s -> Tokens s)
-> (Proxy s -> [Token s] -> Tokens s)
-> (Proxy s -> Tokens s -> [Token s])
-> (Proxy s -> Tokens s -> Int)
-> (Proxy s -> Tokens s -> Bool)
-> (s -> Maybe (Token s, s))
-> (Int -> s -> Maybe (Tokens s, s))
-> ((Token s -> Bool) -> s -> (Tokens s, s))
-> Stream s
$ctokenToChunk :: Proxy RawLineComment
-> Token RawLineComment -> Tokens RawLineComment
tokenToChunk :: Proxy RawLineComment
-> Token RawLineComment -> Tokens RawLineComment
$ctokensToChunk :: Proxy RawLineComment
-> [Token RawLineComment] -> Tokens RawLineComment
tokensToChunk :: Proxy RawLineComment
-> [Token RawLineComment] -> Tokens RawLineComment
$cchunkToTokens :: Proxy RawLineComment
-> Tokens RawLineComment -> [Token RawLineComment]
chunkToTokens :: Proxy RawLineComment
-> Tokens RawLineComment -> [Token RawLineComment]
$cchunkLength :: Proxy RawLineComment -> Tokens RawLineComment -> Int
chunkLength :: Proxy RawLineComment -> Tokens RawLineComment -> Int
$cchunkEmpty :: Proxy RawLineComment -> Tokens RawLineComment -> Bool
chunkEmpty :: Proxy RawLineComment -> Tokens RawLineComment -> Bool
$ctake1_ :: RawLineComment -> Maybe (Token RawLineComment, RawLineComment)
take1_ :: RawLineComment -> Maybe (Token RawLineComment, RawLineComment)
$ctakeN_ :: Int
-> RawLineComment -> Maybe (Tokens RawLineComment, RawLineComment)
takeN_ :: Int
-> RawLineComment -> Maybe (Tokens RawLineComment, RawLineComment)
$ctakeWhile_ :: (Token RawLineComment -> Bool)
-> RawLineComment -> (Tokens RawLineComment, RawLineComment)
takeWhile_ :: (Token RawLineComment -> Bool)
-> RawLineComment -> (Tokens RawLineComment, RawLineComment)
P.Stream
        , Stream RawLineComment
Int
-> PosState RawLineComment
-> (Maybe String, PosState RawLineComment)
Int -> PosState RawLineComment -> PosState RawLineComment
Stream RawLineComment =>
(Int
 -> PosState RawLineComment
 -> (Maybe String, PosState RawLineComment))
-> (Int -> PosState RawLineComment -> PosState RawLineComment)
-> TraversableStream RawLineComment
forall s.
Stream s =>
(Int -> PosState s -> (Maybe String, PosState s))
-> (Int -> PosState s -> PosState s) -> TraversableStream s
$creachOffset :: Int
-> PosState RawLineComment
-> (Maybe String, PosState RawLineComment)
reachOffset :: Int
-> PosState RawLineComment
-> (Maybe String, PosState RawLineComment)
$creachOffsetNoLine :: Int -> PosState RawLineComment -> PosState RawLineComment
reachOffsetNoLine :: Int -> PosState RawLineComment -> PosState RawLineComment
P.TraversableStream
        , Stream RawLineComment
Proxy RawLineComment -> NonEmpty (Token RawLineComment) -> Int
Proxy RawLineComment -> NonEmpty (Token RawLineComment) -> String
Stream RawLineComment =>
(Proxy RawLineComment -> NonEmpty (Token RawLineComment) -> String)
-> (Proxy RawLineComment -> NonEmpty (Token RawLineComment) -> Int)
-> VisualStream RawLineComment
forall s.
Stream s =>
(Proxy s -> NonEmpty (Token s) -> String)
-> (Proxy s -> NonEmpty (Token s) -> Int) -> VisualStream s
$cshowTokens :: Proxy RawLineComment -> NonEmpty (Token RawLineComment) -> String
showTokens :: Proxy RawLineComment -> NonEmpty (Token RawLineComment) -> String
$ctokensLength :: Proxy RawLineComment -> NonEmpty (Token RawLineComment) -> Int
tokensLength :: Proxy RawLineComment -> NonEmpty (Token RawLineComment) -> Int
P.VisualStream
        , NonEmpty RawLineComment -> RawLineComment
RawLineComment -> RawLineComment -> RawLineComment
(RawLineComment -> RawLineComment -> RawLineComment)
-> (NonEmpty RawLineComment -> RawLineComment)
-> (forall b. Integral b => b -> RawLineComment -> RawLineComment)
-> Semigroup RawLineComment
forall b. Integral b => b -> RawLineComment -> RawLineComment
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: RawLineComment -> RawLineComment -> RawLineComment
<> :: RawLineComment -> RawLineComment -> RawLineComment
$csconcat :: NonEmpty RawLineComment -> RawLineComment
sconcat :: NonEmpty RawLineComment -> RawLineComment
$cstimes :: forall b. Integral b => b -> RawLineComment -> RawLineComment
stimes :: forall b. Integral b => b -> RawLineComment -> RawLineComment
Semigroup
        , Semigroup RawLineComment
RawLineComment
Semigroup RawLineComment =>
RawLineComment
-> (RawLineComment -> RawLineComment -> RawLineComment)
-> ([RawLineComment] -> RawLineComment)
-> Monoid RawLineComment
[RawLineComment] -> RawLineComment
RawLineComment -> RawLineComment -> RawLineComment
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: RawLineComment
mempty :: RawLineComment
$cmappend :: RawLineComment -> RawLineComment -> RawLineComment
mappend :: RawLineComment -> RawLineComment -> RawLineComment
$cmconcat :: [RawLineComment] -> RawLineComment
mconcat :: [RawLineComment] -> RawLineComment
Monoid
        , RawLineComment -> ()
(RawLineComment -> ()) -> NFData RawLineComment
forall a. (a -> ()) -> NFData a
$crnf :: RawLineComment -> ()
rnf :: RawLineComment -> ()
NFData
        )

instance Semigroup Comments where
    Comments Map Range RawLineComment
ls Map Range RawBlockComment
bs <> :: Comments -> Comments -> Comments
<> Comments Map Range RawLineComment
ls' Map Range RawBlockComment
bs' = Map Range RawLineComment -> Map Range RawBlockComment -> Comments
Comments (Map Range RawLineComment
ls Map Range RawLineComment
-> Map Range RawLineComment -> Map Range RawLineComment
forall a. Semigroup a => a -> a -> a
<> Map Range RawLineComment
ls') (Map Range RawBlockComment
bs Map Range RawBlockComment
-> Map Range RawBlockComment -> Map Range RawBlockComment
forall a. Semigroup a => a -> a -> a
<> Map Range RawBlockComment
bs')

instance Monoid Comments where
    mempty :: Comments
mempty = Map Range RawLineComment -> Map Range RawBlockComment -> Comments
Comments Map Range RawLineComment
forall a. Monoid a => a
mempty Map Range RawBlockComment
forall a. Monoid a => a
mempty

isProperty :: Test -> Bool
isProperty :: Test -> Bool
isProperty Property {} = Bool
True
isProperty Test
_           = Bool
False

data Format
    = SingleLine
    | -- | @Range@ is that of surrounding entire block comment, not section.
      -- Used for detecting no-newline test commands.
      MultiLine Range
    deriving (Format -> Format -> Bool
(Format -> Format -> Bool)
-> (Format -> Format -> Bool) -> Eq Format
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Format -> Format -> Bool
== :: Format -> Format -> Bool
$c/= :: Format -> Format -> Bool
/= :: Format -> Format -> Bool
Eq, Int -> Format -> ShowS
[Format] -> ShowS
Format -> String
(Int -> Format -> ShowS)
-> (Format -> String) -> ([Format] -> ShowS) -> Show Format
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Format -> ShowS
showsPrec :: Int -> Format -> ShowS
$cshow :: Format -> String
show :: Format -> String
$cshowList :: [Format] -> ShowS
showList :: [Format] -> ShowS
Show, Eq Format
Eq Format =>
(Format -> Format -> Ordering)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Format)
-> (Format -> Format -> Format)
-> Ord Format
Format -> Format -> Bool
Format -> Format -> Ordering
Format -> Format -> Format
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Format -> Format -> Ordering
compare :: Format -> Format -> Ordering
$c< :: Format -> Format -> Bool
< :: Format -> Format -> Bool
$c<= :: Format -> Format -> Bool
<= :: Format -> Format -> Bool
$c> :: Format -> Format -> Bool
> :: Format -> Format -> Bool
$c>= :: Format -> Format -> Bool
>= :: Format -> Format -> Bool
$cmax :: Format -> Format -> Format
max :: Format -> Format -> Format
$cmin :: Format -> Format -> Format
min :: Format -> Format -> Format
Ord, (forall x. Format -> Rep Format x)
-> (forall x. Rep Format x -> Format) -> Generic Format
forall x. Rep Format x -> Format
forall x. Format -> Rep Format x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Format -> Rep Format x
from :: forall x. Format -> Rep Format x
$cto :: forall x. Rep Format x -> Format
to :: forall x. Rep Format x -> Format
Generic, Maybe Format
Value -> Parser [Format]
Value -> Parser Format
(Value -> Parser Format)
-> (Value -> Parser [Format]) -> Maybe Format -> FromJSON Format
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Format
parseJSON :: Value -> Parser Format
$cparseJSONList :: Value -> Parser [Format]
parseJSONList :: Value -> Parser [Format]
$comittedField :: Maybe Format
omittedField :: Maybe Format
FromJSON, [Format] -> Value
[Format] -> Encoding
Format -> Bool
Format -> Value
Format -> Encoding
(Format -> Value)
-> (Format -> Encoding)
-> ([Format] -> Value)
-> ([Format] -> Encoding)
-> (Format -> Bool)
-> ToJSON Format
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Format -> Value
toJSON :: Format -> Value
$ctoEncoding :: Format -> Encoding
toEncoding :: Format -> Encoding
$ctoJSONList :: [Format] -> Value
toJSONList :: [Format] -> Value
$ctoEncodingList :: [Format] -> Encoding
toEncodingList :: [Format] -> Encoding
$comitField :: Format -> Bool
omitField :: Format -> Bool
ToJSON, Format -> ()
(Format -> ()) -> NFData Format
forall a. (a -> ()) -> NFData a
$crnf :: Format -> ()
rnf :: Format -> ()
NFData)

data Language = Plain | Haddock deriving (Language -> Language -> Bool
(Language -> Language -> Bool)
-> (Language -> Language -> Bool) -> Eq Language
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Language -> Language -> Bool
== :: Language -> Language -> Bool
$c/= :: Language -> Language -> Bool
/= :: Language -> Language -> Bool
Eq, Int -> Language -> ShowS
[Language] -> ShowS
Language -> String
(Int -> Language -> ShowS)
-> (Language -> String) -> ([Language] -> ShowS) -> Show Language
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Language -> ShowS
showsPrec :: Int -> Language -> ShowS
$cshow :: Language -> String
show :: Language -> String
$cshowList :: [Language] -> ShowS
showList :: [Language] -> ShowS
Show, (forall x. Language -> Rep Language x)
-> (forall x. Rep Language x -> Language) -> Generic Language
forall x. Rep Language x -> Language
forall x. Language -> Rep Language x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Language -> Rep Language x
from :: forall x. Language -> Rep Language x
$cto :: forall x. Rep Language x -> Language
to :: forall x. Rep Language x -> Language
Generic, Eq Language
Eq Language =>
(Language -> Language -> Ordering)
-> (Language -> Language -> Bool)
-> (Language -> Language -> Bool)
-> (Language -> Language -> Bool)
-> (Language -> Language -> Bool)
-> (Language -> Language -> Language)
-> (Language -> Language -> Language)
-> Ord Language
Language -> Language -> Bool
Language -> Language -> Ordering
Language -> Language -> Language
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Language -> Language -> Ordering
compare :: Language -> Language -> Ordering
$c< :: Language -> Language -> Bool
< :: Language -> Language -> Bool
$c<= :: Language -> Language -> Bool
<= :: Language -> Language -> Bool
$c> :: Language -> Language -> Bool
> :: Language -> Language -> Bool
$c>= :: Language -> Language -> Bool
>= :: Language -> Language -> Bool
$cmax :: Language -> Language -> Language
max :: Language -> Language -> Language
$cmin :: Language -> Language -> Language
min :: Language -> Language -> Language
Ord, Maybe Language
Value -> Parser [Language]
Value -> Parser Language
(Value -> Parser Language)
-> (Value -> Parser [Language])
-> Maybe Language
-> FromJSON Language
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Language
parseJSON :: Value -> Parser Language
$cparseJSONList :: Value -> Parser [Language]
parseJSONList :: Value -> Parser [Language]
$comittedField :: Maybe Language
omittedField :: Maybe Language
FromJSON, [Language] -> Value
[Language] -> Encoding
Language -> Bool
Language -> Value
Language -> Encoding
(Language -> Value)
-> (Language -> Encoding)
-> ([Language] -> Value)
-> ([Language] -> Encoding)
-> (Language -> Bool)
-> ToJSON Language
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Language -> Value
toJSON :: Language -> Value
$ctoEncoding :: Language -> Encoding
toEncoding :: Language -> Encoding
$ctoJSONList :: [Language] -> Value
toJSONList :: [Language] -> Value
$ctoEncodingList :: [Language] -> Encoding
toEncodingList :: [Language] -> Encoding
$comitField :: Language -> Bool
omitField :: Language -> Bool
ToJSON, Language -> ()
(Language -> ()) -> NFData Language
forall a. (a -> ()) -> NFData a
$crnf :: Language -> ()
rnf :: Language -> ()
NFData)

data ExpectedLine = ExpectedLine [LineChunk] | WildCardLine
    deriving (ExpectedLine -> ExpectedLine -> Bool
(ExpectedLine -> ExpectedLine -> Bool)
-> (ExpectedLine -> ExpectedLine -> Bool) -> Eq ExpectedLine
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExpectedLine -> ExpectedLine -> Bool
== :: ExpectedLine -> ExpectedLine -> Bool
$c/= :: ExpectedLine -> ExpectedLine -> Bool
/= :: ExpectedLine -> ExpectedLine -> Bool
Eq, Int -> ExpectedLine -> ShowS
[ExpectedLine] -> ShowS
ExpectedLine -> String
(Int -> ExpectedLine -> ShowS)
-> (ExpectedLine -> String)
-> ([ExpectedLine] -> ShowS)
-> Show ExpectedLine
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExpectedLine -> ShowS
showsPrec :: Int -> ExpectedLine -> ShowS
$cshow :: ExpectedLine -> String
show :: ExpectedLine -> String
$cshowList :: [ExpectedLine] -> ShowS
showList :: [ExpectedLine] -> ShowS
Show, (forall x. ExpectedLine -> Rep ExpectedLine x)
-> (forall x. Rep ExpectedLine x -> ExpectedLine)
-> Generic ExpectedLine
forall x. Rep ExpectedLine x -> ExpectedLine
forall x. ExpectedLine -> Rep ExpectedLine x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExpectedLine -> Rep ExpectedLine x
from :: forall x. ExpectedLine -> Rep ExpectedLine x
$cto :: forall x. Rep ExpectedLine x -> ExpectedLine
to :: forall x. Rep ExpectedLine x -> ExpectedLine
Generic, Maybe ExpectedLine
Value -> Parser [ExpectedLine]
Value -> Parser ExpectedLine
(Value -> Parser ExpectedLine)
-> (Value -> Parser [ExpectedLine])
-> Maybe ExpectedLine
-> FromJSON ExpectedLine
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ExpectedLine
parseJSON :: Value -> Parser ExpectedLine
$cparseJSONList :: Value -> Parser [ExpectedLine]
parseJSONList :: Value -> Parser [ExpectedLine]
$comittedField :: Maybe ExpectedLine
omittedField :: Maybe ExpectedLine
FromJSON, [ExpectedLine] -> Value
[ExpectedLine] -> Encoding
ExpectedLine -> Bool
ExpectedLine -> Value
ExpectedLine -> Encoding
(ExpectedLine -> Value)
-> (ExpectedLine -> Encoding)
-> ([ExpectedLine] -> Value)
-> ([ExpectedLine] -> Encoding)
-> (ExpectedLine -> Bool)
-> ToJSON ExpectedLine
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ExpectedLine -> Value
toJSON :: ExpectedLine -> Value
$ctoEncoding :: ExpectedLine -> Encoding
toEncoding :: ExpectedLine -> Encoding
$ctoJSONList :: [ExpectedLine] -> Value
toJSONList :: [ExpectedLine] -> Value
$ctoEncodingList :: [ExpectedLine] -> Encoding
toEncodingList :: [ExpectedLine] -> Encoding
$comitField :: ExpectedLine -> Bool
omitField :: ExpectedLine -> Bool
ToJSON, ExpectedLine -> ()
(ExpectedLine -> ()) -> NFData ExpectedLine
forall a. (a -> ()) -> NFData a
$crnf :: ExpectedLine -> ()
rnf :: ExpectedLine -> ()
NFData)

instance IsString ExpectedLine where
    fromString :: String -> ExpectedLine
fromString = [LineChunk] -> ExpectedLine
ExpectedLine ([LineChunk] -> ExpectedLine)
-> (String -> [LineChunk]) -> String -> ExpectedLine
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LineChunk -> [LineChunk]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (LineChunk -> [LineChunk])
-> (String -> LineChunk) -> String -> [LineChunk]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> LineChunk
LineChunk

data LineChunk = LineChunk String | WildCardChunk
    deriving (LineChunk -> LineChunk -> Bool
(LineChunk -> LineChunk -> Bool)
-> (LineChunk -> LineChunk -> Bool) -> Eq LineChunk
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LineChunk -> LineChunk -> Bool
== :: LineChunk -> LineChunk -> Bool
$c/= :: LineChunk -> LineChunk -> Bool
/= :: LineChunk -> LineChunk -> Bool
Eq, Int -> LineChunk -> ShowS
[LineChunk] -> ShowS
LineChunk -> String
(Int -> LineChunk -> ShowS)
-> (LineChunk -> String)
-> ([LineChunk] -> ShowS)
-> Show LineChunk
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LineChunk -> ShowS
showsPrec :: Int -> LineChunk -> ShowS
$cshow :: LineChunk -> String
show :: LineChunk -> String
$cshowList :: [LineChunk] -> ShowS
showList :: [LineChunk] -> ShowS
Show, (forall x. LineChunk -> Rep LineChunk x)
-> (forall x. Rep LineChunk x -> LineChunk) -> Generic LineChunk
forall x. Rep LineChunk x -> LineChunk
forall x. LineChunk -> Rep LineChunk x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LineChunk -> Rep LineChunk x
from :: forall x. LineChunk -> Rep LineChunk x
$cto :: forall x. Rep LineChunk x -> LineChunk
to :: forall x. Rep LineChunk x -> LineChunk
Generic, Maybe LineChunk
Value -> Parser [LineChunk]
Value -> Parser LineChunk
(Value -> Parser LineChunk)
-> (Value -> Parser [LineChunk])
-> Maybe LineChunk
-> FromJSON LineChunk
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser LineChunk
parseJSON :: Value -> Parser LineChunk
$cparseJSONList :: Value -> Parser [LineChunk]
parseJSONList :: Value -> Parser [LineChunk]
$comittedField :: Maybe LineChunk
omittedField :: Maybe LineChunk
FromJSON, [LineChunk] -> Value
[LineChunk] -> Encoding
LineChunk -> Bool
LineChunk -> Value
LineChunk -> Encoding
(LineChunk -> Value)
-> (LineChunk -> Encoding)
-> ([LineChunk] -> Value)
-> ([LineChunk] -> Encoding)
-> (LineChunk -> Bool)
-> ToJSON LineChunk
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: LineChunk -> Value
toJSON :: LineChunk -> Value
$ctoEncoding :: LineChunk -> Encoding
toEncoding :: LineChunk -> Encoding
$ctoJSONList :: [LineChunk] -> Value
toJSONList :: [LineChunk] -> Value
$ctoEncodingList :: [LineChunk] -> Encoding
toEncodingList :: [LineChunk] -> Encoding
$comitField :: LineChunk -> Bool
omitField :: LineChunk -> Bool
ToJSON, LineChunk -> ()
(LineChunk -> ()) -> NFData LineChunk
forall a. (a -> ()) -> NFData a
$crnf :: LineChunk -> ()
rnf :: LineChunk -> ()
NFData)

instance IsString LineChunk where
    fromString :: String -> LineChunk
fromString = String -> LineChunk
LineChunk

type EvalId = Int

-- | Specify the test section to execute
data EvalParams = EvalParams
    { EvalParams -> [Section]
sections :: [Section]
    , EvalParams -> TextDocumentIdentifier
module_  :: !TextDocumentIdentifier
    , EvalParams -> Int
evalId   :: !EvalId -- ^ unique group id; for test uses
    }
    deriving (EvalParams -> EvalParams -> Bool
(EvalParams -> EvalParams -> Bool)
-> (EvalParams -> EvalParams -> Bool) -> Eq EvalParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EvalParams -> EvalParams -> Bool
== :: EvalParams -> EvalParams -> Bool
$c/= :: EvalParams -> EvalParams -> Bool
/= :: EvalParams -> EvalParams -> Bool
Eq, Int -> EvalParams -> ShowS
[EvalParams] -> ShowS
EvalParams -> String
(Int -> EvalParams -> ShowS)
-> (EvalParams -> String)
-> ([EvalParams] -> ShowS)
-> Show EvalParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EvalParams -> ShowS
showsPrec :: Int -> EvalParams -> ShowS
$cshow :: EvalParams -> String
show :: EvalParams -> String
$cshowList :: [EvalParams] -> ShowS
showList :: [EvalParams] -> ShowS
Show, (forall x. EvalParams -> Rep EvalParams x)
-> (forall x. Rep EvalParams x -> EvalParams) -> Generic EvalParams
forall x. Rep EvalParams x -> EvalParams
forall x. EvalParams -> Rep EvalParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EvalParams -> Rep EvalParams x
from :: forall x. EvalParams -> Rep EvalParams x
$cto :: forall x. Rep EvalParams x -> EvalParams
to :: forall x. Rep EvalParams x -> EvalParams
Generic, Maybe EvalParams
Value -> Parser [EvalParams]
Value -> Parser EvalParams
(Value -> Parser EvalParams)
-> (Value -> Parser [EvalParams])
-> Maybe EvalParams
-> FromJSON EvalParams
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser EvalParams
parseJSON :: Value -> Parser EvalParams
$cparseJSONList :: Value -> Parser [EvalParams]
parseJSONList :: Value -> Parser [EvalParams]
$comittedField :: Maybe EvalParams
omittedField :: Maybe EvalParams
FromJSON, [EvalParams] -> Value
[EvalParams] -> Encoding
EvalParams -> Bool
EvalParams -> Value
EvalParams -> Encoding
(EvalParams -> Value)
-> (EvalParams -> Encoding)
-> ([EvalParams] -> Value)
-> ([EvalParams] -> Encoding)
-> (EvalParams -> Bool)
-> ToJSON EvalParams
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: EvalParams -> Value
toJSON :: EvalParams -> Value
$ctoEncoding :: EvalParams -> Encoding
toEncoding :: EvalParams -> Encoding
$ctoJSONList :: [EvalParams] -> Value
toJSONList :: [EvalParams] -> Value
$ctoEncodingList :: [EvalParams] -> Encoding
toEncodingList :: [EvalParams] -> Encoding
$comitField :: EvalParams -> Bool
omitField :: EvalParams -> Bool
ToJSON)