{-# LANGUAGE DeriveGeneric       #-}
{-# LANGUAGE LambdaCase          #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# 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
  | -- | This should never occur since we extract the word to lookup from the same map we look it up in.
    LogUnknownKeyWordInContextError KeyWordName
  | -- | This should never occur since we extract the word to lookup from the same map we look it up in.
    LogUnknownStanzaNameInContextError StanzaName
  | LogFilePathCompleterIOError FilePath IOError
  | LogUseWithStaleFastNoResult
  | LogMapLookUpOfKnownKeyFailed T.Text
  deriving (Int -> Log -> ShowS
[Log] -> ShowS
Log -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Log] -> ShowS
$cshowList :: [Log] -> ShowS
show :: Log -> String
$cshow :: Log -> String
showsPrec :: Int -> Log -> ShowS
$cshowsPrec :: Int -> Log -> ShowS
Show)

instance Pretty Log where
  pretty :: forall ann. Log -> Doc ann
pretty = \case
    LogFileSplitError Position
pos -> Doc ann
"An error occured when trying to separate the lines of the cabal file at position:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Show a => a -> Doc ann
viaShow Position
pos
    LogUnknownKeyWordInContextError Text
kw ->
      Doc ann
"Lookup of key word failed for:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Show a => a -> Doc ann
viaShow Text
kw
    LogUnknownStanzaNameInContextError Text
sn ->
      Doc ann
"Lookup of stanza name failed for:" forall ann. Doc ann -> Doc ann -> 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:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Show a => a -> Doc ann
viaShow String
fp forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
"the following unexpected IO error occured" forall ann. Doc ann -> Doc ann -> 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" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Show a => a -> Doc ann
viaShow Text
key

type instance RuleResult ParseCabal = Parse.GenericPackageDescription

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

instance Hashable ParseCabal

instance NFData ParseCabal

-- | The context a cursor can be in within a cabal file.
--
--  We can be in stanzas or the top level,
--  and additionally we can be in a context where we have already
--  written a keyword but no value for it yet
type Context = (StanzaContext, FieldContext)

-- | Context inside a cabal file.
--  Used to decide which keywords to suggest.
data StanzaContext
  = -- | Top level context in a cabal file such as 'author'
    TopLevel
  | -- | Nested context in a cabal file, such as 'library'.
    --
    -- Stanzas have their own fields which differ from top-level fields.
    -- Each stanza must be named, such as 'executable exe',
    -- except for the main library.
    Stanza StanzaType (Maybe StanzaName)
  deriving (StanzaContext -> StanzaContext -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StanzaContext -> StanzaContext -> Bool
$c/= :: StanzaContext -> StanzaContext -> Bool
== :: StanzaContext -> StanzaContext -> Bool
$c== :: StanzaContext -> StanzaContext -> Bool
Eq, Int -> StanzaContext -> ShowS
[StanzaContext] -> ShowS
StanzaContext -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StanzaContext] -> ShowS
$cshowList :: [StanzaContext] -> ShowS
show :: StanzaContext -> String
$cshow :: StanzaContext -> String
showsPrec :: Int -> StanzaContext -> ShowS
$cshowsPrec :: Int -> StanzaContext -> ShowS
Show, ReadPrec [StanzaContext]
ReadPrec StanzaContext
Int -> ReadS StanzaContext
ReadS [StanzaContext]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StanzaContext]
$creadListPrec :: ReadPrec [StanzaContext]
readPrec :: ReadPrec StanzaContext
$creadPrec :: ReadPrec StanzaContext
readList :: ReadS [StanzaContext]
$creadList :: ReadS [StanzaContext]
readsPrec :: Int -> ReadS StanzaContext
$creadsPrec :: Int -> ReadS StanzaContext
Read)

-- | Keyword context in a cabal file.
--
--  Used to decide whether to suggest values or keywords.
data FieldContext
  = -- | Key word context, where a keyword
    -- occurs right before the current word
    -- to be completed
    KeyWord KeyWordName
  | -- | Keyword context where no keyword occurs
    -- right before the current word to be completed
    None
  deriving (FieldContext -> FieldContext -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldContext -> FieldContext -> Bool
$c/= :: FieldContext -> FieldContext -> Bool
== :: FieldContext -> FieldContext -> Bool
$c== :: FieldContext -> FieldContext -> Bool
Eq, Int -> FieldContext -> ShowS
[FieldContext] -> ShowS
FieldContext -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FieldContext] -> ShowS
$cshowList :: [FieldContext] -> ShowS
show :: FieldContext -> String
$cshow :: FieldContext -> String
showsPrec :: Int -> FieldContext -> ShowS
$cshowsPrec :: Int -> FieldContext -> ShowS
Show, ReadPrec [FieldContext]
ReadPrec FieldContext
Int -> ReadS FieldContext
ReadS [FieldContext]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldContext]
$creadListPrec :: ReadPrec [FieldContext]
readPrec :: ReadPrec FieldContext
$creadPrec :: ReadPrec FieldContext
readList :: ReadS [FieldContext]
$creadList :: ReadS [FieldContext]
readsPrec :: Int -> ReadS FieldContext
$creadsPrec :: Int -> ReadS FieldContext
Read)

type KeyWordName = T.Text

type StanzaName = T.Text

type StanzaType = T.Text

-- | Information regarding the current completion status
--
--  Example: @"dir1/fi@ having been written to the file
--  would correspond to:
--
--  @
--    completionPrefix = "dir1/fi"
--    isStringNotation = LeftSide
--    ...
--  @
--
--  We define this type instead of simply using
--  VFS.PosPrefixInfo since e.g. for filepaths we
--  need more than just the word before the
--  cursor (as can be seen above),
--  since we want to capture the whole filepath
--  before the cursor.
--
--  We also use this type to wrap all information
--  necessary to complete filepaths and other values
--  in a cabal file.
data CabalPrefixInfo = CabalPrefixInfo
  { -- | text prefix to complete
    CabalPrefixInfo -> Text
completionPrefix         :: T.Text,
    -- | Did the completion happen in the context of a string notation,
    -- i.e. are there apostrophes around the item to be completed
    CabalPrefixInfo -> Maybe Apostrophe
isStringNotation         :: Maybe Apostrophe,
    -- | the current position of the cursor in the file
    CabalPrefixInfo -> Position
completionCursorPosition :: Position,
    -- | range where completion is to be inserted
    CabalPrefixInfo -> Range
completionRange          :: Range,
    -- | directory of the handled cabal file
    CabalPrefixInfo -> String
completionWorkingDir     :: FilePath,
    -- | filename of the handled cabal file
    CabalPrefixInfo -> Text
completionFileName       :: T.Text
  }
  deriving (CabalPrefixInfo -> CabalPrefixInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CabalPrefixInfo -> CabalPrefixInfo -> Bool
$c/= :: CabalPrefixInfo -> CabalPrefixInfo -> Bool
== :: CabalPrefixInfo -> CabalPrefixInfo -> Bool
$c== :: CabalPrefixInfo -> CabalPrefixInfo -> Bool
Eq, Int -> CabalPrefixInfo -> ShowS
[CabalPrefixInfo] -> ShowS
CabalPrefixInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CabalPrefixInfo] -> ShowS
$cshowList :: [CabalPrefixInfo] -> ShowS
show :: CabalPrefixInfo -> String
$cshow :: CabalPrefixInfo -> String
showsPrec :: Int -> CabalPrefixInfo -> ShowS
$cshowsPrec :: Int -> CabalPrefixInfo -> ShowS
Show)

-- | Where are the apostrophes around the item to be completed?
--
--  'Surrounded' means the item to complete already has the necessary apostrophes,
--  while 'LeftSide' means, a closing apostrophe has to be added after the completion item.
data Apostrophe = Surrounded | LeftSide
  deriving (Apostrophe -> Apostrophe -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Apostrophe -> Apostrophe -> Bool
$c/= :: Apostrophe -> Apostrophe -> Bool
== :: Apostrophe -> Apostrophe -> Bool
$c== :: Apostrophe -> Apostrophe -> Bool
Eq, Eq 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
min :: Apostrophe -> Apostrophe -> Apostrophe
$cmin :: Apostrophe -> Apostrophe -> Apostrophe
max :: Apostrophe -> Apostrophe -> Apostrophe
$cmax :: Apostrophe -> Apostrophe -> Apostrophe
>= :: Apostrophe -> Apostrophe -> Bool
$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
compare :: Apostrophe -> Apostrophe -> Ordering
$ccompare :: Apostrophe -> Apostrophe -> Ordering
Ord, Int -> Apostrophe -> ShowS
[Apostrophe] -> ShowS
Apostrophe -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Apostrophe] -> ShowS
$cshowList :: [Apostrophe] -> ShowS
show :: Apostrophe -> String
$cshow :: Apostrophe -> String
showsPrec :: Int -> Apostrophe -> ShowS
$cshowsPrec :: Int -> Apostrophe -> ShowS
Show)

-- | Wraps a completion in apostrophes where appropriate.
--
--  If a completion starts with an apostrophe we want to end it with an apostrophe.
--  If a completed filepath contains a space, it can only be written in the cabal
--  file if it is wrapped in apostrophes, thus we wrap it.
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 forall a. Semigroup a => a -> a -> a
<> Text
"\""
applyStringNotation Maybe Apostrophe
Nothing Text
compl
  | Just Char
_ <- (Char -> Bool) -> Text -> Maybe Char
T.find (forall a. Eq a => a -> a -> Bool
== Char
' ') Text
compl = Text
"\"" forall a. Semigroup a => a -> a -> a
<> Text
compl forall a. Semigroup a => a -> a -> a
<> Text
"\""
  | Bool
otherwise = Text
compl