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)

-- | Apply a set of refactorings as supplied by HLint
applyRefactorings ::
  -- | FilePath to [GHC's libdir](https://downloads.haskell.org/ghc/latest/docs/users_guide/using.html#ghc-flag---print-libdir).
  --
  -- It is possible to use @libdir@ from [ghc-paths package](https://hackage.haskell.org/package/ghc-paths), but note
  -- this will make it difficult to provide a binary distribution of your program.
  FilePath ->
  -- | Apply hints relevant to a specific position
  Maybe (Int, Int) ->
  -- | 'Refactoring's to apply. Each inner list corresponds to an HLint
  -- <https://hackage.haskell.org/package/hlint/docs/Language-Haskell-HLint.html#t:Idea Idea>.
  -- An @Idea@ may have more than one 'Refactoring'.
  --
  -- The @Idea@s are sorted in ascending order of starting location, and are applied
  -- in that order. If two @Idea@s start at the same location, the one with the larger
  -- source span comes first. An @Idea@ is filtered out (ignored) if there is an @Idea@
  -- prior to it which has an overlapping source span and is not filtered out.
  [[Refactoring SrcSpan]] ->
  -- | Target file
  FilePath ->
  -- | GHC extensions, e.g., @LambdaCase@, @NoStarIsType@. The list is processed from left
  -- to right. An extension (e.g., @StarIsType@) may be overridden later (e.g., by @NoStarIsType@).
  --
  -- These are in addition to the @LANGUAGE@ pragmas in the target file. When they conflict
  -- with the @LANGUAGE@ pragmas, pragmas win.
  [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

-- | Like 'applyRefactorings', but takes a parsed module rather than a file path to parse.
applyRefactorings' ::
  Maybe (Int, Int) ->
  [[Refactoring SrcSpan]] ->
  -- | ghc-exactprint AST annotations. This can be obtained from
  -- 'Language.Haskell.GHC.ExactPrint.Parsers.postParseTransform'.
  -- Anns ->
  -- | Parsed module
  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