Skip to content

Commit

Permalink
Add tests for foldlM'
Browse files Browse the repository at this point in the history
  • Loading branch information
Lysxia committed Mar 13, 2024
1 parent 35c8064 commit 75c2b84
Showing 1 changed file with 45 additions and 0 deletions.
45 changes: 45 additions & 0 deletions tests/Tests/Properties/Folds.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,23 @@
-- | Test folds, scans, and unfolds

{-# LANGUAGE CPP #-}
{-# LANGUAGE ViewPatterns #-}

{-# OPTIONS_GHC -fno-warn-missing-signatures #-}

#ifdef MIN_VERSION_tasty_inspection_testing
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -O -dsuppress-all -dno-suppress-type-signatures -fplugin=Test.Tasty.Inspection.Plugin #-}
#endif

module Tests.Properties.Folds
( testFolds
) where

import Control.Arrow (second)
import Control.Exception (ErrorCall, evaluate, try)
import Data.Functor.Identity (Identity(..))
import Control.Monad.Trans.State (runState, state)
import Data.Word (Word8, Word16)
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.HUnit (testCase, assertFailure, assertBool)
Expand All @@ -21,6 +30,11 @@ import qualified Data.Text.Internal.Fusion.Common as S
import qualified Data.Text.Lazy as TL
import qualified Data.Char as Char

#ifdef MIN_VERSION_tasty_inspection_testing
import Test.Tasty.Inspection (inspectTest, (==~))
import GHC.Exts (inline)
#endif

-- Folds

sf_foldl (applyFun -> p) (applyFun2 -> f) z =
Expand Down Expand Up @@ -193,6 +207,32 @@ tl_unfoldrN n m = (L.take i . L.unfoldr (unf j)) `eq`
where i = fromIntegral (n :: Word16)
j = fromIntegral (m :: Word16)

-- Monadic folds

-- Parametric polymorphism allows us to only test foldlM' specialized to
-- one function in the state monad (called @logger@ in the following tests)
-- that just logs the arguments it was applied to and produces a fresh
-- accumulator. That alone determines the general behavior of foldlM' with an
-- arbitrary function in any monad.
-- Reference: "Testing Polymorphic Properties" by Bernardy et al.
-- https://publications.lib.chalmers.se/records/fulltext/local_99387.pdf

t_foldlM' = (\l -> (length l, zip [0 ..] l)) `eqP` (fmap reverse . (`runState` []) . T.foldlM' logger 0)
where logger i c = state (\cs -> (length cs + 1, (i, c) : cs)) -- list in reverse order
tl_foldlM' = (\l -> (length l, zip [0 ..] l)) `eqP` (fmap reverse . (`runState` []) . TL.foldlM' logger 0)
where logger i c = state (\cs -> (length cs + 1, (i, c) : cs)) -- list in reverse order

#ifdef MIN_VERSION_tasty_inspection_testing
-- As a sanity check for performance, the simplified Core
-- foldlM' specialized to Identity is the same as foldl'.

_T_foldl'_from_foldlM' :: (a -> Char -> a) -> a -> T.Text -> a
_T_foldl'_from_foldlM' f x = runIdentity . T.foldlM' (\i c -> Identity (f i c)) x

_T_foldl' :: (a -> Char -> a) -> a -> T.Text -> a
_T_foldl' = inline T.foldl'
#endif

isAscii_border :: IO ()
isAscii_border = do
let text = T.drop 2 $ T.pack "XX1234五"
Expand Down Expand Up @@ -221,6 +261,11 @@ testFolds =
testProperty "sf_foldr1" sf_foldr1,
testProperty "t_foldr1" t_foldr1,
testProperty "tl_foldr1" tl_foldr1,
testProperty "t_foldlM'" t_foldlM',
testProperty "tl_foldlM'" tl_foldlM',
#ifdef MIN_VERSION_tasty_inspection_testing
$(inspectTest ('_T_foldl'_from_foldlM' ==~ '_T_foldl')),
#endif
testCase "fold_apart" fold_apart,

testGroup "special" [
Expand Down

0 comments on commit 75c2b84

Please sign in to comment.