{-# LANGUAGE OverloadedStrings #-}
module Ide.Plugin.Floskell
( descriptor
, provider
) where
import Control.Monad.IO.Class
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import Development.IDE hiding (pluginHandlers)
import Floskell
import Ide.PluginUtils
import Ide.Types
import Language.LSP.Types
descriptor :: PluginId -> PluginDescriptor IdeState
descriptor :: PluginId -> PluginDescriptor IdeState
descriptor PluginId
plId = (forall ideState. PluginId -> PluginDescriptor ideState
defaultPluginDescriptor PluginId
plId)
{ pluginHandlers :: PluginHandlers IdeState
pluginHandlers = forall a. FormattingHandler a -> PluginHandlers a
mkFormattingHandlers FormattingHandler IdeState
provider
}
provider :: FormattingHandler IdeState
provider :: FormattingHandler IdeState
provider IdeState
_ideState FormattingType
typ Text
contents NormalizedFilePath
fp FormattingOptions
_ = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
let file :: [Char]
file = NormalizedFilePath -> [Char]
fromNormalizedFilePath NormalizedFilePath
fp
AppConfig
config <- [Char] -> IO AppConfig
findConfigOrDefault [Char]
file
let (Range
range, Text
selectedContents) = case FormattingType
typ of
FormattingType
FormatText -> (Text -> Range
fullRange Text
contents, Text
contents)
FormatRange Range
r -> (Range -> Range
normalize Range
r, Range -> Text -> Text
extractRange Range
r Text
contents)
result :: Either [Char] ByteString
result = AppConfig -> Maybe [Char] -> ByteString -> Either [Char] ByteString
reformat AppConfig
config (forall a. a -> Maybe a
Just [Char]
file) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TL.encodeUtf8 forall a b. (a -> b) -> a -> b
$ Text -> Text
TL.fromStrict Text
selectedContents
case Either [Char] ByteString
result of
Left [Char]
err -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Text -> ResponseError
responseError forall a b. (a -> b) -> a -> b
$ [Char] -> Text
T.pack forall a b. (a -> b) -> a -> b
$ [Char]
"floskellCmd: " forall a. [a] -> [a] -> [a]
++ [Char]
err
Right ByteString
new -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a. [a] -> List a
List [Range -> Text -> TextEdit
TextEdit Range
range forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ ByteString -> Text
TL.decodeUtf8 ByteString
new]
findConfigOrDefault :: FilePath -> IO AppConfig
findConfigOrDefault :: [Char] -> IO AppConfig
findConfigOrDefault [Char]
file = do
Maybe [Char]
mbConf <- [Char] -> IO (Maybe [Char])
findAppConfigIn [Char]
file
case Maybe [Char]
mbConf of
Just [Char]
confFile -> [Char] -> IO AppConfig
readAppConfig [Char]
confFile
Maybe [Char]
Nothing ->
let gibiansky :: Style
gibiansky = forall a. [a] -> a
head (forall a. (a -> Bool) -> [a] -> [a]
filter (\Style
s -> Style -> Text
styleName Style
s forall a. Eq a => a -> a -> Bool
== Text
"gibiansky") [Style]
styles)
in forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ AppConfig
defaultAppConfig { appStyle :: Style
appStyle = Style
gibiansky }