{-# LANGUAGE CPP                #-}
{-# LANGUAGE DeriveAnyClass     #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GADTs              #-}
{-# LANGUAGE OverloadedLabels   #-}
{-# LANGUAGE TypeFamilies       #-}
module Development.IDE.Plugin.Completions.Types (
  module Development.IDE.Plugin.Completions.Types
) where
import           Control.DeepSeq
import qualified Data.Map                     as Map
import qualified Data.Text                    as T
import           Data.Aeson
import           Data.Aeson.Types
import           Data.Hashable                (Hashable)
import           Data.Text                    (Text)
import           Data.Typeable                (Typeable)
import           Development.IDE.GHC.Compat
import           Development.IDE.Graph        (RuleResult)
import           Development.IDE.Spans.Common ()
import           GHC.Generics                 (Generic)
import           Ide.Plugin.Properties
import           Language.LSP.Protocol.Types  (CompletionItemKind (..), Uri)
import qualified Language.LSP.Protocol.Types  as J
import qualified GHC.Types.Name.Occurrence    as Occ
type instance RuleResult LocalCompletions = CachedCompletions
type instance RuleResult NonLocalCompletions = CachedCompletions
data LocalCompletions = LocalCompletions
    deriving (LocalCompletions -> LocalCompletions -> Bool
(LocalCompletions -> LocalCompletions -> Bool)
-> (LocalCompletions -> LocalCompletions -> Bool)
-> Eq LocalCompletions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LocalCompletions -> LocalCompletions -> Bool
== :: LocalCompletions -> LocalCompletions -> Bool
$c/= :: LocalCompletions -> LocalCompletions -> Bool
/= :: LocalCompletions -> LocalCompletions -> Bool
Eq, Int -> LocalCompletions -> ShowS
[LocalCompletions] -> ShowS
LocalCompletions -> String
(Int -> LocalCompletions -> ShowS)
-> (LocalCompletions -> String)
-> ([LocalCompletions] -> ShowS)
-> Show LocalCompletions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LocalCompletions -> ShowS
showsPrec :: Int -> LocalCompletions -> ShowS
$cshow :: LocalCompletions -> String
show :: LocalCompletions -> String
$cshowList :: [LocalCompletions] -> ShowS
showList :: [LocalCompletions] -> ShowS
Show, Typeable, (forall x. LocalCompletions -> Rep LocalCompletions x)
-> (forall x. Rep LocalCompletions x -> LocalCompletions)
-> Generic LocalCompletions
forall x. Rep LocalCompletions x -> LocalCompletions
forall x. LocalCompletions -> Rep LocalCompletions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LocalCompletions -> Rep LocalCompletions x
from :: forall x. LocalCompletions -> Rep LocalCompletions x
$cto :: forall x. Rep LocalCompletions x -> LocalCompletions
to :: forall x. Rep LocalCompletions x -> LocalCompletions
Generic)
instance Hashable LocalCompletions
instance NFData   LocalCompletions
data NonLocalCompletions = NonLocalCompletions
    deriving (NonLocalCompletions -> NonLocalCompletions -> Bool
(NonLocalCompletions -> NonLocalCompletions -> Bool)
-> (NonLocalCompletions -> NonLocalCompletions -> Bool)
-> Eq NonLocalCompletions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NonLocalCompletions -> NonLocalCompletions -> Bool
== :: NonLocalCompletions -> NonLocalCompletions -> Bool
$c/= :: NonLocalCompletions -> NonLocalCompletions -> Bool
/= :: NonLocalCompletions -> NonLocalCompletions -> Bool
Eq, Int -> NonLocalCompletions -> ShowS
[NonLocalCompletions] -> ShowS
NonLocalCompletions -> String
(Int -> NonLocalCompletions -> ShowS)
-> (NonLocalCompletions -> String)
-> ([NonLocalCompletions] -> ShowS)
-> Show NonLocalCompletions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NonLocalCompletions -> ShowS
showsPrec :: Int -> NonLocalCompletions -> ShowS
$cshow :: NonLocalCompletions -> String
show :: NonLocalCompletions -> String
$cshowList :: [NonLocalCompletions] -> ShowS
showList :: [NonLocalCompletions] -> ShowS
Show, Typeable, (forall x. NonLocalCompletions -> Rep NonLocalCompletions x)
-> (forall x. Rep NonLocalCompletions x -> NonLocalCompletions)
-> Generic NonLocalCompletions
forall x. Rep NonLocalCompletions x -> NonLocalCompletions
forall x. NonLocalCompletions -> Rep NonLocalCompletions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NonLocalCompletions -> Rep NonLocalCompletions x
from :: forall x. NonLocalCompletions -> Rep NonLocalCompletions x
$cto :: forall x. Rep NonLocalCompletions x -> NonLocalCompletions
to :: forall x. Rep NonLocalCompletions x -> NonLocalCompletions
Generic)
instance Hashable NonLocalCompletions
instance NFData   NonLocalCompletions
data Backtick = Surrounded | LeftSide
  deriving (Backtick -> Backtick -> Bool
(Backtick -> Backtick -> Bool)
-> (Backtick -> Backtick -> Bool) -> Eq Backtick
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Backtick -> Backtick -> Bool
== :: Backtick -> Backtick -> Bool
$c/= :: Backtick -> Backtick -> Bool
/= :: Backtick -> Backtick -> Bool
Eq, Eq Backtick
Eq Backtick =>
(Backtick -> Backtick -> Ordering)
-> (Backtick -> Backtick -> Bool)
-> (Backtick -> Backtick -> Bool)
-> (Backtick -> Backtick -> Bool)
-> (Backtick -> Backtick -> Bool)
-> (Backtick -> Backtick -> Backtick)
-> (Backtick -> Backtick -> Backtick)
-> Ord Backtick
Backtick -> Backtick -> Bool
Backtick -> Backtick -> Ordering
Backtick -> Backtick -> Backtick
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 :: Backtick -> Backtick -> Ordering
compare :: Backtick -> Backtick -> Ordering
$c< :: Backtick -> Backtick -> Bool
< :: Backtick -> Backtick -> Bool
$c<= :: Backtick -> Backtick -> Bool
<= :: Backtick -> Backtick -> Bool
$c> :: Backtick -> Backtick -> Bool
> :: Backtick -> Backtick -> Bool
$c>= :: Backtick -> Backtick -> Bool
>= :: Backtick -> Backtick -> Bool
$cmax :: Backtick -> Backtick -> Backtick
max :: Backtick -> Backtick -> Backtick
$cmin :: Backtick -> Backtick -> Backtick
min :: Backtick -> Backtick -> Backtick
Ord, Int -> Backtick -> ShowS
[Backtick] -> ShowS
Backtick -> String
(Int -> Backtick -> ShowS)
-> (Backtick -> String) -> ([Backtick] -> ShowS) -> Show Backtick
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Backtick -> ShowS
showsPrec :: Int -> Backtick -> ShowS
$cshow :: Backtick -> String
show :: Backtick -> String
$cshowList :: [Backtick] -> ShowS
showList :: [Backtick] -> ShowS
Show)
extendImportCommandId :: Text
extendImportCommandId :: Text
extendImportCommandId = Text
"extendImport"
properties :: Properties
  '[ 'PropertyKey "autoExtendOn" TBoolean,
     'PropertyKey "snippetsOn" TBoolean]
properties :: Properties
  '[ 'PropertyKey "autoExtendOn" 'TBoolean,
     'PropertyKey "snippetsOn" 'TBoolean]
properties = Properties '[]
emptyProperties
  Properties '[]
-> (Properties '[]
    -> Properties '[ 'PropertyKey "snippetsOn" 'TBoolean])
-> Properties '[ 'PropertyKey "snippetsOn" 'TBoolean]
forall a b. a -> (a -> b) -> b
& KeyNameProxy "snippetsOn"
-> Text
-> Bool
-> Properties '[]
-> Properties '[ 'PropertyKey "snippetsOn" 'TBoolean]
forall (s :: Symbol) (r :: [PropertyKey]).
(KnownSymbol s, NotElem s r) =>
KeyNameProxy s
-> Text
-> Bool
-> Properties r
-> Properties ('PropertyKey s 'TBoolean : r)
defineBooleanProperty KeyNameProxy "snippetsOn"
#snippetsOn
    Text
"Inserts snippets when using code completions"
    Bool
True
  Properties '[ 'PropertyKey "snippetsOn" 'TBoolean]
-> (Properties '[ 'PropertyKey "snippetsOn" 'TBoolean]
    -> Properties
         '[ 'PropertyKey "autoExtendOn" 'TBoolean,
            'PropertyKey "snippetsOn" 'TBoolean])
-> Properties
     '[ 'PropertyKey "autoExtendOn" 'TBoolean,
        'PropertyKey "snippetsOn" 'TBoolean]
forall a b. a -> (a -> b) -> b
& KeyNameProxy "autoExtendOn"
-> Text
-> Bool
-> Properties '[ 'PropertyKey "snippetsOn" 'TBoolean]
-> Properties
     '[ 'PropertyKey "autoExtendOn" 'TBoolean,
        'PropertyKey "snippetsOn" 'TBoolean]
forall (s :: Symbol) (r :: [PropertyKey]).
(KnownSymbol s, NotElem s r) =>
KeyNameProxy s
-> Text
-> Bool
-> Properties r
-> Properties ('PropertyKey s 'TBoolean : r)
defineBooleanProperty KeyNameProxy "autoExtendOn"
#autoExtendOn
    Text
"Extends the import list automatically when completing a out-of-scope identifier"
    Bool
True
data CompletionsConfig = CompletionsConfig {
  CompletionsConfig -> Bool
enableSnippets   :: Bool,
  CompletionsConfig -> Bool
enableAutoExtend :: Bool,
  CompletionsConfig -> Int
maxCompletions   :: Int
}
data ExtendImport = ExtendImport
  { ExtendImport -> Uri
doc         :: !Uri,
    ExtendImport -> Text
newThing    :: !T.Text,
    ExtendImport -> Maybe Text
thingParent :: !(Maybe T.Text),
    ExtendImport -> Text
importName  :: !T.Text,
    ExtendImport -> Maybe Text
importQual  :: !(Maybe T.Text)
  }
  deriving (ExtendImport -> ExtendImport -> Bool
(ExtendImport -> ExtendImport -> Bool)
-> (ExtendImport -> ExtendImport -> Bool) -> Eq ExtendImport
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExtendImport -> ExtendImport -> Bool
== :: ExtendImport -> ExtendImport -> Bool
$c/= :: ExtendImport -> ExtendImport -> Bool
/= :: ExtendImport -> ExtendImport -> Bool
Eq, Int -> ExtendImport -> ShowS
[ExtendImport] -> ShowS
ExtendImport -> String
(Int -> ExtendImport -> ShowS)
-> (ExtendImport -> String)
-> ([ExtendImport] -> ShowS)
-> Show ExtendImport
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExtendImport -> ShowS
showsPrec :: Int -> ExtendImport -> ShowS
$cshow :: ExtendImport -> String
show :: ExtendImport -> String
$cshowList :: [ExtendImport] -> ShowS
showList :: [ExtendImport] -> ShowS
Show, (forall x. ExtendImport -> Rep ExtendImport x)
-> (forall x. Rep ExtendImport x -> ExtendImport)
-> Generic ExtendImport
forall x. Rep ExtendImport x -> ExtendImport
forall x. ExtendImport -> Rep ExtendImport x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExtendImport -> Rep ExtendImport x
from :: forall x. ExtendImport -> Rep ExtendImport x
$cto :: forall x. Rep ExtendImport x -> ExtendImport
to :: forall x. Rep ExtendImport x -> ExtendImport
Generic)
  deriving anyclass (Maybe ExtendImport
Value -> Parser [ExtendImport]
Value -> Parser ExtendImport
(Value -> Parser ExtendImport)
-> (Value -> Parser [ExtendImport])
-> Maybe ExtendImport
-> FromJSON ExtendImport
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ExtendImport
parseJSON :: Value -> Parser ExtendImport
$cparseJSONList :: Value -> Parser [ExtendImport]
parseJSONList :: Value -> Parser [ExtendImport]
$comittedField :: Maybe ExtendImport
omittedField :: Maybe ExtendImport
FromJSON, [ExtendImport] -> Value
[ExtendImport] -> Encoding
ExtendImport -> Bool
ExtendImport -> Value
ExtendImport -> Encoding
(ExtendImport -> Value)
-> (ExtendImport -> Encoding)
-> ([ExtendImport] -> Value)
-> ([ExtendImport] -> Encoding)
-> (ExtendImport -> Bool)
-> ToJSON ExtendImport
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ExtendImport -> Value
toJSON :: ExtendImport -> Value
$ctoEncoding :: ExtendImport -> Encoding
toEncoding :: ExtendImport -> Encoding
$ctoJSONList :: [ExtendImport] -> Value
toJSONList :: [ExtendImport] -> Value
$ctoEncodingList :: [ExtendImport] -> Encoding
toEncodingList :: [ExtendImport] -> Encoding
$comitField :: ExtendImport -> Bool
omitField :: ExtendImport -> Bool
ToJSON)
data Provenance
    = ImportedFrom Text
    | DefinedIn Text
    | Local SrcSpan
    deriving (Provenance -> Provenance -> Bool
(Provenance -> Provenance -> Bool)
-> (Provenance -> Provenance -> Bool) -> Eq Provenance
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Provenance -> Provenance -> Bool
== :: Provenance -> Provenance -> Bool
$c/= :: Provenance -> Provenance -> Bool
/= :: Provenance -> Provenance -> Bool
Eq, Eq Provenance
Eq Provenance =>
(Provenance -> Provenance -> Ordering)
-> (Provenance -> Provenance -> Bool)
-> (Provenance -> Provenance -> Bool)
-> (Provenance -> Provenance -> Bool)
-> (Provenance -> Provenance -> Bool)
-> (Provenance -> Provenance -> Provenance)
-> (Provenance -> Provenance -> Provenance)
-> Ord Provenance
Provenance -> Provenance -> Bool
Provenance -> Provenance -> Ordering
Provenance -> Provenance -> Provenance
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 :: Provenance -> Provenance -> Ordering
compare :: Provenance -> Provenance -> Ordering
$c< :: Provenance -> Provenance -> Bool
< :: Provenance -> Provenance -> Bool
$c<= :: Provenance -> Provenance -> Bool
<= :: Provenance -> Provenance -> Bool
$c> :: Provenance -> Provenance -> Bool
> :: Provenance -> Provenance -> Bool
$c>= :: Provenance -> Provenance -> Bool
>= :: Provenance -> Provenance -> Bool
$cmax :: Provenance -> Provenance -> Provenance
max :: Provenance -> Provenance -> Provenance
$cmin :: Provenance -> Provenance -> Provenance
min :: Provenance -> Provenance -> Provenance
Ord, Int -> Provenance -> ShowS
[Provenance] -> ShowS
Provenance -> String
(Int -> Provenance -> ShowS)
-> (Provenance -> String)
-> ([Provenance] -> ShowS)
-> Show Provenance
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Provenance -> ShowS
showsPrec :: Int -> Provenance -> ShowS
$cshow :: Provenance -> String
show :: Provenance -> String
$cshowList :: [Provenance] -> ShowS
showList :: [Provenance] -> ShowS
Show)
data CompItem = CI
  { CompItem -> CompletionItemKind
compKind            :: CompletionItemKind
  , CompItem -> Text
insertText          :: T.Text         
  , CompItem -> Provenance
provenance          :: Provenance     
  , CompItem -> Text
label               :: T.Text         
  , CompItem -> Maybe Text
typeText            :: Maybe T.Text
  , CompItem -> Maybe Backtick
isInfix             :: Maybe Backtick 
                                   
  , CompItem -> Bool
isTypeCompl         :: Bool
  , CompItem -> Maybe ExtendImport
additionalTextEdits :: Maybe ExtendImport
  , CompItem -> Maybe NameDetails
nameDetails         :: Maybe NameDetails 
  , CompItem -> Bool
isLocalCompletion   :: Bool              
  }
  deriving (CompItem -> CompItem -> Bool
(CompItem -> CompItem -> Bool)
-> (CompItem -> CompItem -> Bool) -> Eq CompItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompItem -> CompItem -> Bool
== :: CompItem -> CompItem -> Bool
$c/= :: CompItem -> CompItem -> Bool
/= :: CompItem -> CompItem -> Bool
Eq, Int -> CompItem -> ShowS
[CompItem] -> ShowS
CompItem -> String
(Int -> CompItem -> ShowS)
-> (CompItem -> String) -> ([CompItem] -> ShowS) -> Show CompItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompItem -> ShowS
showsPrec :: Int -> CompItem -> ShowS
$cshow :: CompItem -> String
show :: CompItem -> String
$cshowList :: [CompItem] -> ShowS
showList :: [CompItem] -> ShowS
Show)
newtype QualCompls
  = QualCompls { QualCompls -> Map Text [CompItem]
getQualCompls :: Map.Map T.Text [CompItem] }
  deriving Int -> QualCompls -> ShowS
[QualCompls] -> ShowS
QualCompls -> String
(Int -> QualCompls -> ShowS)
-> (QualCompls -> String)
-> ([QualCompls] -> ShowS)
-> Show QualCompls
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QualCompls -> ShowS
showsPrec :: Int -> QualCompls -> ShowS
$cshow :: QualCompls -> String
show :: QualCompls -> String
$cshowList :: [QualCompls] -> ShowS
showList :: [QualCompls] -> ShowS
Show
instance Semigroup QualCompls where
  (QualCompls Map Text [CompItem]
a) <> :: QualCompls -> QualCompls -> QualCompls
<> (QualCompls Map Text [CompItem]
b) = Map Text [CompItem] -> QualCompls
QualCompls (Map Text [CompItem] -> QualCompls)
-> Map Text [CompItem] -> QualCompls
forall a b. (a -> b) -> a -> b
$ ([CompItem] -> [CompItem] -> [CompItem])
-> Map Text [CompItem]
-> Map Text [CompItem]
-> Map Text [CompItem]
forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Map.unionWith [CompItem] -> [CompItem] -> [CompItem]
forall a. [a] -> [a] -> [a]
(++) Map Text [CompItem]
a Map Text [CompItem]
b
instance Monoid QualCompls where
  mempty :: QualCompls
mempty = Map Text [CompItem] -> QualCompls
QualCompls Map Text [CompItem]
forall k a. Map k a
Map.empty
  mappend :: QualCompls -> QualCompls -> QualCompls
mappend = QualCompls -> QualCompls -> QualCompls
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
data CachedCompletions = CC
  { CachedCompletions -> [Text]
allModNamesAsNS   :: [T.Text] 
                                
  , CachedCompletions -> [CompItem]
unqualCompls      :: [CompItem]  
  , CachedCompletions -> QualCompls
qualCompls        :: QualCompls    
                                
  , CachedCompletions -> [Maybe Text -> CompItem]
anyQualCompls     :: [Maybe T.Text -> CompItem] 
  , CachedCompletions -> [Text]
importableModules :: [T.Text] 
  }
instance Show CachedCompletions where show :: CachedCompletions -> String
show CachedCompletions
_ = String
"<cached completions>"
instance NFData CachedCompletions where
    rnf :: CachedCompletions -> ()
rnf = CachedCompletions -> ()
forall a. a -> ()
rwhnf
instance Monoid CachedCompletions where
    mempty :: CachedCompletions
mempty = [Text]
-> [CompItem]
-> QualCompls
-> [Maybe Text -> CompItem]
-> [Text]
-> CachedCompletions
CC [Text]
forall a. Monoid a => a
mempty [CompItem]
forall a. Monoid a => a
mempty QualCompls
forall a. Monoid a => a
mempty [Maybe Text -> CompItem]
forall a. Monoid a => a
mempty [Text]
forall a. Monoid a => a
mempty
instance Semigroup CachedCompletions where
    CC [Text]
a [CompItem]
b QualCompls
c [Maybe Text -> CompItem]
d [Text]
e <> :: CachedCompletions -> CachedCompletions -> CachedCompletions
<> CC [Text]
a' [CompItem]
b' QualCompls
c' [Maybe Text -> CompItem]
d' [Text]
e' =
        [Text]
-> [CompItem]
-> QualCompls
-> [Maybe Text -> CompItem]
-> [Text]
-> CachedCompletions
CC ([Text]
a[Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<>[Text]
a') ([CompItem]
b[CompItem] -> [CompItem] -> [CompItem]
forall a. Semigroup a => a -> a -> a
<>[CompItem]
b') (QualCompls
cQualCompls -> QualCompls -> QualCompls
forall a. Semigroup a => a -> a -> a
<>QualCompls
c') ([Maybe Text -> CompItem]
d[Maybe Text -> CompItem]
-> [Maybe Text -> CompItem] -> [Maybe Text -> CompItem]
forall a. Semigroup a => a -> a -> a
<>[Maybe Text -> CompItem]
d') ([Text]
e[Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<>[Text]
e')
data PosPrefixInfo = PosPrefixInfo
  { PosPrefixInfo -> Text
fullLine    :: !T.Text
    
  , PosPrefixInfo -> Text
prefixScope :: !T.Text
    
    
    
    
    
  , PosPrefixInfo -> Text
prefixText  :: !T.Text
    
    
    
  , PosPrefixInfo -> Position
cursorPos   :: !J.Position
    
  } deriving (Int -> PosPrefixInfo -> ShowS
[PosPrefixInfo] -> ShowS
PosPrefixInfo -> String
(Int -> PosPrefixInfo -> ShowS)
-> (PosPrefixInfo -> String)
-> ([PosPrefixInfo] -> ShowS)
-> Show PosPrefixInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PosPrefixInfo -> ShowS
showsPrec :: Int -> PosPrefixInfo -> ShowS
$cshow :: PosPrefixInfo -> String
show :: PosPrefixInfo -> String
$cshowList :: [PosPrefixInfo] -> ShowS
showList :: [PosPrefixInfo] -> ShowS
Show,PosPrefixInfo -> PosPrefixInfo -> Bool
(PosPrefixInfo -> PosPrefixInfo -> Bool)
-> (PosPrefixInfo -> PosPrefixInfo -> Bool) -> Eq PosPrefixInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PosPrefixInfo -> PosPrefixInfo -> Bool
== :: PosPrefixInfo -> PosPrefixInfo -> Bool
$c/= :: PosPrefixInfo -> PosPrefixInfo -> Bool
/= :: PosPrefixInfo -> PosPrefixInfo -> Bool
Eq)
data NameDetails
  = NameDetails Module OccName
  deriving (NameDetails -> NameDetails -> Bool
(NameDetails -> NameDetails -> Bool)
-> (NameDetails -> NameDetails -> Bool) -> Eq NameDetails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NameDetails -> NameDetails -> Bool
== :: NameDetails -> NameDetails -> Bool
$c/= :: NameDetails -> NameDetails -> Bool
/= :: NameDetails -> NameDetails -> Bool
Eq)
nsJSON :: NameSpace -> Value
nsJSON :: NameSpace -> Value
nsJSON NameSpace
ns
  | NameSpace -> Bool
isVarNameSpace NameSpace
ns = Text -> Value
String Text
"v"
  | NameSpace -> Bool
isDataConNameSpace NameSpace
ns = Text -> Value
String Text
"c"
  | NameSpace -> Bool
isTcClsNameSpace NameSpace
ns  = Text -> Value
String Text
"t"
  | NameSpace -> Bool
isTvNameSpace NameSpace
ns = Text -> Value
String Text
"z"
  | Bool
otherwise = String -> Value
forall a. HasCallStack => String -> a
error String
"namespace not recognized"
parseNs :: Value -> Parser NameSpace
parseNs :: Value -> Parser NameSpace
parseNs (String Text
"v") = NameSpace -> Parser NameSpace
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure NameSpace
Occ.varName
parseNs (String Text
"c") = NameSpace -> Parser NameSpace
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure NameSpace
dataName
parseNs (String Text
"t") = NameSpace -> Parser NameSpace
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure NameSpace
tcClsName
parseNs (String Text
"z") = NameSpace -> Parser NameSpace
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure NameSpace
tvName
parseNs Value
_            = Parser NameSpace
forall a. Monoid a => a
mempty
instance FromJSON NameDetails where
  parseJSON :: Value -> Parser NameDetails
parseJSON v :: Value
v@(Array Array
_)
    = do
      [Value
modname,Value
modid,Value
namesp,Value
occname] <- Value -> Parser [Value]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
      String
mn  <- Value -> Parser String
forall a. FromJSON a => Value -> Parser a
parseJSON Value
modname
      String
mid <- Value -> Parser String
forall a. FromJSON a => Value -> Parser a
parseJSON Value
modid
      NameSpace
ns <- Value -> Parser NameSpace
parseNs Value
namesp
      String
occn <- Value -> Parser String
forall a. FromJSON a => Value -> Parser a
parseJSON Value
occname
      NameDetails -> Parser NameDetails
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NameDetails -> Parser NameDetails)
-> NameDetails -> Parser NameDetails
forall a b. (a -> b) -> a -> b
$ Module -> OccName -> NameDetails
NameDetails (GenUnit UnitId -> ModuleName -> Module
forall u. u -> ModuleName -> GenModule u
mkModule (String -> GenUnit UnitId
stringToUnit String
mid) (String -> ModuleName
mkModuleName String
mn)) (NameSpace -> String -> OccName
mkOccName NameSpace
ns String
occn)
  parseJSON Value
_ = Parser NameDetails
forall a. Monoid a => a
mempty
instance ToJSON NameDetails where
  toJSON :: NameDetails -> Value
toJSON (NameDetails Module
mdl OccName
occ) = [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON [String -> Value
forall a. ToJSON a => a -> Value
toJSON String
mname,String -> Value
forall a. ToJSON a => a -> Value
toJSON String
mid,NameSpace -> Value
nsJSON NameSpace
ns,String -> Value
forall a. ToJSON a => a -> Value
toJSON String
occs]
    where
      mname :: String
mname = ModuleName -> String
moduleNameString (ModuleName -> String) -> ModuleName -> String
forall a b. (a -> b) -> a -> b
$ Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
mdl
      mid :: String
mid = UnitId -> String
unitIdString (UnitId -> String) -> UnitId -> String
forall a b. (a -> b) -> a -> b
$ Module -> UnitId
moduleUnitId Module
mdl
      ns :: NameSpace
ns = OccName -> NameSpace
occNameSpace OccName
occ
      occs :: String
occs = OccName -> String
occNameString OccName
occ
instance Show NameDetails where
  show :: NameDetails -> String
show = Value -> String
forall a. Show a => a -> String
show (Value -> String)
-> (NameDetails -> Value) -> NameDetails -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameDetails -> Value
forall a. ToJSON a => a -> Value
toJSON
data CompletionResolveData = CompletionResolveData
  { CompletionResolveData -> Uri
itemFile      :: Uri
  , CompletionResolveData -> Bool
itemNeedsType :: Bool 
  , CompletionResolveData -> NameDetails
itemName      :: NameDetails
  }
  deriving stock (forall x. CompletionResolveData -> Rep CompletionResolveData x)
-> (forall x. Rep CompletionResolveData x -> CompletionResolveData)
-> Generic CompletionResolveData
forall x. Rep CompletionResolveData x -> CompletionResolveData
forall x. CompletionResolveData -> Rep CompletionResolveData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CompletionResolveData -> Rep CompletionResolveData x
from :: forall x. CompletionResolveData -> Rep CompletionResolveData x
$cto :: forall x. Rep CompletionResolveData x -> CompletionResolveData
to :: forall x. Rep CompletionResolveData x -> CompletionResolveData
Generic
  deriving anyclass (Maybe CompletionResolveData
Value -> Parser [CompletionResolveData]
Value -> Parser CompletionResolveData
(Value -> Parser CompletionResolveData)
-> (Value -> Parser [CompletionResolveData])
-> Maybe CompletionResolveData
-> FromJSON CompletionResolveData
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser CompletionResolveData
parseJSON :: Value -> Parser CompletionResolveData
$cparseJSONList :: Value -> Parser [CompletionResolveData]
parseJSONList :: Value -> Parser [CompletionResolveData]
$comittedField :: Maybe CompletionResolveData
omittedField :: Maybe CompletionResolveData
FromJSON, [CompletionResolveData] -> Value
[CompletionResolveData] -> Encoding
CompletionResolveData -> Bool
CompletionResolveData -> Value
CompletionResolveData -> Encoding
(CompletionResolveData -> Value)
-> (CompletionResolveData -> Encoding)
-> ([CompletionResolveData] -> Value)
-> ([CompletionResolveData] -> Encoding)
-> (CompletionResolveData -> Bool)
-> ToJSON CompletionResolveData
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: CompletionResolveData -> Value
toJSON :: CompletionResolveData -> Value
$ctoEncoding :: CompletionResolveData -> Encoding
toEncoding :: CompletionResolveData -> Encoding
$ctoJSONList :: [CompletionResolveData] -> Value
toJSONList :: [CompletionResolveData] -> Value
$ctoEncodingList :: [CompletionResolveData] -> Encoding
toEncodingList :: [CompletionResolveData] -> Encoding
$comitField :: CompletionResolveData -> Bool
omitField :: CompletionResolveData -> Bool
ToJSON)