{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}

module Test.Syd.Yesod.Def
  ( yesodSpec,
    yesodSpecWithSiteGenerator,
    yesodSpecWithSiteGeneratorAndArgument,
    yesodSpecWithSiteSupplier,
    yesodSpecWithSiteSupplierWith,
    yesodSpecWithSiteSetupFunc,
    yesodSpecWithSiteSetupFunc',
    yesodClientSetupFunc,
    YesodSpec,
    yit,
    ydescribe,
  )
where

import GHC.Stack
import Network.HTTP.Client as HTTP
import Test.Syd
import Test.Syd.Wai
import Test.Syd.Yesod.Client
import Yesod.Core as Yesod

-- | Run a test suite using the given 'site'.
--
-- If your 'site' contains any resources that need to be set up, you probably want to be using one of the following functions instead.
--
-- Example usage with a minimal yesod 'App':
--
-- > {-# LANGUAGE MultiParamTypeClasses #-}
-- > {-# LANGUAGE OverloadedStrings     #-}
-- > {-# LANGUAGE QuasiQuotes           #-}
-- > {-# LANGUAGE TemplateHaskell       #-}
-- > {-# LANGUAGE TypeFamilies          #-}
-- >
-- > module Minimal where
-- >
-- > import Yesod
-- > import Test.Syd
-- >
-- > data App = App -- | Empty App type
-- >
-- > mkYesod "App" [parseRoutes|
-- >     / HomeR GET
-- > |]
-- >
-- > instance Yesod App
-- >
-- > getHomeR :: Handler Html
-- > getHomeR = "Hello, world!"
-- >
-- > main :: IO ()
-- > main = Yesod.warp 3000 App
-- >
-- > testMain :: IO ()
-- > testMain = sydTest spec
-- >
-- > spec :: Spec
-- > spec = yesodSpec App $ do
-- >   it "returns 200 on the homepage" $ do
-- >     get HomeR
-- >     statusIs 200
--
-- This function exists for backward compatibility with yesod-test.
yesodSpec :: YesodDispatch site => site -> YesodSpec site -> Spec
yesodSpec :: site -> YesodSpec site -> Spec
yesodSpec site
site = IO site -> YesodSpec site -> Spec
forall site.
YesodDispatch site =>
IO site -> YesodSpec site -> Spec
yesodSpecWithSiteGenerator (IO site -> YesodSpec site -> Spec)
-> IO site -> YesodSpec site -> Spec
forall a b. (a -> b) -> a -> b
$ site -> IO site
forall (f :: * -> *) a. Applicative f => a -> f a
pure site
site

-- | Run a test suite using the given 'site' generator.
--
-- If your 'site' contains any resources that you will want to have set up beforhand, you will probably want to use 'yesodSpecWithSiteGeneratorAndArgument' or 'yesodSpecWithSiteSupplierWith' instead.
--
--
-- Example usage with a yesod 'App' that contains a secret key that is generated at startup but not used during tests:
--
-- > data Key = Key -- The implementation of the actual key is omitted here for brevity.
-- > genKey :: IO Key
-- > genKey = pure Key
-- >
-- > data App = App { appSecretKey :: Key }
-- >
-- > genApp :: IO App
-- > genApp = App <$> genKey
-- >
-- > main :: IO ()
-- > main = sydTest spec
-- >
-- > spec :: Spec
-- > spec = yesodSpecWithSiteGenerator genApp $ do
-- >   it "returns 200 on the homepage" $ do
-- >     get HomeR
-- >     statusIs 200
--
-- This function exists for backward compatibility with yesod-test.
yesodSpecWithSiteGenerator :: YesodDispatch site => IO site -> YesodSpec site -> Spec
yesodSpecWithSiteGenerator :: IO site -> YesodSpec site -> Spec
yesodSpecWithSiteGenerator IO site
siteGen = (() -> IO site) -> YesodSpec site -> Spec
forall site a.
YesodDispatch site =>
(a -> IO site) -> YesodSpec site -> SpecWith a
yesodSpecWithSiteGeneratorAndArgument ((() -> IO site) -> YesodSpec site -> Spec)
-> (() -> IO site) -> YesodSpec site -> Spec
forall a b. (a -> b) -> a -> b
$ \() -> IO site
siteGen

-- | Run a test suite using the given 'site' generator which uses an inner resource.
--
-- If your 'site' contains any resources that you need to set up using a 'withX' function, you will want to use `yesodSpecWithSiteSupplier` instead.
--
-- This function exists for backward compatibility with yesod-test.
yesodSpecWithSiteGeneratorAndArgument :: YesodDispatch site => (a -> IO site) -> YesodSpec site -> SpecWith a
yesodSpecWithSiteGeneratorAndArgument :: (a -> IO site) -> YesodSpec site -> SpecWith a
yesodSpecWithSiteGeneratorAndArgument a -> IO site
func = (forall r. (site -> IO r) -> a -> IO r)
-> YesodSpec site -> SpecWith a
forall site a.
YesodDispatch site =>
(forall r. (site -> IO r) -> a -> IO r)
-> YesodSpec site -> SpecWith a
yesodSpecWithSiteSupplierWith ((forall r. (site -> IO r) -> a -> IO r)
 -> YesodSpec site -> SpecWith a)
-> (forall r. (site -> IO r) -> a -> IO r)
-> YesodSpec site
-> SpecWith a
forall a b. (a -> b) -> a -> b
$ \site -> IO r
f a
a -> a -> IO site
func a
a IO site -> (site -> IO r) -> IO r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= site -> IO r
f

-- | Using a function that supplies a 'site', run a test suite.
--
-- Example usage with a yesod 'App' that contains an sqlite database connection. See 'sydtest-persistent-sqlite'.
--
-- > import Test.Syd.Persistent.Sqlite
-- >
-- > data App = App { appConnectionPool :: ConnectionPool }
-- >
-- > main :: IO ()
-- > main = sydTest spec
-- >
-- > appSupplier :: (App -> IO r) -> IO r
-- > appSupplier func =
-- >   withConnectionPool myMigration $ \pool ->
-- >     func $ App { appConnectionPool = pool}
-- >
-- > spec :: Spec
-- > spec = yesodSpecWithSiteSupplier appSupplier $ do
-- >   it "returns 200 on the homepage" $ do
-- >     get HomeR
-- >     statusIs 200
yesodSpecWithSiteSupplier :: YesodDispatch site => (forall r. (site -> IO r) -> IO r) -> YesodSpec site -> Spec
yesodSpecWithSiteSupplier :: (forall r. (site -> IO r) -> IO r) -> YesodSpec site -> Spec
yesodSpecWithSiteSupplier forall r. (site -> IO r) -> IO r
func = (forall r. (site -> IO r) -> () -> IO r) -> YesodSpec site -> Spec
forall site a.
YesodDispatch site =>
(forall r. (site -> IO r) -> a -> IO r)
-> YesodSpec site -> SpecWith a
yesodSpecWithSiteSupplierWith (\site -> IO r
f () -> (site -> IO r) -> IO r
forall r. (site -> IO r) -> IO r
func site -> IO r
f)

-- | Using a function that supplies a 'site', based on an inner resource, run a test suite.
yesodSpecWithSiteSupplierWith :: YesodDispatch site => (forall r. (site -> IO r) -> (a -> IO r)) -> YesodSpec site -> SpecWith a
yesodSpecWithSiteSupplierWith :: (forall r. (site -> IO r) -> a -> IO r)
-> YesodSpec site -> SpecWith a
yesodSpecWithSiteSupplierWith forall r. (site -> IO r) -> a -> IO r
func = (Manager -> SetupFunc a site) -> YesodSpec site -> SpecWith a
forall site a (l :: [*]).
YesodDispatch site =>
(Manager -> SetupFunc a site)
-> TestDef (Manager : l) (YesodClient site) -> TestDef l a
yesodSpecWithSiteSetupFunc ((Manager -> SetupFunc a site) -> YesodSpec site -> SpecWith a)
-> (Manager -> SetupFunc a site) -> YesodSpec site -> SpecWith a
forall a b. (a -> b) -> a -> b
$ \Manager
_ -> (forall r. (site -> IO r) -> a -> IO r) -> SetupFunc a site
forall old new.
(forall r. (new -> IO r) -> old -> IO r) -> SetupFunc old new
SetupFunc forall r. (site -> IO r) -> a -> IO r
func

-- | Using a function that supplies a 'site', using a 'SetupFunc'
yesodSpecWithSiteSetupFunc :: YesodDispatch site => (HTTP.Manager -> SetupFunc a site) -> TestDef (HTTP.Manager ': l) (YesodClient site) -> TestDef l a
yesodSpecWithSiteSetupFunc :: (Manager -> SetupFunc a site)
-> TestDef (Manager : l) (YesodClient site) -> TestDef l a
yesodSpecWithSiteSetupFunc Manager -> SetupFunc a site
setupFunc = TestDef (Manager : l) a -> TestDef l a
forall (l :: [*]) a. TestDef (Manager : l) a -> TestDef l a
managerSpec (TestDef (Manager : l) a -> TestDef l a)
-> (TestDef (Manager : l) (YesodClient site)
    -> TestDef (Manager : l) a)
-> TestDef (Manager : l) (YesodClient site)
-> TestDef l a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Manager -> SetupFunc a site)
-> TestDef (Manager : l) (YesodClient site)
-> TestDef (Manager : l) a
forall site a (l :: [*]).
YesodDispatch site =>
(Manager -> SetupFunc a site)
-> TestDef (Manager : l) (YesodClient site)
-> TestDef (Manager : l) a
yesodSpecWithSiteSetupFunc' Manager -> SetupFunc a site
setupFunc

-- | Using a function that supplies a 'site', using a 'SetupFunc' but without setting up the 'HTTP.Manager' beforehand.
--
-- This function assumed that you've already set up the 'HTTP.Manager' beforehand using something like 'managerSpec'.
yesodSpecWithSiteSetupFunc' :: YesodDispatch site => (HTTP.Manager -> SetupFunc a site) -> TestDef (HTTP.Manager ': l) (YesodClient site) -> TestDef (HTTP.Manager ': l) a
yesodSpecWithSiteSetupFunc' :: (Manager -> SetupFunc a site)
-> TestDef (Manager : l) (YesodClient site)
-> TestDef (Manager : l) a
yesodSpecWithSiteSetupFunc' Manager -> SetupFunc a site
setupFunc = (Manager -> SetupFunc a (YesodClient site))
-> TestDef (Manager : l) (YesodClient site)
-> TestDef (Manager : l) a
forall (outers :: [*]) outer oldInner newInner result.
HContains outers outer =>
(outer -> SetupFunc oldInner newInner)
-> TestDefM outers newInner result
-> TestDefM outers oldInner result
setupAroundWith' (\Manager
man -> Manager -> SetupFunc a site
setupFunc Manager
man SetupFunc a site
-> SetupFunc site (YesodClient site)
-> SetupFunc a (YesodClient site)
forall old newer newest.
SetupFunc old newer
-> SetupFunc newer newest -> SetupFunc old newest
`connectSetupFunc` Manager -> SetupFunc site (YesodClient site)
forall site.
YesodDispatch site =>
Manager -> SetupFunc site (YesodClient site)
yesodClientSetupFunc Manager
man)

yesodClientSetupFunc :: YesodDispatch site => HTTP.Manager -> SetupFunc site (YesodClient site)
yesodClientSetupFunc :: Manager -> SetupFunc site (YesodClient site)
yesodClientSetupFunc Manager
man = (site -> SetupFunc () (YesodClient site))
-> SetupFunc site (YesodClient site)
forall old new. (old -> SetupFunc () new) -> SetupFunc old new
wrapSetupFunc ((site -> SetupFunc () (YesodClient site))
 -> SetupFunc site (YesodClient site))
-> (site -> SetupFunc () (YesodClient site))
-> SetupFunc site (YesodClient site)
forall a b. (a -> b) -> a -> b
$ \site
site -> do
  Application
application <- IO Application -> SetupFunc () Application
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Application -> SetupFunc () Application)
-> IO Application -> SetupFunc () Application
forall a b. (a -> b) -> a -> b
$ site -> IO Application
forall site. YesodDispatch site => site -> IO Application
Yesod.toWaiAppPlain site
site
  Port
p <- SetupFunc Application Port -> Application -> SetupFunc () Port
forall old new. SetupFunc old new -> old -> SetupFunc () new
unwrapSetupFunc SetupFunc Application Port
applicationSetupFunc Application
application
  let client :: YesodClient site
client =
        YesodClient :: forall site. site -> Manager -> Port -> YesodClient site
YesodClient
          { yesodClientManager :: Manager
yesodClientManager = Manager
man,
            yesodClientSite :: site
yesodClientSite = site
site,
            yesodClientSitePort :: Port
yesodClientSitePort = Port
p
          }
  YesodClient site -> SetupFunc () (YesodClient site)
forall (f :: * -> *) a. Applicative f => a -> f a
pure YesodClient site
client

-- | For backward compatibility with yesod-test
type YesodSpec site = TestDef '[HTTP.Manager] (YesodClient site)

-- | Define a test in the 'YesodClientM site' monad instead of 'IO'.
yit ::
  forall site e.
  ( HasCallStack,
    IsTest (YesodClient site -> IO e),
    Arg1 (YesodClient site -> IO e) ~ (),
    Arg2 (YesodClient site -> IO e) ~ YesodClient site
  ) =>
  String ->
  YesodClientM site e ->
  YesodSpec site
yit :: String -> YesodClientM site e -> YesodSpec site
yit String
s YesodClientM site e
f = String -> (YesodClient site -> IO e) -> YesodSpec site
forall (outers :: [*]) inner test.
(HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) =>
String -> test -> TestDefM outers inner ()
it String
s ((\YesodClient site
cenv -> YesodClient site -> YesodClientM site e -> IO e
forall site a. YesodClient site -> YesodClientM site a -> IO a
runYesodClientM YesodClient site
cenv YesodClientM site e
f) :: YesodClient site -> IO e)

-- | For backward compatibility
--
-- > ydescribe = describe
ydescribe :: String -> YesodSpec site -> YesodSpec site
ydescribe :: String -> YesodSpec site -> YesodSpec site
ydescribe = String -> YesodSpec site -> YesodSpec site
forall (outers :: [*]) inner.
String -> TestDefM outers inner () -> TestDefM outers inner ()
describe