177 lines
6.8 KiB
Haskell
177 lines
6.8 KiB
Haskell
{-# LANGUAGE NoImplicitPrelude #-}
|
|
|
|
module Language.Haskell.Brittany.Internal.Config.InlineParsing
|
|
( extractCommentConfigs
|
|
)
|
|
where
|
|
|
|
import Language.Haskell.Brittany.Internal.Prelude
|
|
|
|
import qualified Data.ByteString.Char8
|
|
import Data.Char ( isSpace )
|
|
import qualified Data.Map as Map
|
|
import qualified Data.Yaml
|
|
import qualified GHC
|
|
import GHC ( EpaComment(EpaComment)
|
|
, GenLocated(L)
|
|
)
|
|
import qualified GHC.OldList as List
|
|
import GHC.Parser.Annotation ( EpaCommentTok
|
|
( EpaBlockComment
|
|
, EpaLineComment
|
|
)
|
|
)
|
|
import qualified UI.Butcher.Monadic as Butcher
|
|
import Control.Monad.Trans.Except
|
|
|
|
import Language.Haskell.Brittany.Internal.Config.Config
|
|
import Language.Haskell.Brittany.Internal.Config.Types
|
|
import Language.Haskell.Brittany.Internal.Types
|
|
import Language.Haskell.Brittany.Internal.Config.Types.Instances1 ()
|
|
import Language.Haskell.Brittany.Internal.Config.Types.Instances2 ()
|
|
-- import Language.Haskell.Brittany.Internal.Utils
|
|
-- import qualified Language.Haskell.GHC.ExactPrint.Utils as ExactPrint.Utils
|
|
-- import Data.Data(toConstr)
|
|
|
|
|
|
|
|
data InlineConfigTarget
|
|
= InlineConfigTargetModule
|
|
| InlineConfigTargetNextDecl -- really only next in module
|
|
| InlineConfigTargetNextBinding -- by name
|
|
| InlineConfigTargetBinding String
|
|
deriving Show
|
|
|
|
extractCommentConfigs
|
|
:: (String -> IO ())
|
|
-> Map GHC.RealSrcSpan [String]
|
|
-> FinalList ModuleElement a
|
|
-> ExceptT (String, String) IO (CConfig Maybe, PerItemConfig)
|
|
extractCommentConfigs _putErrorLn declMap moduleElementList = do
|
|
let comments = concatMapFinal (void moduleElementList) $ \case
|
|
MEExactModuleHead modul -> case GHC.hsmodAnn $ GHC.unLoc modul of
|
|
GHC.EpAnn _ _ (GHC.EpaComments prior) -> prior
|
|
GHC.EpAnn _ _ (GHC.EpaCommentsBalanced prior following) ->
|
|
prior ++ following
|
|
GHC.EpAnnNotUsed -> []
|
|
MEPrettyModuleHead{} -> []
|
|
MEImportDecl{} -> []
|
|
MEDecl{} -> []
|
|
MEComment (_, comment) -> [comment]
|
|
MEWhitespace{} -> []
|
|
lineConfigs <- sequence
|
|
[ case Butcher.runCmdParserSimpleString line2 parser of
|
|
Left err -> throwE (err, line2)
|
|
Right (target, conf) -> pure $ (GHC.anchor anchr, target, conf)
|
|
| L anchr (EpaComment comm _) <- comments
|
|
, Just line1 <- case comm of
|
|
EpaLineComment l ->
|
|
[ List.stripPrefix "-- BRITTANY" l
|
|
<|> List.stripPrefix "--BRITTANY" l
|
|
<|> List.stripPrefix "-- brittany" l
|
|
<|> List.stripPrefix "--brittany" l
|
|
]
|
|
EpaBlockComment l ->
|
|
[List.stripPrefix "{- BRITTANY" l >>= stripSuffix "-}"]
|
|
_ -> []
|
|
, let line2 = dropWhile isSpace line1
|
|
, ( ("@" `isPrefixOf` line2)
|
|
|| ("-disable" `isPrefixOf` line2)
|
|
|| ("-next" `isPrefixOf` line2)
|
|
|| ("{" `isPrefixOf` line2)
|
|
|| ("--" `isPrefixOf` line2)
|
|
)
|
|
]
|
|
let perModule = foldl'
|
|
(<>)
|
|
mempty
|
|
[ conf | (_, InlineConfigTargetModule, conf) <- lineConfigs ]
|
|
let perBinding = Map.fromListWith
|
|
(<>)
|
|
[ (n, conf)
|
|
| (srcSpan, target, conf) <- lineConfigs
|
|
, let perBindRes = Map.lookupGT srcSpan declMap
|
|
, n <- case target of
|
|
InlineConfigTargetBinding s -> [s]
|
|
InlineConfigTargetNextBinding | Just (_, names) <- perBindRes -> names
|
|
_ -> []
|
|
]
|
|
let perSpan = Map.fromListWith
|
|
(<>)
|
|
[ (declSpan, conf)
|
|
| (srcSpan, target, conf) <- lineConfigs
|
|
, Just (declSpan, names) <- [Map.lookupGT srcSpan declMap]
|
|
, case target of
|
|
InlineConfigTargetNextDecl -> True
|
|
InlineConfigTargetNextBinding -> null names
|
|
_ -> False
|
|
]
|
|
|
|
pure
|
|
$ ( perModule
|
|
, PerItemConfig { _icd_perBinding = perBinding, _icd_perAnchor = perSpan }
|
|
)
|
|
where
|
|
configParser = Butcher.addAlternatives
|
|
[ ( "commandline-config"
|
|
, \s -> "-" `isPrefixOf` dropWhile (== ' ') s
|
|
, cmdlineConfigParser
|
|
)
|
|
, ( "yaml-config-document"
|
|
, \s -> "{" `isPrefixOf` dropWhile (== ' ') s
|
|
, Butcher.addCmdPart (Butcher.varPartDesc "yaml-config-document")
|
|
$ either
|
|
(\_ -> Butcher.Failure Nothing)
|
|
(\lconf -> Butcher.Success (mempty { _conf_layout = lconf }) "")
|
|
. Data.Yaml.decodeEither'
|
|
. Data.ByteString.Char8.pack
|
|
-- TODO: use some proper utf8 encoder instead?
|
|
)
|
|
]
|
|
parser = do -- we will (mis?)use butcher here to parse the inline config
|
|
-- line.
|
|
let nextDecl = do
|
|
conf <- configParser
|
|
Butcher.addCmdImpl (InlineConfigTargetNextDecl, conf)
|
|
Butcher.addCmd "-next-declaration" nextDecl
|
|
Butcher.addCmd "-Next-Declaration" nextDecl
|
|
Butcher.addCmd "-NEXT-DECLARATION" nextDecl
|
|
let nextBinding = do
|
|
conf <- configParser
|
|
Butcher.addCmdImpl (InlineConfigTargetNextBinding, conf)
|
|
Butcher.addCmd "-next-binding" nextBinding
|
|
Butcher.addCmd "-Next-Binding" nextBinding
|
|
Butcher.addCmd "-NEXT-BINDING" nextBinding
|
|
let disableNextBinding = do
|
|
Butcher.addCmdImpl
|
|
( InlineConfigTargetNextBinding
|
|
, mempty { _conf_roundtrip_exactprint_only = pure $ pure True }
|
|
)
|
|
Butcher.addCmd "-disable-next-binding" disableNextBinding
|
|
Butcher.addCmd "-Disable-Next-Binding" disableNextBinding
|
|
Butcher.addCmd "-DISABLE-NEXT-BINDING" disableNextBinding
|
|
let disableNextDecl = do
|
|
Butcher.addCmdImpl
|
|
( InlineConfigTargetNextDecl
|
|
, mempty { _conf_roundtrip_exactprint_only = pure $ pure True }
|
|
)
|
|
Butcher.addCmd "-disable-next-declaration" disableNextDecl
|
|
Butcher.addCmd "-Disable-Next-Declaration" disableNextDecl
|
|
Butcher.addCmd "-DISABLE-NEXT-DECLARATION" disableNextDecl
|
|
let disableFormatting = do
|
|
Butcher.addCmdImpl
|
|
( InlineConfigTargetModule
|
|
, mempty { _conf_disable_formatting = pure $ pure True }
|
|
)
|
|
Butcher.addCmd "-disable" disableFormatting
|
|
Butcher.addCmd "@" $ do
|
|
-- Butcher.addCmd "module" $ do
|
|
-- conf <- configParser
|
|
-- Butcher.addCmdImpl (InlineConfigTargetModule, conf)
|
|
Butcher.addNullCmd $ do
|
|
bindingName <- Butcher.addParamString "BINDING" mempty
|
|
conf <- configParser
|
|
Butcher.addCmdImpl (InlineConfigTargetBinding bindingName, conf)
|
|
conf <- configParser
|
|
Butcher.addCmdImpl (InlineConfigTargetModule, conf)
|