module Shaker.Action.Test
 where

import Shaker.Type
import Shaker.Reflexivite
import Control.Monad.Reader
import Language.Haskell.TH

runTestFramework :: Plugin 
runTestFramework = collectAllModulesForTest >>= getModulesWithFunctionFiltering  >>= runTestFramework'

runIntelligentTestFramework :: Plugin
runIntelligentTestFramework = collectChangedModulesForTest >>= getModulesWithFunctionFiltering >>= runTestFramework'

runModuleTestFramework :: Plugin 
runModuleTestFramework = collectAllModulesForTest >>= getModulesWithModuleFiltering >>= runTestFramework' 

runModuleIntelligentTestFramework :: Plugin
runModuleIntelligentTestFramework = collectChangedModulesForTest >>= getModulesWithModuleFiltering >>= runTestFramework'

getModulesWithModuleFiltering :: [ModuleMapping] -> Shaker IO ( [ModuleMapping] )
getModulesWithModuleFiltering module_list = asks argument >>= return . process
  where process [] = module_list
        process list = concatMap (filterModulesWithPattern module_list) list

getModulesWithFunctionFiltering :: [ModuleMapping] -> Shaker IO ([ModuleMapping] ) 
getModulesWithFunctionFiltering module_list = asks argument >>= 
  return . removeNonTestModule . filterFunctionsWithPatterns module_list

runTestFramework' :: [ModuleMapping] -> Plugin
runTestFramework' modules = do
  let import_modules = base_modules ++ map cfModuleName modules
  resolvedExp <- lift $ runQ (listTestFrameworkGroupList modules)
  let function =  filter (/= '\n') $ pprint resolvedExp
  lift $ putStrLn function
  runFunction $ RunnableFunction import_modules ("defaultMain $ " ++ function) 
  return () 
  where base_modules =["Data.Maybe","Shaker.SourceHelper","Test.Framework", "Test.Framework.Providers.HUnit", "Test.Framework.Providers.QuickCheck2", "Test.QuickCheck", "Test.HUnit", "Prelude" ]