{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
module Ide.Plugin.Cabal.Completion.Types where
import Control.DeepSeq (NFData)
import Data.Hashable
import qualified Data.Text as T
import Data.Typeable
import Development.IDE as D
import GHC.Generics
import qualified Ide.Plugin.Cabal.Parse as Parse
data Log
= LogFileSplitError Position
|
LogUnknownKeyWordInContextError KeyWordName
|
LogUnknownStanzaNameInContextError StanzaName
| LogFilePathCompleterIOError FilePath IOError
| LogUseWithStaleFastNoResult
| LogMapLookUpOfKnownKeyFailed T.Text
deriving (Int -> Log -> ShowS
[Log] -> ShowS
Log -> String
(Int -> Log -> ShowS)
-> (Log -> String) -> ([Log] -> ShowS) -> Show Log
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Log -> ShowS
showsPrec :: Int -> Log -> ShowS
$cshow :: Log -> String
show :: Log -> String
$cshowList :: [Log] -> ShowS
showList :: [Log] -> ShowS
Show)
instance Pretty Log where
pretty :: forall ann. Log -> Doc ann
pretty = \case
LogFileSplitError Position
pos -> Doc ann
"An error occurred when trying to separate the lines of the cabal file at position:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Position -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Position -> Doc ann
pretty Position
pos
LogUnknownKeyWordInContextError Text
kw ->
Doc ann
"Lookup of key word failed for:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow Text
kw
LogUnknownStanzaNameInContextError Text
sn ->
Doc ann
"Lookup of stanza name failed for:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow Text
sn
LogFilePathCompleterIOError String
fp IOError
ioErr ->
Doc ann
"When trying to complete the file path:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty String
fp Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
"the following unexpected IO error occurred" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> IOError -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow IOError
ioErr
Log
LogUseWithStaleFastNoResult -> Doc ann
"Package description couldn't be read"
LogMapLookUpOfKnownKeyFailed Text
key -> Doc ann
"Lookup of key in map failed even though it should exist" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc ann
forall ann. Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Text
key
type instance RuleResult GetCabalDiagnostics = Parse.GenericPackageDescription
data GetCabalDiagnostics = GetCabalDiagnostics
deriving (GetCabalDiagnostics -> GetCabalDiagnostics -> Bool
(GetCabalDiagnostics -> GetCabalDiagnostics -> Bool)
-> (GetCabalDiagnostics -> GetCabalDiagnostics -> Bool)
-> Eq GetCabalDiagnostics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetCabalDiagnostics -> GetCabalDiagnostics -> Bool
== :: GetCabalDiagnostics -> GetCabalDiagnostics -> Bool
$c/= :: GetCabalDiagnostics -> GetCabalDiagnostics -> Bool
/= :: GetCabalDiagnostics -> GetCabalDiagnostics -> Bool
Eq, Int -> GetCabalDiagnostics -> ShowS
[GetCabalDiagnostics] -> ShowS
GetCabalDiagnostics -> String
(Int -> GetCabalDiagnostics -> ShowS)
-> (GetCabalDiagnostics -> String)
-> ([GetCabalDiagnostics] -> ShowS)
-> Show GetCabalDiagnostics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetCabalDiagnostics -> ShowS
showsPrec :: Int -> GetCabalDiagnostics -> ShowS
$cshow :: GetCabalDiagnostics -> String
show :: GetCabalDiagnostics -> String
$cshowList :: [GetCabalDiagnostics] -> ShowS
showList :: [GetCabalDiagnostics] -> ShowS
Show, Typeable, (forall x. GetCabalDiagnostics -> Rep GetCabalDiagnostics x)
-> (forall x. Rep GetCabalDiagnostics x -> GetCabalDiagnostics)
-> Generic GetCabalDiagnostics
forall x. Rep GetCabalDiagnostics x -> GetCabalDiagnostics
forall x. GetCabalDiagnostics -> Rep GetCabalDiagnostics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GetCabalDiagnostics -> Rep GetCabalDiagnostics x
from :: forall x. GetCabalDiagnostics -> Rep GetCabalDiagnostics x
$cto :: forall x. Rep GetCabalDiagnostics x -> GetCabalDiagnostics
to :: forall x. Rep GetCabalDiagnostics x -> GetCabalDiagnostics
Generic)
instance Hashable GetCabalDiagnostics
instance NFData GetCabalDiagnostics
type Context = (StanzaContext, FieldContext)
data StanzaContext
=
TopLevel
|
Stanza StanzaType (Maybe StanzaName)
deriving (StanzaContext -> StanzaContext -> Bool
(StanzaContext -> StanzaContext -> Bool)
-> (StanzaContext -> StanzaContext -> Bool) -> Eq StanzaContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StanzaContext -> StanzaContext -> Bool
== :: StanzaContext -> StanzaContext -> Bool
$c/= :: StanzaContext -> StanzaContext -> Bool
/= :: StanzaContext -> StanzaContext -> Bool
Eq, Int -> StanzaContext -> ShowS
[StanzaContext] -> ShowS
StanzaContext -> String
(Int -> StanzaContext -> ShowS)
-> (StanzaContext -> String)
-> ([StanzaContext] -> ShowS)
-> Show StanzaContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StanzaContext -> ShowS
showsPrec :: Int -> StanzaContext -> ShowS
$cshow :: StanzaContext -> String
show :: StanzaContext -> String
$cshowList :: [StanzaContext] -> ShowS
showList :: [StanzaContext] -> ShowS
Show, ReadPrec [StanzaContext]
ReadPrec StanzaContext
Int -> ReadS StanzaContext
ReadS [StanzaContext]
(Int -> ReadS StanzaContext)
-> ReadS [StanzaContext]
-> ReadPrec StanzaContext
-> ReadPrec [StanzaContext]
-> Read StanzaContext
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StanzaContext
readsPrec :: Int -> ReadS StanzaContext
$creadList :: ReadS [StanzaContext]
readList :: ReadS [StanzaContext]
$creadPrec :: ReadPrec StanzaContext
readPrec :: ReadPrec StanzaContext
$creadListPrec :: ReadPrec [StanzaContext]
readListPrec :: ReadPrec [StanzaContext]
Read)
data FieldContext
=
KeyWord KeyWordName
|
None
deriving (FieldContext -> FieldContext -> Bool
(FieldContext -> FieldContext -> Bool)
-> (FieldContext -> FieldContext -> Bool) -> Eq FieldContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldContext -> FieldContext -> Bool
== :: FieldContext -> FieldContext -> Bool
$c/= :: FieldContext -> FieldContext -> Bool
/= :: FieldContext -> FieldContext -> Bool
Eq, Int -> FieldContext -> ShowS
[FieldContext] -> ShowS
FieldContext -> String
(Int -> FieldContext -> ShowS)
-> (FieldContext -> String)
-> ([FieldContext] -> ShowS)
-> Show FieldContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldContext -> ShowS
showsPrec :: Int -> FieldContext -> ShowS
$cshow :: FieldContext -> String
show :: FieldContext -> String
$cshowList :: [FieldContext] -> ShowS
showList :: [FieldContext] -> ShowS
Show, ReadPrec [FieldContext]
ReadPrec FieldContext
Int -> ReadS FieldContext
ReadS [FieldContext]
(Int -> ReadS FieldContext)
-> ReadS [FieldContext]
-> ReadPrec FieldContext
-> ReadPrec [FieldContext]
-> Read FieldContext
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FieldContext
readsPrec :: Int -> ReadS FieldContext
$creadList :: ReadS [FieldContext]
readList :: ReadS [FieldContext]
$creadPrec :: ReadPrec FieldContext
readPrec :: ReadPrec FieldContext
$creadListPrec :: ReadPrec [FieldContext]
readListPrec :: ReadPrec [FieldContext]
Read)
type KeyWordName = T.Text
type StanzaName = T.Text
type StanzaType = T.Text
data CabalPrefixInfo = CabalPrefixInfo
{
CabalPrefixInfo -> Text
completionPrefix :: T.Text,
CabalPrefixInfo -> Maybe Apostrophe
isStringNotation :: Maybe Apostrophe,
CabalPrefixInfo -> Position
completionCursorPosition :: Position,
CabalPrefixInfo -> Range
completionRange :: Range,
CabalPrefixInfo -> String
completionWorkingDir :: FilePath,
CabalPrefixInfo -> Text
completionFileName :: T.Text
}
deriving (CabalPrefixInfo -> CabalPrefixInfo -> Bool
(CabalPrefixInfo -> CabalPrefixInfo -> Bool)
-> (CabalPrefixInfo -> CabalPrefixInfo -> Bool)
-> Eq CabalPrefixInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CabalPrefixInfo -> CabalPrefixInfo -> Bool
== :: CabalPrefixInfo -> CabalPrefixInfo -> Bool
$c/= :: CabalPrefixInfo -> CabalPrefixInfo -> Bool
/= :: CabalPrefixInfo -> CabalPrefixInfo -> Bool
Eq, Int -> CabalPrefixInfo -> ShowS
[CabalPrefixInfo] -> ShowS
CabalPrefixInfo -> String
(Int -> CabalPrefixInfo -> ShowS)
-> (CabalPrefixInfo -> String)
-> ([CabalPrefixInfo] -> ShowS)
-> Show CabalPrefixInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CabalPrefixInfo -> ShowS
showsPrec :: Int -> CabalPrefixInfo -> ShowS
$cshow :: CabalPrefixInfo -> String
show :: CabalPrefixInfo -> String
$cshowList :: [CabalPrefixInfo] -> ShowS
showList :: [CabalPrefixInfo] -> ShowS
Show)
data Apostrophe = Surrounded | LeftSide
deriving (Apostrophe -> Apostrophe -> Bool
(Apostrophe -> Apostrophe -> Bool)
-> (Apostrophe -> Apostrophe -> Bool) -> Eq Apostrophe
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Apostrophe -> Apostrophe -> Bool
== :: Apostrophe -> Apostrophe -> Bool
$c/= :: Apostrophe -> Apostrophe -> Bool
/= :: Apostrophe -> Apostrophe -> Bool
Eq, Eq Apostrophe
Eq Apostrophe =>
(Apostrophe -> Apostrophe -> Ordering)
-> (Apostrophe -> Apostrophe -> Bool)
-> (Apostrophe -> Apostrophe -> Bool)
-> (Apostrophe -> Apostrophe -> Bool)
-> (Apostrophe -> Apostrophe -> Bool)
-> (Apostrophe -> Apostrophe -> Apostrophe)
-> (Apostrophe -> Apostrophe -> Apostrophe)
-> Ord Apostrophe
Apostrophe -> Apostrophe -> Bool
Apostrophe -> Apostrophe -> Ordering
Apostrophe -> Apostrophe -> Apostrophe
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 :: Apostrophe -> Apostrophe -> Ordering
compare :: Apostrophe -> Apostrophe -> Ordering
$c< :: Apostrophe -> Apostrophe -> Bool
< :: Apostrophe -> Apostrophe -> Bool
$c<= :: Apostrophe -> Apostrophe -> Bool
<= :: Apostrophe -> Apostrophe -> Bool
$c> :: Apostrophe -> Apostrophe -> Bool
> :: Apostrophe -> Apostrophe -> Bool
$c>= :: Apostrophe -> Apostrophe -> Bool
>= :: Apostrophe -> Apostrophe -> Bool
$cmax :: Apostrophe -> Apostrophe -> Apostrophe
max :: Apostrophe -> Apostrophe -> Apostrophe
$cmin :: Apostrophe -> Apostrophe -> Apostrophe
min :: Apostrophe -> Apostrophe -> Apostrophe
Ord, Int -> Apostrophe -> ShowS
[Apostrophe] -> ShowS
Apostrophe -> String
(Int -> Apostrophe -> ShowS)
-> (Apostrophe -> String)
-> ([Apostrophe] -> ShowS)
-> Show Apostrophe
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Apostrophe -> ShowS
showsPrec :: Int -> Apostrophe -> ShowS
$cshow :: Apostrophe -> String
show :: Apostrophe -> String
$cshowList :: [Apostrophe] -> ShowS
showList :: [Apostrophe] -> ShowS
Show)
applyStringNotation :: Maybe Apostrophe -> T.Text -> T.Text
applyStringNotation :: Maybe Apostrophe -> Text -> Text
applyStringNotation (Just Apostrophe
Surrounded) Text
compl = Text
compl
applyStringNotation (Just Apostrophe
LeftSide) Text
compl = Text
compl Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
applyStringNotation Maybe Apostrophe
Nothing Text
compl
| Just Char
_ <- (Char -> Bool) -> Text -> Maybe Char
T.find (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ') Text
compl = Text
"\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
compl Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
| Bool
otherwise = Text
compl