{-# LANGUAGE TupleSections, RecordWildCards, ScopedTypeVariables #-} module Action.Test(actionTest) where import Query import Action.CmdLine import Action.Search import Action.Server import Action.Generate import General.Util import General.Web import Input.Item import Input.Haddock import System.IO.Extra import Control.Monad import Output.Items import Control.DeepSeq import Control.Exception actionTest :: CmdLine -> IO () actionTest :: CmdLine -> IO () actionTest Test{Bool FilePath Language disable_network_tests :: CmdLine -> Bool deep :: CmdLine -> Bool language :: CmdLine -> Language database :: CmdLine -> FilePath language :: Language database :: FilePath disable_network_tests :: Bool deep :: Bool ..} = Handle -> BufferMode -> IO () -> IO () forall a. Handle -> BufferMode -> IO a -> IO a withBuffering Handle stdout BufferMode NoBuffering (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ (FilePath -> IO ()) -> IO () forall a. (FilePath -> IO a) -> IO a withTempFile ((FilePath -> IO ()) -> IO ()) -> (FilePath -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $ \FilePath sample -> do FilePath -> IO () putStrLn FilePath "Code tests" IO () general_util_test IO () general_web_test IO () input_haddock_test IO () query_test IO () action_server_test_ IO () item_test FilePath -> IO () putStrLn FilePath "" FilePath -> IO () putStrLn FilePath "Sample database tests" CmdLine -> IO () actionGenerate CmdLine defaultGenerate{database :: FilePath database=FilePath sample, local_ :: [FilePath] local_=[FilePath "misc/sample-data"]} Bool -> FilePath -> IO () action_search_test Bool True FilePath sample Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless Bool disable_network_tests (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ Bool -> FilePath -> IO () action_server_test Bool True FilePath sample FilePath -> IO () putStrLn FilePath "" Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless Bool disable_network_tests (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ do FilePath -> IO () putStrLn FilePath "Haskell.org database tests" Bool -> FilePath -> IO () action_search_test Bool False FilePath database Bool -> FilePath -> IO () action_server_test Bool False FilePath database Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () when Bool deep (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ FilePath -> (StoreRead -> IO ()) -> IO () forall a. NFData a => FilePath -> (StoreRead -> IO a) -> IO a withSearch FilePath database ((StoreRead -> IO ()) -> IO ()) -> (StoreRead -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $ \StoreRead store -> do FilePath -> IO () putStrLn FilePath "Deep tests" let xs :: [FilePath] xs = (Target -> FilePath) -> [Target] -> [FilePath] forall a b. (a -> b) -> [a] -> [b] map Target -> FilePath targetItem ([Target] -> [FilePath]) -> [Target] -> [FilePath] forall a b. (a -> b) -> a -> b $ StoreRead -> [Target] listItems StoreRead store () -> IO () forall a. a -> IO a evaluate (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ [FilePath] -> () forall a. NFData a => a -> () rnf [FilePath] xs FilePath -> IO () putStrLn (FilePath -> IO ()) -> FilePath -> IO () forall a b. (a -> b) -> a -> b $ FilePath "Loaded " FilePath -> FilePath -> FilePath forall a. [a] -> [a] -> [a] ++ Int -> FilePath forall a. Show a => a -> FilePath show ([FilePath] -> Int forall (t :: * -> *) a. Foldable t => t a -> Int length [FilePath] xs) FilePath -> FilePath -> FilePath forall a. [a] -> [a] -> [a] ++ FilePath " items"