module Refact.Apply
( applyRefactorings,
applyRefactorings',
runRefactoring,
parseExtensions,
)
where
import Control.Monad (unless)
import Data.List (intercalate)
import Refact.Compat (Module)
import Refact.Fixity (applyFixities)
import Refact.Internal
import Refact.Types (Refactoring, SrcSpan)
applyRefactorings ::
FilePath ->
Maybe (Int, Int) ->
[[Refactoring SrcSpan]] ->
FilePath ->
[String] ->
IO String
applyRefactorings :: String
-> Maybe (Int, Int)
-> [[Refactoring SrcSpan]]
-> String
-> [String]
-> IO String
applyRefactorings String
libdir Maybe (Int, Int)
optionsPos [[Refactoring SrcSpan]]
inp String
file [String]
exts = do
let ([Extension]
enabled, [Extension]
disabled, [String]
invalid) = [String] -> ([Extension], [Extension], [String])
parseExtensions [String]
exts
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
invalid) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Unsupported extensions: " forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
invalid
Module
m <-
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a. String -> Errors -> a
onError String
"apply") Module -> IO Module
applyFixities
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String
-> ([Extension], [Extension])
-> String
-> IO (Either Errors Module)
parseModuleWithArgs String
libdir ([Extension]
enabled, [Extension]
disabled) String
file
Maybe (Int, Int)
-> Bool
-> [(String, [Refactoring SrcSpan])]
-> Maybe String
-> Verbosity
-> Module
-> IO String
apply Maybe (Int, Int)
optionsPos Bool
False ((forall a. Monoid a => a
mempty,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Refactoring SrcSpan]]
inp) (forall a. a -> Maybe a
Just String
file) Verbosity
Silent Module
m
applyRefactorings' ::
Maybe (Int, Int) ->
[[Refactoring SrcSpan]] ->
Module ->
IO String
applyRefactorings' :: Maybe (Int, Int) -> [[Refactoring SrcSpan]] -> Module -> IO String
applyRefactorings' Maybe (Int, Int)
optionsPos [[Refactoring SrcSpan]]
inp = Maybe (Int, Int)
-> Bool
-> [(String, [Refactoring SrcSpan])]
-> Maybe String
-> Verbosity
-> Module
-> IO String
apply Maybe (Int, Int)
optionsPos Bool
False ((forall a. Monoid a => a
mempty,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Refactoring SrcSpan]]
inp) forall a. Maybe a
Nothing Verbosity
Silent