Skip to content

Commit 1feb3e9

Browse files
authored
Remove Plutus Tx functions with Haskell.Monad constraint (#5195)
1 parent fef318f commit 1feb3e9

File tree

4 files changed

+16
-40
lines changed

4 files changed

+16
-40
lines changed

plutus-benchmark/ed25519-throughput/Main.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ import UntypedPlutusCore qualified as UPLC
2525
import UntypedPlutusCore.Evaluation.Machine.Cek qualified as Cek
2626

2727
import PlutusTx.IsData (toData, unstableMakeIsData)
28-
import PlutusTx.Prelude as Tx hiding (sort, (*))
28+
import PlutusTx.Prelude as Tx hiding (sort, traverse_, (*))
2929

3030
import Cardano.Crypto.DSIGN.Class (ContextDSIGN, DSIGNAlgorithm, Signable, deriveVerKeyDSIGN, genKeyDSIGN,
3131
rawSerialiseSigDSIGN, rawSerialiseVerKeyDSIGN, signDSIGN)
@@ -35,6 +35,7 @@ import Cardano.Crypto.Seed (mkSeedFromBytes)
3535
import Data.ByteString (ByteString)
3636
import Data.ByteString qualified as BS
3737
import Data.ByteString.Hash qualified as Hash
38+
import Data.Foldable (traverse_)
3839
import Flat qualified
3940
import Hedgehog.Internal.Gen qualified as G
4041
import Hedgehog.Internal.Range qualified as R
@@ -217,4 +218,4 @@ main = do
217218
testHaskell 100
218219
printf " n script size CPU usage Memory usage\n"
219220
printf " ----------------------------------------------------------------------\n"
220-
mapM_ printStatistics [0, 10..150]
221+
traverse_ printStatistics [0, 10..150]

plutus-benchmark/nofib/exe/Main.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ import Control.Monad ()
1212
import Control.Monad.Trans.Except (runExceptT)
1313
import Data.ByteString qualified as BS
1414
import Data.Char (isSpace)
15+
import Data.Foldable (traverse_)
1516
import Flat qualified
1617
import Options.Applicative as Opt hiding (action)
1718
import System.Exit (exitFailure)
@@ -35,7 +36,7 @@ import PlutusCore.Evaluation.Machine.ExMemory (ExCPU (..), ExMemory (..))
3536
import PlutusCore.Pretty (prettyPlcClassicDebug)
3637
import PlutusTx (getPlcNoAnn)
3738
import PlutusTx.Code (CompiledCode, sizePlc)
38-
import PlutusTx.Prelude hiding (fmap, mappend, (<$), (<$>), (<*>), (<>))
39+
import PlutusTx.Prelude hiding (fmap, mappend, traverse_, (<$), (<$>), (<*>), (<>))
3940
import UntypedPlutusCore qualified as UPLC
4041
import UntypedPlutusCore.Evaluation.Machine.Cek qualified as UPLC
4142

@@ -296,7 +297,7 @@ printSizesAndBudgets = do
296297

297298
putStrLn "Script Size CPU budget Memory budget"
298299
putStrLn "-----------------------------------------------------------------"
299-
mapM_ (putStr . formatInfo) statistics
300+
traverse_ (putStr . formatInfo) statistics
300301

301302

302303
main :: IO ()
@@ -314,7 +315,7 @@ main = do
314315
Primetest n -> if n<0 then Hs.error "Positive number expected"
315316
else print $ Prime.runPrimalityTest n
316317
DumpPLC pa ->
317-
Hs.mapM_ putStrLn $ unindent . prettyPlcClassicDebug . UPLC.mkDefaultProg . getTerm $ pa
318+
traverse_ putStrLn $ unindent . prettyPlcClassicDebug . UPLC.mkDefaultProg . getTerm $ pa
318319
where unindent d = map (dropWhile isSpace) $ (Hs.lines . Hs.show $ d)
319320
DumpFlatNamed pa ->
320321
writeFlatNamed . UPLC.mkDefaultProg . getTerm $ pa
Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
### Removed
2+
3+
- Removed Plutus Tx library functions with the `Haskell.Monad` constraint.
4+
Functions requiring `Functor` and `Applicative` are using `PlutusTx.Functor` and
5+
`PlutusTx.Applicative`, but those requiring `Monad` were using Haskell's `Monad`, which
6+
is inconsistent and confusing. We should either add a `PlutusTx.Monad` class, or switch
7+
to Haskell's `Functor` and `Applicative`. Some of these functions like `sequence_` and
8+
`mapM_` are also not useful, and one should prefer `sequenceA_` and `traverse_`, respectively.

plutus-tx/src/PlutusTx/Foldable.hs

Lines changed: 1 addition & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -3,18 +3,11 @@
33
{-# OPTIONS_GHC -fno-omit-interface-pragmas #-}
44
module PlutusTx.Foldable (
55
Foldable(..),
6-
-- * Special biased folds
7-
foldrM,
8-
foldlM,
9-
-- * Folding actions
10-
-- ** Applicative actions
6+
-- * Applicative actions
117
traverse_,
128
for_,
139
sequenceA_,
14-
sequence_,
1510
asum,
16-
-- ** Monadic actions
17-
mapM_,
1811
-- * Specialized folds
1912
concat,
2013
concatMap,
@@ -51,8 +44,6 @@ import PlutusTx.Monoid (Monoid (..))
5144
import PlutusTx.Numeric
5245
import PlutusTx.Semigroup ((<>))
5346

54-
import Prelude qualified as Haskell (Monad, return, (>>), (>>=))
55-
5647
-- | Plutus Tx version of 'Data.Foldable.Foldable'.
5748
class Foldable t where
5849
-- | Plutus Tx version of 'Data.Foldable.foldr'.
@@ -137,30 +128,12 @@ sum = foldr (+) zero
137128
product :: (Foldable t, MultiplicativeMonoid a) => t a -> a
138129
product = foldr (*) one
139130

140-
-- | Plutus Tx version of 'Data.Foldable.foldrM'.
141-
foldrM :: (Foldable t, Haskell.Monad m) => (a -> b -> m b) -> b -> t a -> m b
142-
foldrM f z0 xs = foldl c Haskell.return xs z0
143-
where c k x z = f x z Haskell.>>= k
144-
{-# INLINE c #-}
145-
146-
-- | Plutus Tx version of 'Data.Foldable.foldlM'.
147-
foldlM :: (Foldable t, Haskell.Monad m) => (b -> a -> m b) -> b -> t a -> m b
148-
foldlM f z0 xs = foldr c Haskell.return xs z0
149-
where c x k z = f z x Haskell.>>= k
150-
{-# INLINE c #-}
151-
152131
-- | Plutus Tx version of 'Data.Foldable.traverse_'.
153132
traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
154133
traverse_ f = foldr c (pure ())
155134
where c x k = f x *> k
156135
{-# INLINE c #-}
157136

158-
-- | Plutus Tx version of 'Data.Foldable.sequence_'.
159-
sequence_ :: (Foldable t, Haskell.Monad m) => t (m a) -> m ()
160-
sequence_ = foldr c (Haskell.return ())
161-
where c m k = m Haskell.>> k
162-
{-# INLINE c #-}
163-
164137
-- | Plutus Tx version of 'Data.Foldable.for_'.
165138
for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()
166139
{-# INLINE for_ #-}
@@ -222,10 +195,3 @@ find :: Foldable t => (a -> Bool) -> t a -> Maybe a
222195
find p = foldr f Nothing
223196
where
224197
f a acc = if p a then Just a else acc
225-
226-
-- | Plutus Tx version of 'Data.Foldable.mapM_'.
227-
{-# INLINABLE mapM_ #-}
228-
mapM_ :: (Foldable t, Haskell.Monad m) => (a -> m b) -> t a -> m ()
229-
mapM_ f = foldr c (Haskell.return ())
230-
where c x k = f x Haskell.>> k
231-
{-# INLINE c #-}

0 commit comments

Comments
 (0)