{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module CabalFmt.Refactoring (
CommentsPragmas,
refactor,
) where
import qualified Distribution.Fields as C
import CabalFmt.Monad
import CabalFmt.Refactoring.ExpandExposedModules
import CabalFmt.Refactoring.Fragments
import CabalFmt.Refactoring.GlobFiles
import CabalFmt.Refactoring.Type
import CabalFmt.Fields.SourceFiles
refactor :: forall m r. MonadCabalFmt r m => [C.Field CommentsPragmas] -> m [C.Field CommentsPragmas]
refactor :: forall (m :: * -> *) r.
MonadCabalFmt r m =>
[Field CommentsPragmas] -> m [Field CommentsPragmas]
refactor = forall r (m :: * -> *).
MonadCabalFmt r m =>
(Field CommentsPragmas -> m (Maybe (Field CommentsPragmas)))
-> [Field CommentsPragmas] -> m [Field CommentsPragmas]
rewriteFields Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))
rewrite
where
rewrite :: C.Field CommentsPragmas -> m (Maybe (C.Field CommentsPragmas))
rewrite :: Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))
rewrite f :: Field CommentsPragmas
f@(C.Field (C.Name CommentsPragmas
_ FieldName
n) [FieldLine CommentsPragmas]
_)
| FieldName
n forall a. Eq a => a -> a -> Bool
== FieldName
"exposed-modules" Bool -> Bool -> Bool
|| FieldName
n forall a. Eq a => a -> a -> Bool
== FieldName
"other-modules" = forall (m :: * -> *).
Monad m =>
[Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))]
-> Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))
combine
[ FieldRefactoring
refactoringFragments
, FieldRefactoring
refactoringExpandExposedModules
] Field CommentsPragmas
f
| FieldName
n forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [FieldName]
fileFields = forall (m :: * -> *).
Monad m =>
[Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))]
-> Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))
combine
[ FieldRefactoring
refactoringFragments
, FieldRefactoring
refactoringGlobFiles
] Field CommentsPragmas
f
| Bool
otherwise = forall (m :: * -> *).
Monad m =>
[Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))]
-> Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))
combine
[ FieldRefactoring
refactoringFragments
] Field CommentsPragmas
f
rewrite f :: Field CommentsPragmas
f@(C.Section Name CommentsPragmas
_ [SectionArg CommentsPragmas]
_ [Field CommentsPragmas]
_)
| Bool
otherwise = forall (m :: * -> *).
Monad m =>
[Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))]
-> Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))
combine
[ FieldRefactoring
refactoringFragments
] Field CommentsPragmas
f
combine
:: Monad m
=> [C.Field CommentsPragmas -> m (Maybe (C.Field CommentsPragmas))]
-> C.Field CommentsPragmas -> m (Maybe (C.Field CommentsPragmas))
combine :: forall (m :: * -> *).
Monad m =>
[Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))]
-> Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))
combine [] Field CommentsPragmas
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
combine (Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))
r:[Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))]
rs) Field CommentsPragmas
f = do
Maybe (Field CommentsPragmas)
m <- Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))
r Field CommentsPragmas
f
case Maybe (Field CommentsPragmas)
m of
Maybe (Field CommentsPragmas)
Nothing -> forall (m :: * -> *).
Monad m =>
[Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))]
-> Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))
combine [Field CommentsPragmas -> m (Maybe (Field CommentsPragmas))]
rs Field CommentsPragmas
f
Just Field CommentsPragmas
f' -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just Field CommentsPragmas
f')