-- | Description: Support functions for @doctest-driver@.
-- Copyright: Copyright 2024, Ruifeng Xie
-- License: LGPL-3.0-or-later
-- Maintainer: Ruifeng Xie <ruifengx@outlook.com>
--
-- Support functions used by code generated by @doctest-driver@.
module Test.DocTest.Support
  -- NOTE: empty lines are significant
  -- they prevent sections from being joint with previous paragraphs

  -- | Here we demonstrate features of @doctest-driver@. Readers of this documentation are
  -- encouraged to also refer to the source code of this module as an illustration.

  -- * Examples
  -- | @doctest-driver@ supports testing Haddock examples.

  -- ** REPL (Read-Eval-Print-Loop) Style Examples
  -- $REPL-Style-Examples

  -- ** QuickCheck Properties
  -- $QuickCheck-Properties

  -- ** Verbatim Examples
  -- $Verbatim-Examples

  -- ** Verbatim Properties
  -- $Verbatim-Properties

  -- ** Support API
  ( shouldMatch
  , ReplResult
  , ReplAction (..)

  -- * Captures
  -- $Captures
  , withWriteTempFile
  , textStrict
  , textLazy
  , byteStringStrict
  , byteStringLazy
  , shortByteString

  -- * Hooks
  , markUsed
  ) where

import Control.DeepSeq (deepseq)
import Control.Exception (throwIO)
import Control.Monad (unless)
import Data.ByteString (ByteString)
import Data.ByteString.Lazy (LazyByteString, fromStrict)
import Data.ByteString.Short (ShortByteString, toShort)
import Data.CallStack (HasCallStack, SrcLoc, callStack)
import Data.Kind (Type)
import Data.List.NonEmpty (NonEmpty ((:|)))
import Data.List.NonEmpty qualified as N (last)
import Data.Text qualified as T (Text, pack)
import Data.Text.Encoding qualified as T (encodeUtf8)
import Data.Text.Lazy qualified as TL (Text, pack)
import System.IO (hClose, hPutStr, hSetBinaryMode)
import System.IO.Temp (withSystemTempFile)
import Test.DocTest.FuzzyMatch (match)
import Test.DocTest.FuzzySyntax (parsePattern)
import Test.HUnit.Lang (Assertion, FailureReason (..), HUnitFailure (..))

lastMaybe :: [a] -> Maybe a
lastMaybe :: forall a. [a] -> Maybe a
lastMaybe []       = Maybe a
forall a. Maybe a
Nothing
lastMaybe (a
x : [a]
xs) = a -> Maybe a
forall a. a -> Maybe a
Just (NonEmpty a -> a
forall a. NonEmpty a -> a
N.last (a
x a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [a]
xs))

location :: HasCallStack => Maybe SrcLoc
location :: HasCallStack => Maybe SrcLoc
location = (String, SrcLoc) -> SrcLoc
forall a b. (a, b) -> b
snd ((String, SrcLoc) -> SrcLoc)
-> Maybe (String, SrcLoc) -> Maybe SrcLoc
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> [(String, SrcLoc)] -> Maybe (String, SrcLoc)
forall a. [a] -> Maybe a
lastMaybe [(String, SrcLoc)]
HasCallStack => [(String, SrcLoc)]
callStack

infix 1 `shouldMatch`

{- $setup
>>> import Control.Exception (try)
>>> import Test.HUnit.Lang
>>> import Test.DocTest.FuzzyMatch
>>> import Test.DocTest.FuzzySyntax
-}

{- $REPL-Style-Examples

Each example is one program line starting with @>>>@ followed by zero or more result lines.

>>> "hello" ++ ", " ++ "world"
"hello, world"

Since @doctest-driver@ extracts the doctests to a test suite and does not rely on GHCi, there
are some subtle edge cases to be aware of.

1. GHCi supports evaluating both pure values and 'IO' actions. @doctest-driver@ also supports
this via the type class 'ReplAction' and type family 'ReplResult'. As a result, if the target
expression to be evaluated has a polymorphic type (in technical terms, the type is not specific
enough to determine whether it matches @'IO' a@ or not), the generated test suite will fail to
compile. To fix the issue, add a type signature or use @TypeApplications@ to disambiguate.

    > -- this will not work
    > >>> 6 * 7
    > 42

    >>> (6 * 7) :: Int
    42

2. GHCi displays the result as a string by calling 'show'. The well-known @doctest@ library
additionally supports fuzzy result matching. To replicate these behaviours, we also call 'show'
on the program line expression, and perform fuzzy matching against the expected output lines.
This fuzzy matching is implemented in "Test.DocTest.FuzzyMatch". See 'shouldMatch' for examples.

3. Haddock renders examples adjacent to each other (i.e., not separated by one or more empty
lines) as a single code block. Therefore, we generate one single @do@-block for each such
example block, which means local variables bound by @let@ or monadic bind (@<-@) are in scope
up until the current example block ends. To introduce variables shared by multiple example
groups, use one of the hook instructions explained below.

    >>> let x = 3 :: Int
    >>> -- x is now in scope
    >>> x + 1
    4

4. The evaluator plugin in haskell-language-server (HLS) allows writing multiple examples to
be evaluated, and then (following all the examples) all of their results. This requires some
efforts to implement correctly. Additionally, this style makes it harder to tell which output
line comes from which test example, since it is possible for a single test example to have
multiple lines of output. Therefore, we do not support this style.

    > -- this is not supported
    > >>> 1 + 1 :: Int
    > >>> 6 * 7 :: Int
    > 2
    > 42

    The above test case would attempt run @1 + 1 :: Int@ as an 'IO' action, and compare the
    result of @6 * 7 :: Int@ (after calling 'show' as explained above) with the two output
    lines, which results in compile errors. The tests should be written as follows, instead:

    >>> 1 + 1 :: Int
    2
    >>> 6 * 7 :: Int
    42

5. GHCi allows type definitions and function definitions without @let@. Since examples are put
into @do@-blocks, neither type definitions nor function definitions are allowed. To introduce
such definitions, you must promote them to the top-level using one of the @setup@ instructions
explained below. Alternatively, functions can still be defined locally using @let@.

6. GHCi supports various commands starting with a colon (@:@). Since we do not use GHCi, these
commands are not supported in @doctest-driver@. Among all the commands, @:{@ and @:}@ are used
to start and close multiline expressions and definitions in GHCi. The @doctest@ library takes
this syntax and supports multiline test cases as follows:

    > >>> :{
    > first line
    >   second line (indented)
    >   more lines
    > :}
    > first line of expected output
    > more output lines

    Note the lack of @>>>@ markers for line 2-5: it is a clever trick to avoid the indentation
    from being removed by Haddock. However, strictly speaking (from Haddock's perspective),
    this test consist of a single line of code (@:{@) and five lines lines of expected output.
    Over all, this syntax does not render in the same way as the test writer, and may look
    confusing to users. @doctest-driver@ does not support this syntax. For multiline tests
    and properties, one should use verbatim code blocks with appropriate doctest instructions
    (@test@ and @property@ respectively) as explained in the following sections.
-}

{- $QuickCheck-Properties

Each QuickCheck property is one program line starting with @prop>@. Typically, a property is
written as a lambda expression, with multiple parameters (considered universally quantified).
The @doctest@ library allows omitting the binders; under the hood, it uses GHCi to collect the
free variables (by type-checking the expression and parsing the error messages) and implicitly
add lambda abstractions for them. QuickCheck relies on the @Arbitrary@ type class for random
generation, and thus the properties must be specific enough. The @doctest@ library uses the
@polyQuickCheck@ function (provided by QuickCheck, dependent on Template Haskell) to test the
properties, which defaults all type variables to 'Integer', making the properties monomorphic.

@doctest-driver@ cannot rely on GHCi, and it is hard to use Template Haskell (due to its phase
restrictions) in generated tests. Therefore, neither of the above features is supported. All
the free variables must be introduced explicitly through the lambda abstraction, and all input
variables should have a monomorphic type (possibly by adding type annotations).

prop> \(xs :: [Int]) -> reverse (reverse xs) == xs

This example above describes the well-recognised property for the 'reverse' function. Notice
the explicit lambda abstraction and the accompanying type annotation.
-}

{- $Verbatim-Examples

Haddock also allows verbatim code blocks, with each line preceded by a bird track (@>@). To
make such code blocks work as tests, use the @test@ instruction as follows:

> -- doctest:test
> (1 + 1) `shouldBe` (2 :: Int)

These examples are implicitly put into a @do@ block for the 'IO' monad, and the whole block is
copied verbatim into the generated text (except adjusting the indentation). Unlike REPL-style
examples, we cannot specify expected output lines, and the comparison must be done explicitly.

Verbatim examples are more flexible than REPL-style examples.

First, REPL-style examples call 'show' on the result to compare with the expected output lines.
When the result type does not implement 'Show', or when the 'Show' instance does not provide
sufficient meaningful information, REPL-style examples are not suitable.

Second, Haddock strips leading whitespace from test lines in REPL-style examples. To ensure the
behaviour of test examples is consistent with the way they are rendered, @doctest-driver@ also
strips the leading whitespace. This means REPL-style examples are not suitable for multiline
test cases with indentation.
-}

{- $Verbatim-Properties

Haddock only supports single-line properties. For multiline properties, one can write them as
verbatim examples by calling the @property@ function from QuickCheck:

> -- doctest:setup-import
> import Test.QuickCheck

(This @setup-import@ block adds an @import@ statement to the generated module. The details will
be explained in later sections, and readers can safely ignore it for now.)

> -- doctest:test
> property $ \(xs :: [Int]) ->
>   reverse (reverse xs) == xs

For this specific use case, @doctest-driver@ also provides the @property@ instruction to write
verbatim properties. One should prefer the following (using @property@) over the above (using
@test@ and call @property@ explicitly) to better express the intention concisely:

> -- doctest:property
> \(xs :: [Int]) ->
>   reverse (reverse xs) == xs
-}

{- $Captures

Sometimes we need some textual contents in our tests, and it might also be useful to let the
user see them while browsing the documentation. In such cases, we can use the @capture@
instruction in a verbatim code block. The whole block is unindented by stripping the common
whitespace prefix. The captured text does not contain a trailing @\'\\n\'@ character. To force
adding one, leave an empty line at the end of the verbatim code block.

It is most natural to start with the test cases making use of the captured variable:

>>> take 15 stringCapture
"This text block"
>>> length (lines stringCapture)
2

and show its contents afterwards:

> -- doctest:capture(stringCapture :: String)
> This text block is supposed to be captured as a String variable.
> Everything besides the first line (the doctest instruction) is captured verbatim.

Sometimes, our tests expect the contents to be saved somewhere as a file. The @capture@
instruction conveniently allow specifying the variable to have type 'FilePath' in such cases:

> -- doctest:capture(fileCapture :: FilePath)
> This text block will be saved to a temporary file.
> The file is written once and reused for all test cases in this group.
> Therefore, it is only suitable for reading.
> For advanced usage involving editing and deletion, use a String capture with a "before" or "around" hook.

The @fileCapture :: 'FilePath'@ variable is then available for use.

>>> fileContents <- readFile fileCapture
>>> length (lines fileContents)
4
>>> lines fileContents !! 2
"Therefore, it is only suitable for reading."

We can also capture texts as @Text@s and @ByteString@s (strict or lazy).

For strict 'T.Text', use @Text@ or @Strict.Text@:

> -- doctest:capture(captureStrictText :: Text)
> strict text

> -- doctest:capture(captureStrictTextAlt :: Strict.Text)
> strict text

>>> captureStrictText :: T.Text
"strict text"
>>> captureStrictText == captureStrictTextAlt
True

For lazy 'TL.Text', use @Lazy.Text@:

> -- doctest:capture(captureLazyText :: Lazy.Text)
> lazy text

>>> captureLazyText :: TL.Text
"lazy text"

The same applies to strict and lazy 'ByteString's, as well as 'ShortByteString's:

> -- doctest:capture(captureStrictByteString :: ByteString)
> strict byte string

> -- doctest:capture(captureStrictByteStringAlt :: Strict.ByteString)
> strict byte string

> -- doctest:capture(captureLazyByteString :: Lazy.ByteString)
> lazy byte string

> -- doctest:capture(captureShortByteString :: ShortByteString)
> short byte string

>>> captureStrictByteString :: ByteString
"strict byte string"
>>> captureStrictByteString == captureStrictByteStringAlt
True

>>> captureLazyByteString :: LazyByteString
"lazy byte string"

>>> captureShortByteString :: ShortByteString
"short byte string"

@doctest-driver@ will take care of correctly wrapping the text contents into the requested
types. For byte strings, the text is encoded as UTF-8. No extra import is required for the
captures themselves, but in order to use them in a meaningful way, one may still need to add
explicit dependency on the @text@ and @bytestring@ packages, and import the required modules.
In this example, we use type ascriptions to assert that the captured variables have the
expected type, which requires the following imports:

> -- doctest:setup-import
> import qualified Data.Text as T (Text)
> import qualified Data.Text.Lazy as TL (Text)
> import Data.ByteString (ByteString)
> import Data.ByteString.Lazy (LazyByteString)
> import Data.ByteString.Short (ShortByteString)

If your specific use case requires capturing text in encodings other than UTF-8, you can use
'String' capture and do the encoding yourself. We expect UTF-8 to be enough for most use cases.
-}

-- | Expect that the value @a@, when 'show'n, 'match'es the pattern string.
--
-- Simple usage: no pattern in the pattern string.
--
-- >>> try @HUnitFailure ((123 :: Int) `shouldMatch` "123")
-- Right ()
-- >>> try @HUnitFailure ((123 :: Int) `shouldMatch` "000")
-- Left (HUnitFailure (Just (SrcLoc {...})) (ExpectedButGot Nothing "000" "123"))
-- >>> try @HUnitFailure ("测试«αβ»" `shouldMatch` "\"\\27979\\35797\\171\\945\\946\\187\"")
-- Right ()
--
-- Advanced usage: @...@ for inline and multiline wildcard.
--
-- >>> try @HUnitFailure (True `shouldMatch` "T...e")
-- Right ()
-- >>> try @HUnitFailure ("some fancy string" `shouldMatch` "\"some ... string\"")
-- Right ()
--
-- > -- doctest:setup-top
-- > data Verbatim = Verbatim String
-- > instance Show Verbatim where show (Verbatim s) = s
--
-- >>> try @HUnitFailure (Verbatim "aaa\n\nbbb" `shouldMatch` "aaa\n...\nbbb")
-- Right ()
-- >>> try @HUnitFailure (Verbatim "aaa\nccc\nddd\nbbb" `shouldMatch` "aaa\n...\nbbb")
-- Right ()
shouldMatch :: (HasCallStack, ReplAction a, Show (ReplResult a)) => a -> String -> Assertion
shouldMatch :: forall a.
(HasCallStack, ReplAction a, Show (ReplResult a)) =>
a -> String -> Assertion
shouldMatch a
actual String
expected = do
  String
sActual <- ReplResult a -> String
forall a. Show a => a -> String
show (ReplResult a -> String) -> IO (ReplResult a) -> IO String
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> IO (ReplResult a)
forall a. ReplAction a => a -> IO (ReplResult a)
replAction a
actual
  let err :: HUnitFailure
err = Maybe SrcLoc -> FailureReason -> HUnitFailure
HUnitFailure Maybe SrcLoc
HasCallStack => Maybe SrcLoc
location (Maybe String -> String -> String -> FailureReason
ExpectedButGot Maybe String
forall a. Maybe a
Nothing String
expected String
sActual)
  let onError :: Assertion
onError = String
expected String -> Assertion -> Assertion
forall a b. NFData a => a -> b -> b
`deepseq` String
sActual String -> Assertion -> Assertion
forall a b. NFData a => a -> b -> b
`deepseq` HUnitFailure -> Assertion
forall e a. Exception e => e -> IO a
throwIO HUnitFailure
err
  Bool -> Assertion -> Assertion
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
unless (Pattern -> String -> Bool
match (String -> Pattern
parsePattern String
expected) String
sActual) Assertion
onError

-- | Result type of running as a 'ReplAction'. Unfortunately, this cannot handle polymorphic types
-- without a known top-level type constructor.
type family ReplResult (a :: Type) :: Type where
  ReplResult (IO a) = a
  ReplResult a = a

-- | GHCi session supports both evaluating pure values and running 'IO' actions. Use this type
-- class to let the compiler deduce which one a test line should use.
class ReplAction a where
  -- | Embed into an 'IO' action.
  --
  -- >>> replAction (123 :: Int)
  -- 123
  -- >>> replAction (pure 123 :: IO Int)
  -- 123
  replAction :: a -> IO (ReplResult a)

instance a ~ ReplResult a => ReplAction a where
  replAction :: a -> IO (ReplResult a)
replAction = a -> IO a
a -> IO (ReplResult a)
forall a. a -> IO a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure

instance {-# OVERLAPPING #-} ReplAction (IO a) where
  replAction :: IO a -> IO (ReplResult (IO a))
replAction = IO a -> IO a
IO a -> IO (ReplResult (IO a))
forall a. a -> a
id

-- | Create a temporary file, write the given contents, run the action with the 'FilePath', and
-- remove the file at last. Used to implement 'FilePath' captures.
withWriteTempFile :: (FilePath -> IO a) -> String -> IO a
withWriteTempFile :: forall a. (String -> IO a) -> String -> IO a
withWriteTempFile String -> IO a
act String
contents = String -> (String -> Handle -> IO a) -> IO a
forall (m :: Type -> Type) a.
(MonadIO m, MonadMask m) =>
String -> (String -> Handle -> m a) -> m a
withSystemTempFile String
"doctest.txt" String -> Handle -> IO a
go
  where go :: String -> Handle -> IO a
go String
path Handle
h = Handle -> Bool -> Assertion
hSetBinaryMode Handle
h Bool
True Assertion -> Assertion -> Assertion
forall a b. IO a -> IO b -> IO b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Handle -> String -> Assertion
hPutStr Handle
h String
contents Assertion -> Assertion -> Assertion
forall a b. IO a -> IO b -> IO b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> Handle -> Assertion
hClose Handle
h Assertion -> IO a -> IO a
forall a b. IO a -> IO b -> IO b
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f b
*> String -> IO a
act String
path

-- | Convert a string to strict text.
textStrict :: String -> T.Text
textStrict :: String -> Text
textStrict = String -> Text
T.pack

-- | Convert a string to lazy text.
textLazy :: String -> TL.Text
textLazy :: String -> Text
textLazy = String -> Text
TL.pack

-- | Convert a string to strict byte string.
byteStringStrict :: String -> ByteString
byteStringStrict :: String -> ByteString
byteStringStrict = Text -> ByteString
T.encodeUtf8 (Text -> ByteString) -> (String -> Text) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
textStrict

-- | Convert a string to lazy byte string.
byteStringLazy :: String -> LazyByteString
byteStringLazy :: String -> LazyByteString
byteStringLazy = ByteString -> LazyByteString
fromStrict (ByteString -> LazyByteString)
-> (String -> ByteString) -> String -> LazyByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
byteStringStrict

-- | Convert a string to short byte string.
shortByteString :: String -> ShortByteString
shortByteString :: String -> ShortByteString
shortByteString = ByteString -> ShortByteString
toShort (ByteString -> ShortByteString)
-> (String -> ByteString) -> String -> ShortByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
byteStringStrict

-- | No-op function. Used to silence the "variable unused" warning.
markUsed :: a -> IO ()
markUsed :: forall a. a -> Assertion
markUsed a
_ = () -> Assertion
forall a. a -> IO a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ()
{-# INLINE markUsed #-}