{-# LANGUAGE DeriveAnyClass     #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE OverloadedStrings  #-}

module Ide.Plugin.Splice.Types where

import           Data.Aeson                  (FromJSON, ToJSON)
import qualified Data.Text                   as T
 -- This import is needed for the ToJSON/FromJSON instances of RealSrcSpan
import           Development.IDE             ()
import           Development.IDE.GHC.Compat  (RealSrcSpan)
import           GHC.Generics                (Generic)
import           Ide.Types                   (CommandId)
import           Language.LSP.Protocol.Types (VersionedTextDocumentIdentifier)

-- | Parameter for the addMethods PluginCommand.
data ExpandSpliceParams = ExpandSpliceParams
    { ExpandSpliceParams -> VersionedTextDocumentIdentifier
verTxtDocId   :: VersionedTextDocumentIdentifier
    , ExpandSpliceParams -> RealSrcSpan
spliceSpan    :: RealSrcSpan
    , ExpandSpliceParams -> SpliceContext
spliceContext :: SpliceContext
    }
    deriving (Int -> ExpandSpliceParams -> ShowS
[ExpandSpliceParams] -> ShowS
ExpandSpliceParams -> String
(Int -> ExpandSpliceParams -> ShowS)
-> (ExpandSpliceParams -> String)
-> ([ExpandSpliceParams] -> ShowS)
-> Show ExpandSpliceParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExpandSpliceParams -> ShowS
showsPrec :: Int -> ExpandSpliceParams -> ShowS
$cshow :: ExpandSpliceParams -> String
show :: ExpandSpliceParams -> String
$cshowList :: [ExpandSpliceParams] -> ShowS
showList :: [ExpandSpliceParams] -> ShowS
Show, ExpandSpliceParams -> ExpandSpliceParams -> Bool
(ExpandSpliceParams -> ExpandSpliceParams -> Bool)
-> (ExpandSpliceParams -> ExpandSpliceParams -> Bool)
-> Eq ExpandSpliceParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExpandSpliceParams -> ExpandSpliceParams -> Bool
== :: ExpandSpliceParams -> ExpandSpliceParams -> Bool
$c/= :: ExpandSpliceParams -> ExpandSpliceParams -> Bool
/= :: ExpandSpliceParams -> ExpandSpliceParams -> Bool
Eq, (forall x. ExpandSpliceParams -> Rep ExpandSpliceParams x)
-> (forall x. Rep ExpandSpliceParams x -> ExpandSpliceParams)
-> Generic ExpandSpliceParams
forall x. Rep ExpandSpliceParams x -> ExpandSpliceParams
forall x. ExpandSpliceParams -> Rep ExpandSpliceParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExpandSpliceParams -> Rep ExpandSpliceParams x
from :: forall x. ExpandSpliceParams -> Rep ExpandSpliceParams x
$cto :: forall x. Rep ExpandSpliceParams x -> ExpandSpliceParams
to :: forall x. Rep ExpandSpliceParams x -> ExpandSpliceParams
Generic)
    deriving anyclass ([ExpandSpliceParams] -> Value
[ExpandSpliceParams] -> Encoding
ExpandSpliceParams -> Bool
ExpandSpliceParams -> Value
ExpandSpliceParams -> Encoding
(ExpandSpliceParams -> Value)
-> (ExpandSpliceParams -> Encoding)
-> ([ExpandSpliceParams] -> Value)
-> ([ExpandSpliceParams] -> Encoding)
-> (ExpandSpliceParams -> Bool)
-> ToJSON ExpandSpliceParams
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ExpandSpliceParams -> Value
toJSON :: ExpandSpliceParams -> Value
$ctoEncoding :: ExpandSpliceParams -> Encoding
toEncoding :: ExpandSpliceParams -> Encoding
$ctoJSONList :: [ExpandSpliceParams] -> Value
toJSONList :: [ExpandSpliceParams] -> Value
$ctoEncodingList :: [ExpandSpliceParams] -> Encoding
toEncodingList :: [ExpandSpliceParams] -> Encoding
$comitField :: ExpandSpliceParams -> Bool
omitField :: ExpandSpliceParams -> Bool
ToJSON, Maybe ExpandSpliceParams
Value -> Parser [ExpandSpliceParams]
Value -> Parser ExpandSpliceParams
(Value -> Parser ExpandSpliceParams)
-> (Value -> Parser [ExpandSpliceParams])
-> Maybe ExpandSpliceParams
-> FromJSON ExpandSpliceParams
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ExpandSpliceParams
parseJSON :: Value -> Parser ExpandSpliceParams
$cparseJSONList :: Value -> Parser [ExpandSpliceParams]
parseJSONList :: Value -> Parser [ExpandSpliceParams]
$comittedField :: Maybe ExpandSpliceParams
omittedField :: Maybe ExpandSpliceParams
FromJSON)

-- FIXME: HsDecl needs different treatment of splicing.
data SpliceContext = Expr | HsDecl | Pat | HsType
    deriving (ReadPrec [SpliceContext]
ReadPrec SpliceContext
Int -> ReadS SpliceContext
ReadS [SpliceContext]
(Int -> ReadS SpliceContext)
-> ReadS [SpliceContext]
-> ReadPrec SpliceContext
-> ReadPrec [SpliceContext]
-> Read SpliceContext
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SpliceContext
readsPrec :: Int -> ReadS SpliceContext
$creadList :: ReadS [SpliceContext]
readList :: ReadS [SpliceContext]
$creadPrec :: ReadPrec SpliceContext
readPrec :: ReadPrec SpliceContext
$creadListPrec :: ReadPrec [SpliceContext]
readListPrec :: ReadPrec [SpliceContext]
Read, Int -> SpliceContext -> ShowS
[SpliceContext] -> ShowS
SpliceContext -> String
(Int -> SpliceContext -> ShowS)
-> (SpliceContext -> String)
-> ([SpliceContext] -> ShowS)
-> Show SpliceContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SpliceContext -> ShowS
showsPrec :: Int -> SpliceContext -> ShowS
$cshow :: SpliceContext -> String
show :: SpliceContext -> String
$cshowList :: [SpliceContext] -> ShowS
showList :: [SpliceContext] -> ShowS
Show, SpliceContext -> SpliceContext -> Bool
(SpliceContext -> SpliceContext -> Bool)
-> (SpliceContext -> SpliceContext -> Bool) -> Eq SpliceContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SpliceContext -> SpliceContext -> Bool
== :: SpliceContext -> SpliceContext -> Bool
$c/= :: SpliceContext -> SpliceContext -> Bool
/= :: SpliceContext -> SpliceContext -> Bool
Eq, Eq SpliceContext
Eq SpliceContext =>
(SpliceContext -> SpliceContext -> Ordering)
-> (SpliceContext -> SpliceContext -> Bool)
-> (SpliceContext -> SpliceContext -> Bool)
-> (SpliceContext -> SpliceContext -> Bool)
-> (SpliceContext -> SpliceContext -> Bool)
-> (SpliceContext -> SpliceContext -> SpliceContext)
-> (SpliceContext -> SpliceContext -> SpliceContext)
-> Ord SpliceContext
SpliceContext -> SpliceContext -> Bool
SpliceContext -> SpliceContext -> Ordering
SpliceContext -> SpliceContext -> SpliceContext
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 :: SpliceContext -> SpliceContext -> Ordering
compare :: SpliceContext -> SpliceContext -> Ordering
$c< :: SpliceContext -> SpliceContext -> Bool
< :: SpliceContext -> SpliceContext -> Bool
$c<= :: SpliceContext -> SpliceContext -> Bool
<= :: SpliceContext -> SpliceContext -> Bool
$c> :: SpliceContext -> SpliceContext -> Bool
> :: SpliceContext -> SpliceContext -> Bool
$c>= :: SpliceContext -> SpliceContext -> Bool
>= :: SpliceContext -> SpliceContext -> Bool
$cmax :: SpliceContext -> SpliceContext -> SpliceContext
max :: SpliceContext -> SpliceContext -> SpliceContext
$cmin :: SpliceContext -> SpliceContext -> SpliceContext
min :: SpliceContext -> SpliceContext -> SpliceContext
Ord, (forall x. SpliceContext -> Rep SpliceContext x)
-> (forall x. Rep SpliceContext x -> SpliceContext)
-> Generic SpliceContext
forall x. Rep SpliceContext x -> SpliceContext
forall x. SpliceContext -> Rep SpliceContext x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SpliceContext -> Rep SpliceContext x
from :: forall x. SpliceContext -> Rep SpliceContext x
$cto :: forall x. Rep SpliceContext x -> SpliceContext
to :: forall x. Rep SpliceContext x -> SpliceContext
Generic)
    deriving anyclass ([SpliceContext] -> Value
[SpliceContext] -> Encoding
SpliceContext -> Bool
SpliceContext -> Value
SpliceContext -> Encoding
(SpliceContext -> Value)
-> (SpliceContext -> Encoding)
-> ([SpliceContext] -> Value)
-> ([SpliceContext] -> Encoding)
-> (SpliceContext -> Bool)
-> ToJSON SpliceContext
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: SpliceContext -> Value
toJSON :: SpliceContext -> Value
$ctoEncoding :: SpliceContext -> Encoding
toEncoding :: SpliceContext -> Encoding
$ctoJSONList :: [SpliceContext] -> Value
toJSONList :: [SpliceContext] -> Value
$ctoEncodingList :: [SpliceContext] -> Encoding
toEncodingList :: [SpliceContext] -> Encoding
$comitField :: SpliceContext -> Bool
omitField :: SpliceContext -> Bool
ToJSON, Maybe SpliceContext
Value -> Parser [SpliceContext]
Value -> Parser SpliceContext
(Value -> Parser SpliceContext)
-> (Value -> Parser [SpliceContext])
-> Maybe SpliceContext
-> FromJSON SpliceContext
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser SpliceContext
parseJSON :: Value -> Parser SpliceContext
$cparseJSONList :: Value -> Parser [SpliceContext]
parseJSONList :: Value -> Parser [SpliceContext]
$comittedField :: Maybe SpliceContext
omittedField :: Maybe SpliceContext
FromJSON)

data ExpandStyle = Inplace | Commented
    deriving (ReadPrec [ExpandStyle]
ReadPrec ExpandStyle
Int -> ReadS ExpandStyle
ReadS [ExpandStyle]
(Int -> ReadS ExpandStyle)
-> ReadS [ExpandStyle]
-> ReadPrec ExpandStyle
-> ReadPrec [ExpandStyle]
-> Read ExpandStyle
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ExpandStyle
readsPrec :: Int -> ReadS ExpandStyle
$creadList :: ReadS [ExpandStyle]
readList :: ReadS [ExpandStyle]
$creadPrec :: ReadPrec ExpandStyle
readPrec :: ReadPrec ExpandStyle
$creadListPrec :: ReadPrec [ExpandStyle]
readListPrec :: ReadPrec [ExpandStyle]
Read, Int -> ExpandStyle -> ShowS
[ExpandStyle] -> ShowS
ExpandStyle -> String
(Int -> ExpandStyle -> ShowS)
-> (ExpandStyle -> String)
-> ([ExpandStyle] -> ShowS)
-> Show ExpandStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExpandStyle -> ShowS
showsPrec :: Int -> ExpandStyle -> ShowS
$cshow :: ExpandStyle -> String
show :: ExpandStyle -> String
$cshowList :: [ExpandStyle] -> ShowS
showList :: [ExpandStyle] -> ShowS
Show, ExpandStyle -> ExpandStyle -> Bool
(ExpandStyle -> ExpandStyle -> Bool)
-> (ExpandStyle -> ExpandStyle -> Bool) -> Eq ExpandStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExpandStyle -> ExpandStyle -> Bool
== :: ExpandStyle -> ExpandStyle -> Bool
$c/= :: ExpandStyle -> ExpandStyle -> Bool
/= :: ExpandStyle -> ExpandStyle -> Bool
Eq, Eq ExpandStyle
Eq ExpandStyle =>
(ExpandStyle -> ExpandStyle -> Ordering)
-> (ExpandStyle -> ExpandStyle -> Bool)
-> (ExpandStyle -> ExpandStyle -> Bool)
-> (ExpandStyle -> ExpandStyle -> Bool)
-> (ExpandStyle -> ExpandStyle -> Bool)
-> (ExpandStyle -> ExpandStyle -> ExpandStyle)
-> (ExpandStyle -> ExpandStyle -> ExpandStyle)
-> Ord ExpandStyle
ExpandStyle -> ExpandStyle -> Bool
ExpandStyle -> ExpandStyle -> Ordering
ExpandStyle -> ExpandStyle -> ExpandStyle
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 :: ExpandStyle -> ExpandStyle -> Ordering
compare :: ExpandStyle -> ExpandStyle -> Ordering
$c< :: ExpandStyle -> ExpandStyle -> Bool
< :: ExpandStyle -> ExpandStyle -> Bool
$c<= :: ExpandStyle -> ExpandStyle -> Bool
<= :: ExpandStyle -> ExpandStyle -> Bool
$c> :: ExpandStyle -> ExpandStyle -> Bool
> :: ExpandStyle -> ExpandStyle -> Bool
$c>= :: ExpandStyle -> ExpandStyle -> Bool
>= :: ExpandStyle -> ExpandStyle -> Bool
$cmax :: ExpandStyle -> ExpandStyle -> ExpandStyle
max :: ExpandStyle -> ExpandStyle -> ExpandStyle
$cmin :: ExpandStyle -> ExpandStyle -> ExpandStyle
min :: ExpandStyle -> ExpandStyle -> ExpandStyle
Ord, (forall x. ExpandStyle -> Rep ExpandStyle x)
-> (forall x. Rep ExpandStyle x -> ExpandStyle)
-> Generic ExpandStyle
forall x. Rep ExpandStyle x -> ExpandStyle
forall x. ExpandStyle -> Rep ExpandStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExpandStyle -> Rep ExpandStyle x
from :: forall x. ExpandStyle -> Rep ExpandStyle x
$cto :: forall x. Rep ExpandStyle x -> ExpandStyle
to :: forall x. Rep ExpandStyle x -> ExpandStyle
Generic)

expandStyles :: [(ExpandStyle, (T.Text, CommandId))]
expandStyles :: [(ExpandStyle, (Text, CommandId))]
expandStyles =
    [ (ExpandStyle
Inplace, (Text
inplaceCmdName, CommandId
expandInplaceId))
    -- , (Commented, commentedCmdName, expandCommentedId)
    ]

toExpandCmdTitle :: ExpandStyle -> T.Text
toExpandCmdTitle :: ExpandStyle -> Text
toExpandCmdTitle ExpandStyle
Inplace   = Text
inplaceCmdName
toExpandCmdTitle ExpandStyle
Commented = Text
commentedCmdName

toCommandId :: ExpandStyle -> CommandId
toCommandId :: ExpandStyle -> CommandId
toCommandId ExpandStyle
Inplace   = CommandId
expandInplaceId
toCommandId ExpandStyle
Commented = CommandId
expandCommentedId

expandInplaceId, expandCommentedId :: CommandId
expandInplaceId :: CommandId
expandInplaceId = CommandId
"expandTHSpliceInplace"
expandCommentedId :: CommandId
expandCommentedId = CommandId
"expandTHSpliceCommented"

inplaceCmdName :: T.Text
inplaceCmdName :: Text
inplaceCmdName = Text
"expand TemplateHaskell Splice (in-place)"

commentedCmdName :: T.Text
commentedCmdName :: Text
commentedCmdName = Text
"expand TemplateHaskell Splice (commented-out)"