Refactor exposed function (now parsePrintModule)

- Rename parsePrintModule -> parsePrintModuleTests
- Rename pureModuleTransform -> parsePrintModule
- Change argument type from (CConfig Option) to Config
- Expose CConfig type fully
pull/35/head
Lennart Spitzner 2017-05-23 00:31:58 +02:00
parent dfec26e55b
commit 3784a0123b
5 changed files with 22 additions and 15 deletions

View File

@ -25,7 +25,7 @@ main = hspec $ do
, " , 00000000000000000000000" , " , 00000000000000000000000"
, " ]" , " ]"
] ]
output <- liftIO $ pureModuleTransform mempty input output <- liftIO $ parsePrintModule staticDefaultConfig input
input `shouldSatisfy` \_ -> case output of input `shouldSatisfy` \_ -> case output of
Right x | x == expected -> True Right x | x == expected -> True
_ -> False _ -> False

View File

@ -131,7 +131,7 @@ main = do
roundTripEqual :: Text -> Expectation roundTripEqual :: Text -> Expectation
roundTripEqual t = roundTripEqual t =
fmap (fmap PPTextWrapper) fmap (fmap PPTextWrapper)
(parsePrintModule defaultTestConfig "TestFakeFileName.hs" t) (parsePrintModuleTests defaultTestConfig "TestFakeFileName.hs" t)
`shouldReturn` Right (PPTextWrapper t) `shouldReturn` Right (PPTextWrapper t)
newtype PPTextWrapper = PPTextWrapper Text newtype PPTextWrapper = PPTextWrapper Text

View File

@ -23,7 +23,7 @@ import Data.Coerce ( coerce )
roundTripEqual :: Text -> Expectation roundTripEqual :: Text -> Expectation
roundTripEqual t = roundTripEqual t =
fmap (fmap PPTextWrapper) fmap (fmap PPTextWrapper)
(parsePrintModule defaultTestConfig "TestFakeFileName.hs" t) (parsePrintModuleTests defaultTestConfig "TestFakeFileName.hs" t)
`shouldReturn` Right (PPTextWrapper t) `shouldReturn` Right (PPTextWrapper t)
roundTripEqualWithTimeout :: Int -> Text -> Expectation roundTripEqualWithTimeout :: Int -> Text -> Expectation
@ -31,7 +31,7 @@ roundTripEqualWithTimeout time t =
timeout time (action >>= evaluate) >>= (`shouldSatisfy`Data.Maybe.isJust) timeout time (action >>= evaluate) >>= (`shouldSatisfy`Data.Maybe.isJust)
where where
action = fmap (fmap PPTextWrapper) action = fmap (fmap PPTextWrapper)
(parsePrintModule defaultTestConfig "TestFakeFileName.hs" t) (parsePrintModuleTests defaultTestConfig "TestFakeFileName.hs" t)
newtype PPTextWrapper = PPTextWrapper Text newtype PPTextWrapper = PPTextWrapper Text
deriving Eq deriving Eq

View File

@ -1,8 +1,15 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
module Language.Haskell.Brittany module Language.Haskell.Brittany
( pureModuleTransform ( parsePrintModule
, CConfig , staticDefaultConfig
, Config
, CConfig(..)
, CDebugConfig(..)
, CLayoutConfig(..)
, CErrorHandlingConfig(..)
, CForwardOptions(..)
, CPreProcessorConfig(..)
, BrittanyError(..) , BrittanyError(..)
) )
where where

View File

@ -1,8 +1,8 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
module Language.Haskell.Brittany.Internal module Language.Haskell.Brittany.Internal
( pureModuleTransform ( parsePrintModule
, parsePrintModule , parsePrintModuleTests
, pPrintModule , pPrintModule
, pPrintModuleAndCheck , pPrintModuleAndCheck
-- re-export from utils: -- re-export from utils:
@ -60,9 +60,8 @@ import qualified GHC.LanguageExtensions.Type as GHC
-- --
-- Note that this function ignores/resets all config values regarding -- Note that this function ignores/resets all config values regarding
-- debugging, i.e. it will never use `trace`/write to stderr. -- debugging, i.e. it will never use `trace`/write to stderr.
pureModuleTransform :: CConfig Option -> Text -> IO (Either [BrittanyError] Text) parsePrintModule :: Config -> Text -> IO (Either [BrittanyError] Text)
pureModuleTransform oConfigRaw inputText = runEitherT $ do parsePrintModule configRaw inputText = runEitherT $ do
let configRaw = cZipWith fromOptionIdentity staticDefaultConfig oConfigRaw
let config = configRaw { _conf_debug = _conf_debug staticDefaultConfig } let config = configRaw { _conf_debug = _conf_debug staticDefaultConfig }
let ghcOptions = config & _conf_forward & _options_ghc & runIdentity let ghcOptions = config & _conf_forward & _options_ghc & runIdentity
let config_pp = config & _conf_preprocessor let config_pp = config & _conf_preprocessor
@ -173,8 +172,9 @@ pPrintModuleAndCheck conf anns parsedModule = do
-- used for testing mostly, currently. -- used for testing mostly, currently.
parsePrintModule :: Config -> String -> Text -> IO (Either String Text) -- TODO: use parsePrintModule instead and remove this function.
parsePrintModule conf filename input = do parsePrintModuleTests :: Config -> String -> Text -> IO (Either String Text)
parsePrintModuleTests conf filename input = do
let inputStr = Text.unpack input let inputStr = Text.unpack input
parseResult <- ExactPrint.Parsers.parseModuleFromString filename inputStr parseResult <- ExactPrint.Parsers.parseModuleFromString filename inputStr
case parseResult of case parseResult of
@ -204,8 +204,8 @@ parsePrintModule conf filename input = do
-- Unfortunately that does not exist yet, so we cannot provide a nominally -- Unfortunately that does not exist yet, so we cannot provide a nominally
-- pure interface. -- pure interface.
-- parsePrintModule :: Text -> Either String Text -- parsePrintModuleTests :: Text -> Either String Text
-- parsePrintModule input = do -- parsePrintModuleTests input = do
-- let dflags = GHC.unsafeGlobalDynFlags -- let dflags = GHC.unsafeGlobalDynFlags
-- let fakeFileName = "SomeTestFakeFileName.hs" -- let fakeFileName = "SomeTestFakeFileName.hs"
-- let pragmaInfo = GHC.getOptions -- let pragmaInfo = GHC.getOptions