{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RecordWildCards #-} module Test.Hspec.Core.Runner.PrintSlowSpecItems ( printSlowSpecItems ) where import Prelude () import Test.Hspec.Core.Compat import Test.Hspec.Core.Util import Test.Hspec.Core.Format import Test.Hspec.Core.Clock import Test.Hspec.Core.Formatters.V2 (formatLocation) data SlowItem = SlowItem { SlowItem -> Maybe Location location :: Maybe Location , SlowItem -> Path path :: Path , SlowItem -> Int duration :: Int } printSlowSpecItems :: Int -> Format -> Format printSlowSpecItems :: Int -> Format -> Format printSlowSpecItems Int n Format format Event event = do Format format Event event case Event event of Done [(Path, Item)] items -> do let xs :: [SlowItem] xs = Int -> [SlowItem] -> [SlowItem] slowItems Int n ([SlowItem] -> [SlowItem]) -> [SlowItem] -> [SlowItem] forall a b. (a -> b) -> a -> b $ ((Path, Item) -> SlowItem) -> [(Path, Item)] -> [SlowItem] forall a b. (a -> b) -> [a] -> [b] map (Path, Item) -> SlowItem toSlowItem [(Path, Item)] items Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless ([SlowItem] -> Bool forall (t :: * -> *) a. Foldable t => t a -> Bool null [SlowItem] xs) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ do String -> IO () putStrLn String "\nSlow spec items:" (SlowItem -> IO ()) -> [SlowItem] -> IO () forall (t :: * -> *) (m :: * -> *) a b. (Foldable t, Monad m) => (a -> m b) -> t a -> m () mapM_ SlowItem -> IO () printSlowSpecItem [SlowItem] xs Event _ -> () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () toSlowItem :: (Path, Item) -> SlowItem toSlowItem :: (Path, Item) -> SlowItem toSlowItem (Path path, Item item) = Maybe Location -> Path -> Int -> SlowItem SlowItem (Item -> Maybe Location itemLocation Item item) Path path (Seconds -> Int toMilliseconds (Seconds -> Int) -> Seconds -> Int forall a b. (a -> b) -> a -> b $ Item -> Seconds itemDuration Item item) slowItems :: Int -> [SlowItem] -> [SlowItem] slowItems :: Int -> [SlowItem] -> [SlowItem] slowItems Int n = Int -> [SlowItem] -> [SlowItem] forall a. Int -> [a] -> [a] take Int n ([SlowItem] -> [SlowItem]) -> ([SlowItem] -> [SlowItem]) -> [SlowItem] -> [SlowItem] forall b c a. (b -> c) -> (a -> b) -> a -> c . [SlowItem] -> [SlowItem] forall a. [a] -> [a] reverse ([SlowItem] -> [SlowItem]) -> ([SlowItem] -> [SlowItem]) -> [SlowItem] -> [SlowItem] forall b c a. (b -> c) -> (a -> b) -> a -> c . (SlowItem -> Int) -> [SlowItem] -> [SlowItem] forall b a. Ord b => (a -> b) -> [a] -> [a] sortOn SlowItem -> Int duration ([SlowItem] -> [SlowItem]) -> ([SlowItem] -> [SlowItem]) -> [SlowItem] -> [SlowItem] forall b c a. (b -> c) -> (a -> b) -> a -> c . (SlowItem -> Bool) -> [SlowItem] -> [SlowItem] forall a. (a -> Bool) -> [a] -> [a] filter ((Int -> Int -> Bool forall a. Eq a => a -> a -> Bool /= Int 0) (Int -> Bool) -> (SlowItem -> Int) -> SlowItem -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c . SlowItem -> Int duration) printSlowSpecItem :: SlowItem -> IO () printSlowSpecItem :: SlowItem -> IO () printSlowSpecItem SlowItem{Int Maybe Location Path duration :: Int path :: Path location :: Maybe Location duration :: SlowItem -> Int path :: SlowItem -> Path location :: SlowItem -> Maybe Location ..} = do String -> IO () putStrLn (String -> IO ()) -> String -> IO () forall a b. (a -> b) -> a -> b $ String " " String -> String -> String forall a. [a] -> [a] -> [a] ++ String -> (Location -> String) -> Maybe Location -> String forall b a. b -> (a -> b) -> Maybe a -> b maybe String "" Location -> String formatLocation Maybe Location location String -> String -> String forall a. [a] -> [a] -> [a] ++ Path -> String joinPath Path path String -> String -> String forall a. [a] -> [a] -> [a] ++ String " (" String -> String -> String forall a. [a] -> [a] -> [a] ++ Int -> String forall a. Show a => a -> String show Int duration String -> String -> String forall a. [a] -> [a] -> [a] ++ String "ms)"