module Hix.Managed.Handlers.Report.Test where import Data.IORef (IORef, modifyIORef, newIORef) import Hix.Data.Monad (M) import Hix.Managed.Data.Mutation (FailedMutation) import qualified Hix.Managed.Data.ProjectResult import Hix.Managed.Data.ProjectResult (ProjectResult) import qualified Hix.Managed.EnvResult as EnvResult import Hix.Managed.Handlers.Report (ReportHandlers (..), handlersNull) reportMutationsIORef :: IORef [FailedMutation] -> ProjectResult -> M () reportMutationsIORef :: IORef [FailedMutation] -> ProjectResult -> M () reportMutationsIORef IORef [FailedMutation] out ProjectResult results = IO () -> M () forall a. IO a -> M a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> M ()) -> IO () -> M () forall a b. (a -> b) -> a -> b $ IORef [FailedMutation] -> ([FailedMutation] -> [FailedMutation]) -> IO () forall a. IORef a -> (a -> a) -> IO () modifyIORef IORef [FailedMutation] out \ [FailedMutation] old -> ([FailedMutation] -> [FailedMutation] -> [FailedMutation]) -> [FailedMutation] -> [[FailedMutation]] -> [FailedMutation] forall b a. (b -> a -> b) -> b -> [a] -> b forall (t :: * -> *) b a. Foldable t => (b -> a -> b) -> b -> t a -> b foldl' (([FailedMutation] -> [FailedMutation] -> [FailedMutation]) -> [FailedMutation] -> [FailedMutation] -> [FailedMutation] forall a b c. (a -> b -> c) -> b -> a -> c flip [FailedMutation] -> [FailedMutation] -> [FailedMutation] forall a. [a] -> [a] -> [a] (++)) [FailedMutation] old [[FailedMutation]] failed where failed :: [[FailedMutation]] failed = EnvResult -> [FailedMutation] EnvResult.failures (EnvResult -> [FailedMutation]) -> [EnvResult] -> [[FailedMutation]] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> NonEmpty EnvResult -> [EnvResult] forall a. NonEmpty a -> [a] forall (t :: * -> *) a. Foldable t => t a -> [a] toList ProjectResult results.envs handlersUnitTest :: MonadIO m => m (ReportHandlers, IORef [FailedMutation]) handlersUnitTest :: forall (m :: * -> *). MonadIO m => m (ReportHandlers, IORef [FailedMutation]) handlersUnitTest = do IORef [FailedMutation] mutationsRef <- IO (IORef [FailedMutation]) -> m (IORef [FailedMutation]) forall a. IO a -> m a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO ([FailedMutation] -> IO (IORef [FailedMutation]) forall a. a -> IO (IORef a) newIORef []) pure (ReportHandlers handlersNull {mutations = reportMutationsIORef mutationsRef}, IORef [FailedMutation] mutationsRef)