From b2a8ebc583be46a2a981592c4049e3710b2efaa1 Mon Sep 17 00:00:00 2001 From: zeme Date: Tue, 22 Apr 2025 18:43:45 +0200 Subject: [PATCH 01/30] PlutusTx.Data.List & PlutusTx.BuiltinList - Feature Parity --- plutus-tx/src/PlutusTx/BuiltinList.hs | 447 +++++++++++++++++-- plutus-tx/src/PlutusTx/Builtins.hs | 9 + plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs | 2 +- plutus-tx/src/PlutusTx/ErrorCodes.hs | 71 +-- plutus-tx/src/PlutusTx/List.hs | 113 +++-- 5 files changed, 532 insertions(+), 110 deletions(-) diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index d7d9e8d41d4..c369b3e60a4 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -5,6 +5,8 @@ module PlutusTx.BuiltinList ( BuiltinList, B.caseList, B.caseList', + B.null, + B.uncons, map, elem, find, @@ -14,76 +16,443 @@ module PlutusTx.BuiltinList ( ) where -import Prelude (Bool (..), Integer, Maybe (..), otherwise, (.)) +import Prelude (Bool (..), Integer, Maybe (..), const, curry, id, not, otherwise, undefined, (.)) import PlutusTx.Builtins qualified as B import PlutusTx.Builtins.HasOpaque -import PlutusTx.Builtins.Internal (BuiltinList) +import PlutusTx.Builtins.Internal (BuiltinList, BuiltinPair) import PlutusTx.Builtins.Internal qualified as BI import PlutusTx.Eq import PlutusTx.ErrorCodes +import PlutusTx.Ord import PlutusTx.Trace (traceError) -infixl 9 !! +-- | Plutus Tx version of 'Data.List.map' for 'BuiltinList'. map :: forall a b. (MkNil b) => (a -> b) -> BuiltinList a -> BuiltinList b map f = go - where - go :: BuiltinList a -> BuiltinList b - go = - B.caseList' - B.mkNil - (\x -> BI.mkCons (f x) . go) + where + go :: BuiltinList a -> BuiltinList b + go = B.caseList' B.mkNil ( \x xs -> f x `BI.mkCons` go xs ) {-# INLINEABLE map #-} +-- | Plutus Tx version of 'Data.List.mapMaybe' for 'BuiltinList'. +mapMaybe :: forall a b. (MkNil b) => (a -> Maybe b) -> BuiltinList a -> BuiltinList b +mapMaybe f = go + where + go :: BuiltinList a -> BuiltinList b + go = B.caseList' B.mkNil + ( \x xs -> case f x of + Nothing -> go xs + Just y -> y `BI.mkCons` go xs + ) +{-# INLINEABLE mapMaybe #-} + +-- | Does the element occur in the list? elem :: forall a. (Eq a) => a -> BuiltinList a -> Bool elem a = go - where - go :: BuiltinList a -> Bool - go = B.caseList' False (\x xs -> if a == x then True else go xs) + where + go :: BuiltinList a -> Bool + go = B.caseList' False ( \x xs -> if a == x then True else go xs ) {-# INLINEABLE elem #-} +-- | Returns the leftmost element matching the predicate, or `Nothing` if there's no such element. find :: forall a. (a -> Bool) -> BuiltinList a -> Maybe a find p = go - where - go :: BuiltinList a -> Maybe a - go = - B.caseList' - Nothing - (\x xs -> if p x then Just x else go xs) + where + go :: BuiltinList a -> Maybe a + go = B.caseList' Nothing ( \x xs -> if p x then Just x else go xs ) {-# INLINEABLE find #-} +-- | Determines whether any element of the structure satisfies the predicate. any :: forall a. (a -> Bool) -> BuiltinList a -> Bool any p = go - where - go :: BuiltinList a -> Bool - go = B.caseList' False (\x xs -> if p x then True else go xs) + where + go :: BuiltinList a -> Bool + go = B.caseList' False ( \x xs -> if p x then True else go xs ) {-# INLINEABLE any #-} +-- | Determines whether all elements of the list satisfy the predicate. all :: forall a. (a -> Bool) -> BuiltinList a -> Bool all p = go - where - go :: BuiltinList a -> Bool - go = B.caseList' True (\x xs -> if p x then go xs else False) + where + go :: BuiltinList a -> Bool + go = B.caseList' True ( \x xs -> if p x then go xs else False ) {-# INLINEABLE all #-} -{-| Get the element at a given index. - -This function is partial and takes linear time. --} +-- | Plutus Tx version of '(GHC.List.!!)' for 'BuiltinList'. +-- This function is partial and takes linear time. +infixl 9 !! (!!) :: forall a. BuiltinList a -> Integer -> a (!!) xs0 i0 | i0 `B.lessThanInteger` 0 = traceError builtinListNegativeIndexError - | otherwise = go xs0 i0 + | otherwise = go i0 xs0 where - go :: BuiltinList a -> Integer -> a - go xs i = - B.caseList - (\_ -> traceError builtinListIndexTooLargeError) - ( \y ys _ -> - if i `B.equalsInteger` 0 - then y - else go ys (B.subtractInteger i 1) + go :: Integer -> BuiltinList a -> a + go i = B.caseList' + (traceError builtinListIndexTooLargeError) + ( \y ys -> + if i `B.equalsInteger` 0 + then y + else go (B.subtractInteger i 1) ys + ) +{-# INLINEABLE (!!) #-} + +-- TODO add tests and changelog for Data.List + +-- | Plutus Tx version of 'Data.List.length' for 'BuiltinList'. +length :: forall a. BuiltinList a -> Integer +length = foldr ( \_ -> B.addInteger 1 ) 0 +{-# INLINABLE length #-} + +-- | Returns the conjunction of a list of Bools. +and :: BuiltinList Bool -> Bool +and = all id + +-- | Returns the disjunction of a list of Bools. +or :: BuiltinList Bool -> Bool +or = any id +{-# INLINABLE or #-} + +-- | The negation of `elem`. +notElem :: forall a. (Eq a) => a -> BuiltinList a -> Bool +notElem a = not . elem a +{-# INLINABLE notElem #-} + +-- | Plutus Tx version of 'Data.List.foldr' for 'BuiltinList'. +foldr :: forall a b. (a -> b -> b) -> b -> BuiltinList a -> b +foldr f acc = go + where + go :: BuiltinList a -> b + go = B.caseList' acc ( \x xs -> f x (go xs) ) +{-# INLINABLE foldr #-} + +-- | Plutus Tx velsion of 'Data.List.foldl' for 'BuiltinList'. +foldl :: forall a b. (b -> a -> b) -> b -> BuiltinList a -> b +foldl f = go + where + go :: b -> BuiltinList a -> b + go acc = B.caseList' acc ( \x xs -> go (f acc x) xs ) +{-# INLINABLE foldl #-} + +-- | Plutus Tx version of '(Data.List.++)' for 'BuiltinList'. +infixr 5 ++ +(++) :: forall a. BuiltinList a -> BuiltinList a -> BuiltinList a +(++) l r = foldr BI.mkCons r l +{-# INLINABLE (++) #-} + +-- | Plutus Tx version of 'Data.List.concat' for 'BuiltinList'. +concat :: forall a. (MkNil a) => BuiltinList (BuiltinList a) -> BuiltinList a +concat = foldr (++) B.mkNil +{-# INLINABLE concat #-} + +-- | Plutus Tx version of 'Data.List.concatMap' for 'BuiltinList'. +concatMap :: forall a b. (MkNil b) => (a -> BuiltinList b) -> BuiltinList a -> BuiltinList b +concatMap f = foldr ( \x ys -> f x ++ ys ) B.mkNil +{-# INLINABLE concatMap #-} + +-- | Plutus Tx version of 'Data.List.filter' for 'BuiltinList'. +filter :: forall a. (MkNil a) => (a -> Bool) -> BuiltinList a -> BuiltinList a +filter p = foldr ( \x xs -> if p x then x `BI.mkCons` xs else xs ) B.mkNil +{-# INLINABLE filter #-} + +-- | Plutus Tx version of 'Data.List.listToMaybe' for 'BuiltinList'. +listToMaybe :: forall a. BuiltinList a -> Maybe a +listToMaybe = BI.caseList' Nothing ( \x _ -> Just x ) +{-# INLINABLE listToMaybe #-} + +-- | Return the element in the list, if there is precisely one. +uniqueElement :: forall a. BuiltinList a -> Maybe a +uniqueElement = BI.caseList' Nothing + ( \x -> BI.caseList' (Just x) ( \_ _ -> Nothing ) + ) +{-# INLINABLE uniqueElement #-} + +-- | Plutus Tx version of 'Data.List.findIndices' for 'BuiltinList'. +findIndices :: forall a. (a -> Bool) -> BuiltinList a -> BuiltinList Integer +findIndices p = go 0 + where + go :: Integer -> BuiltinList a -> BuiltinList Integer + go i = BI.caseList' B.mkNil + ( \x xs -> + let indices = go (B.addInteger i 1) xs + in if p x then BI.mkCons i indices else indices ) - xs - () +{-# INLINABLE findIndices #-} + +-- | Plutus Tx version of 'Data.List.findIndex'. +findIndex :: forall a. (a -> Bool) -> BuiltinList a -> Maybe Integer +findIndex f = go 0 + where + go :: Integer -> BuiltinList a -> Maybe Integer + go i = BI.caseList' Nothing + ( \x xs -> if f x then Just i else go (B.addInteger i 1) xs + ) +{-# INLINABLE findIndex #-} + +-- | Cons each element of the first list to the second one in reverse order +-- (i.e. the last element of the first list is the head of the result). +-- +-- > revAppend xs ys === reverse xs ++ ys +revAppend :: forall a. BuiltinList a -> BuiltinList a -> BuiltinList a +revAppend l r = BI.caseList' r ( \x xs -> revAppend xs (x `BI.mkCons` r) ) l +{-# INLINABLE revAppend #-} + +-- | Plutus Tx version of 'Data.List.reverse' for 'BuiltinList'. +reverse :: forall a. (MkNil a) => BuiltinList a -> BuiltinList a +reverse xs = revAppend xs B.mkNil +{-# INLINABLE reverse #-} + +-- | Plutus Tx version of 'Data.List.zip' for 'BuiltinList'. +zip + :: forall a b. (MkNil a, MkNil b) + => BuiltinList a + -> BuiltinList b + -> BuiltinList (BuiltinPair a b) +zip = zipWith (curry BI.BuiltinPair) +{-# INLINABLE zip #-} + +-- | Plutus Tx version of 'Data.List.unzip' for 'BuiltinList'. +unzip + :: forall a b. (MkNil a, MkNil b) + => BuiltinList (BuiltinPair a b) + -> BuiltinPair (BuiltinList a) (BuiltinList b) +unzip = B.caseList' emptyPair + ( \p l -> do + let BI.BuiltinPair (x, y) = p + let BI.BuiltinPair (xs', ys') = unzip l + BI.BuiltinPair (x `BI.mkCons` xs', y `BI.mkCons` ys') + ) + where + emptyPair :: BuiltinPair (BuiltinList a) (BuiltinList b) + emptyPair = BI.BuiltinPair (B.mkNil, B.mkNil) +{-# INLINABLE unzip #-} + +-- | Plutus Tx version of 'Data.List.head' for 'BuiltinList'. +head :: forall a. BuiltinList a -> a +head = B.caseList' (traceError headEmptyBuiltinListError) ( \x _ -> x ) +{-# INLINABLE head #-} + +-- | Plutus Tx version of 'Data.List.last' for 'BuiltinList'. +last :: forall a. BuiltinList a -> a +last = B.caseList' (traceError lastEmptyBuiltinListError) + ( \x -> B.caseList' x ( \_ -> last ) + ) +{-# INLINABLE last #-} + +-- | Plutus Tx version of 'Data.List.tail' for 'BuiltinList'. +tail :: forall a. BuiltinList a -> BuiltinList a +tail = B.caseList' (traceError lastEmptyBuiltinListError) ( \_ xs -> xs ) +{-# INLINABLE tail #-} + +-- | Plutus Tx version of 'Data.List.take' for 'BuiltinList'. +take :: forall a. (MkNil a) => Integer -> BuiltinList a -> BuiltinList a +take n l + | n `B.lessThanInteger` 0 = B.mkNil + | otherwise = B.caseList' B.mkNil + ( \x xs -> x `BI.mkCons` take (B.subtractInteger n 1) xs + ) l +{-# INLINABLE take #-} + +-- | Plutus Tx version of 'Data.List.drop' for 'BuiltinList'. +drop :: forall a. (MkNil a) => Integer -> BuiltinList a -> BuiltinList a +drop n l + | n `B.lessThanEqualsInteger` 0 = B.mkNil + | otherwise = B.caseList' B.mkNil + ( \_ xs -> drop (B.subtractInteger n 1) xs + ) l +{-# INLINABLE drop #-} + +-- -- | Plutus Tx version of 'Data.List.splitAt'. +-- splitAt :: forall a. Integer -> BuiltinList a -> BuiltinPair (BuiltinList a) (BuiltinList a) +-- splitAt n xs +-- | n `B.lessThanEqualInteger` 0 = BI.BuiltinPair (B.mkNil, xs) +-- | otherwise = go n xs +-- where +-- go :: Integer -> BuiltinList a -> (BuiltinList a, BuiltinList a) +-- go m = B.caseList' (BI.BuiltinPair (B.mkNil, B.mkNil)) (\x xs -> +-- if m `B.equalsInteger` 0 +-- then BI.BuiltinPair (B.mkNil, xs) +-- else let BI.BuiltinPair (zs, ws) = go (B.subtractInteger m 1) xs +-- in BI.BuiltinPair (BI.mkCons x zs, ws) +-- ) + + +-- [] = ([], []) +-- go m (y:ys) +-- | m == 1 = ([y], ys) +-- | otherwise = case go (Builtins.subtractInteger m 1) ys of +-- (zs, ws) -> (y:zs, ws) +-- {-# INLINABLE splitAt #-} + +-- | Plutus Tx version of 'Data.List.nub' for 'BuiltinList'. +nub :: forall a. (Eq a, MkNil a) => BuiltinList a -> BuiltinList a +nub = nubBy (==) +{-# INLINABLE nub #-} + +-- | Plutus Tx version of 'Data.List.elemBy' for 'BuiltinList'. +elemBy :: forall a. (a -> a -> Bool) -> a -> BuiltinList a -> Bool +elemBy eq y = go + where + go :: BuiltinList a -> Bool + go = B.caseList' False ( \x xs -> if eq x y then True else go xs ) +{-# INLINABLE elemBy #-} + +-- | Plutus Tx version of 'Data.List.nubBy' for 'BuiltinList'. +nubBy :: forall a. (MkNil a) => (a -> a -> Bool) -> BuiltinList a -> BuiltinList a +nubBy eq = go B.mkNil + where + go :: BuiltinList a -> BuiltinList a -> BuiltinList a + go xs = B.caseList' B.mkNil + ( \y ys -> + if elemBy eq y xs + then go xs ys + else y `BI.mkCons` go ys (y `BI.mkCons` xs) + ) +{-# INLINABLE nubBy #-} + +-- | Plutus Tx version of 'Data.List.zipWith' for 'BuiltinList'. +zipWith + :: forall a b c. (MkNil c) + => (a -> b -> c) + -> BuiltinList a + -> BuiltinList b + -> BuiltinList c +zipWith f = go + where + go :: BuiltinList a -> BuiltinList b -> BuiltinList c + go xs ys = + B.caseList' B.mkNil + ( \x xs' -> + B.caseList' B.mkNil + ( \y ys' -> f x y `BI.mkCons` go xs' ys' + ) ys + ) xs +{-# INLINABLE zipWith #-} + +-- | Plutus Tx version of 'Data.List.dropWhile' for 'BuiltinList'. +dropWhile :: forall a. (MkNil a) => (a -> Bool) -> BuiltinList a -> BuiltinList a +dropWhile p = go + where + go :: BuiltinList a -> BuiltinList a + go xs = B.caseList' B.mkNil ( \x xs' -> if p x then go xs' else xs ) xs +{-# INLINABLE dropWhile #-} + +-- | Plutus Tx version of 'Data.List.replicate' for 'BuiltinList'. +replicate :: forall a. (MkNil a) => Integer -> a -> BuiltinList a +replicate n0 x = go n0 + where + go :: Integer -> BuiltinList a + go n + | n `B.lessThanEqualsInteger` 0 = B.mkNil + | otherwise = x `BI.mkCons` go (B.subtractInteger n 1) +{-# INLINABLE replicate #-} + +-- | Plutus Tx version of 'Data.List.partition' for 'BuiltinList'. +partition + :: forall a. (MkNil a) + => (a -> Bool) + -> BuiltinList a + -> BuiltinPair (BuiltinList a) (BuiltinList a) +partition p = BI.BuiltinPair . foldr select (B.mkNil, B.mkNil) + where + select :: a -> (BuiltinList a, BuiltinList a) -> (BuiltinList a, BuiltinList a) + select x ~(ts, fs) + | p x = (x `BI.mkCons` ts, fs) + | otherwise = (ts, x `BI.mkCons` fs) +{-# INLINABLE partition #-} + +-- -- | Plutus Tx version of 'Data.List.nubBy' for 'BuiltinList'. +-- nubByFast :: forall a. (MkNil a) => (a -> a -> Bool) -> BuiltinList a -> BuiltinList a +-- nubByFast eq = toBuiltinList (Prelude.nubBy eq (fromBuiltinList)) +-- where +-- go :: BuiltinList a -> BuiltinList a -> BuiltinList a +-- go xs = B.caseList' B.mkNil +-- ( \y ys -> +-- if elemBy eq y xs then +-- go xs ys +-- else +-- y `BI.mkCons` go ys (y `BI.mkCons` xs) +-- ) +-- {-# INLINABLE nubBy #-} +-- | Plutus Tx version of 'Data.List.sort'. +-- sort :: Ord a => BuiltinList a -> BuiltinList a +-- sort = sortBy compare +-- {-# INLINABLE sort #-} + +-- sortBy = undefined +-- -- | Plutus Tx version of 'Data.List.sortBy'. +-- sortBy :: (a -> a -> Ordering) -> BuiltinList a -> BuiltinList a +-- sortBy cmp l = mergeAll (sequences l) +-- where +-- sequences (a:b:xs) +-- | a `cmp` b == GT = descending b BuiltinList a xs +-- | otherwise = ascending b (a:) xs +-- sequences xs = [xs] + +-- descending a as (b:bs) +-- | a `cmp` b == GT = descending b (a:as) bs +-- descending a as bs = (a:as): sequences bs + +-- ascending a as (b:bs) +-- | a `cmp` b /= GT = ascending b (\ys -> as (a:ys)) bs +-- ascending a as bs = let x = as BuiltinList a +-- in x : sequences bs + +-- mergeAll [x] = x +-- mergeAll xs = mergeAll (mergePairs xs) + +-- mergePairs (a:b:xs) = let x = merge a b +-- in x : mergePairs xs +-- mergePairs xs = xs + +-- merge as@(a:as') bs@(b:bs') +-- | a `cmp` b == GT = b:merge as bs' +-- | otherwise = a:merge as' bs +-- merge [] bs = bs +-- merge as [] = as +-- {-# INLINABLE sortBy #-} + + +-- -- append, +-- -- findIndices, +-- -- filter, +-- -- mapMaybe, +-- -- foldMap, +-- -- length, +-- -- mconcat, +-- -- (<|), +-- -- cons, +-- -- nil, +-- -- singleton, +-- -- uncons, +-- -- and, +-- -- or, +-- -- notElem, +-- -- foldr, +-- -- foldl, +-- -- concat, +-- -- concatMap, +-- -- listToMaybe, +-- -- uniqueElement, +-- -- revAppend, +-- -- reverse, +-- -- replicate, +-- -- findIndex, +-- -- unzip, +-- -- zipWith, +-- -- head, +-- -- last, +-- -- tail, +-- -- take, +-- -- drop, +-- -- dropWhile, +-- -- splitAt, +-- -- elemBy, +-- -- nubBy, +-- -- nub, +-- -- partition, +-- -- toBuiltinList, +-- -- fromBuiltinList, +-- -- toSOP, +-- -- fromSOP, diff --git a/plutus-tx/src/PlutusTx/Builtins.hs b/plutus-tx/src/PlutusTx/Builtins.hs index 3914701f173..a97ca15c185 100644 --- a/plutus-tx/src/PlutusTx/Builtins.hs +++ b/plutus-tx/src/PlutusTx/Builtins.hs @@ -485,7 +485,16 @@ pairToPair :: BI.BuiltinPair a b -> (a, b) pairToPair tup = (BI.fst tup, BI.snd tup) {-# INLINE pairToPair #-} +<<<<<<< HEAD sopListToArray :: (HasToOpaque a arep, MkNil arep) => [a] -> BI.BuiltinArray arep +======= +-- | Turn a normal pair into a builtin pair, useful in patterns. +pairFromPair :: (a, b) -> BI.BuiltinPair a b +pairFromPair = BI.BuiltinPair +{-# INLINE pairFromPair #-} + +sopListToArray :: (HasToOpaque a arep, MkNil arep) => [a] -> BI.BuiltinArray arep +>>>>>>> 14e3427f6c (PlutusTx.Data.List & PlutusTx.BuiltinList - Feature Parity) sopListToArray l = BI.listToArray (toOpaque l) {-# INLINEABLE sopListToArray #-} diff --git a/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs b/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs index 4e03115610f..93e26aab5e0 100644 --- a/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs +++ b/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs @@ -274,7 +274,7 @@ class MkNil arep where instance MkNil BuiltinInteger instance MkNil BuiltinBool instance MkNil BuiltinData -instance MkNil (BuiltinPair BuiltinData BuiltinData) +instance (MkNil a, MkNil b) => MkNil (BuiltinPair a b) instance (HasToOpaque a arep, MkNil arep) => HasToOpaque [a] (BuiltinList arep) where toOpaque = goList diff --git a/plutus-tx/src/PlutusTx/ErrorCodes.hs b/plutus-tx/src/PlutusTx/ErrorCodes.hs index daec646fc6c..f94df70f630 100644 --- a/plutus-tx/src/PlutusTx/ErrorCodes.hs +++ b/plutus-tx/src/PlutusTx/ErrorCodes.hs @@ -36,30 +36,32 @@ When writing a new error description please follow existing patterns: -- | All error codes used in the plutus prelude associated with a human-readable description. plutusPreludeErrorCodes :: Map Builtins.BuiltinString String -plutusPreludeErrorCodes = - Map.fromList - [ ("PT1", "TH Generation of Indexed Data Error") - , ("PT2", "PlutusTx.IsData.Class.unsafeFromBuiltinData: Void is not supported") - , ("PT3", "PlutusTx.Ratio: zero denominator") - , ("PT5", "PlutusTx.Prelude.check: input is 'False'") - , ("PT6", "PlutusTx.List.!!: negative index") - , ("PT7", "PlutusTx.List.!!: index too large") - , ("PT8", "PlutusTx.List.head: empty list") - , ("PT9", "PlutusTx.List.tail: empty list") - , ("PT10", "PlutusTx.Enum.().succ: bad argument") - , ("PT11", "PlutusTx.Enum.().pred: bad argument") - , ("PT12", "PlutusTx.Enum.().toEnum: bad argument") - , ("PT13", "PlutusTx.Enum.Bool.succ: bad argument") - , ("PT14", "PlutusTx.Enum.Bool.pred: bad argument") - , ("PT15", "PlutusTx.Enum.Bool.toEnum: bad argument") - , ("PT16", "PlutusTx.Enum.Ordering.succ: bad argument") - , ("PT17", "PlutusTx.Enum.Ordering.pred: bad argument") - , ("PT18", "PlutusTx.Enum.Ordering.toEnum: bad argument") - , ("PT19", "PlutusTx.List.last: empty list") - , ("PT20", "PlutusTx.Ratio.recip: reciprocal of zero") - , ("PT21", "PlutusTx.List.indexBuiltinList: negative index") - , ("PT22", "PlutusTx.List.indexBuiltinList: index too large") - ] +plutusPreludeErrorCodes = Map.fromList + [ ("PT1", "TH Generation of Indexed Data Error") + , ("PT2", "PlutusTx.IsData.Class.unsafeFromBuiltinData: Void is not supported") + , ("PT3", "PlutusTx.Ratio: zero denominator") + , ("PT5", "PlutusTx.Prelude.check: input is 'False'") + , ("PT6", "PlutusTx.List.!!: negative index") + , ("PT7", "PlutusTx.List.!!: index too large") + , ("PT8", "PlutusTx.List.head: empty list") + , ("PT9", "PlutusTx.List.tail: empty list") + , ("PT10", "PlutusTx.Enum.().succ: bad argument") + , ("PT11", "PlutusTx.Enum.().pred: bad argument") + , ("PT12", "PlutusTx.Enum.().toEnum: bad argument") + , ("PT13", "PlutusTx.Enum.Bool.succ: bad argument") + , ("PT14", "PlutusTx.Enum.Bool.pred: bad argument") + , ("PT15", "PlutusTx.Enum.Bool.toEnum: bad argument") + , ("PT16", "PlutusTx.Enum.Ordering.succ: bad argument") + , ("PT17", "PlutusTx.Enum.Ordering.pred: bad argument") + , ("PT18", "PlutusTx.Enum.Ordering.toEnum: bad argument") + , ("PT19", "PlutusTx.List.last: empty list") + , ("PT20", "PlutusTx.Ratio.recip: reciprocal of zero") + , ("PT21", "PlutusTx.BuiltinList.!!: negative index") + , ("PT22", "PlutusTx.BuiltinList.!!: index too large") + , ("PT23", "PlutusTx.BuiltinList.head: empty list") + , ("PT24", "PlutusTx.BuiltinList.tail: empty list") + , ("PT25", "PlutusTx.BuiltinList.last: empty list") + ] -- | The error happens in TH generation of indexed data reconstructCaseError :: Builtins.BuiltinString @@ -156,12 +158,27 @@ reciprocalOfZeroError :: Builtins.BuiltinString reciprocalOfZeroError = "PT20" {-# INLINEABLE reciprocalOfZeroError #-} --- | PlutusTx.List.indexBuiltinList: negative index +-- | PlutusTx.BuiltinList.!!: negative index builtinListNegativeIndexError :: Builtins.BuiltinString builtinListNegativeIndexError = "PT21" {-# INLINEABLE builtinListNegativeIndexError #-} --- | PlutusTx.List.indexBuiltinList: index too large +-- | PlutusTx.BuiltinList.!!: index too large builtinListIndexTooLargeError :: Builtins.BuiltinString builtinListIndexTooLargeError = "PT22" -{-# INLINEABLE builtinListIndexTooLargeError #-} +{-# INLINABLE builtinListIndexTooLargeError #-} + +-- | PlutusTx.BuiltinList.head: empty list +headEmptyBuiltinListError :: Builtins.BuiltinString +headEmptyBuiltinListError = "PT23" +{-# INLINABLE headEmptyBuiltinListError #-} + +-- | PlutusTx.BuiltinList.tail: empty list +tailEmptyBuiltinListError :: Builtins.BuiltinString +tailEmptyBuiltinListError = "PT24" +{-# INLINABLE tailEmptyBuiltinListError #-} + +-- | PlutusTx.BuiltinList.last: empty list +lastEmptyBuiltinListError :: Builtins.BuiltinString +lastEmptyBuiltinListError = "PT25" +{-# INLINABLE lastEmptyBuiltinListError #-} diff --git a/plutus-tx/src/PlutusTx/List.hs b/plutus-tx/src/PlutusTx/List.hs index 2ba3ff8d045..e0f1ade12e7 100644 --- a/plutus-tx/src/PlutusTx/List.hs +++ b/plutus-tx/src/PlutusTx/List.hs @@ -4,48 +4,49 @@ {-# OPTIONS_GHC -fno-omit-interface-pragmas #-} module PlutusTx.List ( - uncons, - null, - length, - map, - and, - or, - any, - all, - elem, - notElem, - find, - filter, - listToMaybe, - uniqueElement, - findIndices, - findIndex, - foldr, - foldl, - revAppend, - reverse, - concat, - concatMap, - zip, - unzip, - (++), - (!!), - head, - last, - tail, - take, - drop, - splitAt, - nub, - nubBy, - zipWith, - dropWhile, - replicate, - partition, - sort, - sortBy, - elemBy, -) where + uncons, + null, + length, + map, + mapMaybe, + and, + or, + any, + all, + elem, + notElem, + find, + filter, + listToMaybe, + uniqueElement, + findIndices, + findIndex, + foldr, + foldl, + revAppend, + reverse, + concat, + concatMap, + zip, + unzip, + (++), + (!!), + head, + last, + tail, + take, + drop, + splitAt, + nub, + nubBy, + zipWith, + dropWhile, + replicate, + partition, + sort, + sortBy, + elemBy, + ) where import PlutusTx.Bool (Bool (..), not, otherwise, (||)) import PlutusTx.Builtins (Integer) @@ -54,7 +55,7 @@ import PlutusTx.Eq (Eq, (/=), (==)) import PlutusTx.ErrorCodes import PlutusTx.Ord (Ord, Ordering (..), compare, (<), (<=)) import PlutusTx.Trace (traceError) -import Prelude (Maybe (..), (.)) +import Prelude (Maybe (..), maybe, (.)) {- HLINT ignore -} @@ -94,6 +95,20 @@ map f = go x : xs -> f x : go xs {-# INLINEABLE map #-} +-- | Plutus Tx version of 'Data.List.mapMaybe'. +-- +-- >>> mapMaybe (\i -> if odd i then Just i else Nothing) [1, 2, 3, 4] +-- [1,3] +-- +mapMaybe :: forall a b. (a -> Maybe b) -> [a] -> [b] +mapMaybe f = go + where + go :: [a] -> [b] + go = \case + [] -> [] + x:xs -> maybe (go xs) (\y -> y:go xs) (f x) +{-# INLINABLE mapMaybe #-} + -- | Returns the conjunction of a list of Bools. and :: [Bool] -> Bool and = \case @@ -247,6 +262,17 @@ findIndex f = go 0 12 -} infixl 9 !! +(!!) :: forall a. [a] -> Integer -> a +_ !! n0 | n0 < 0 = traceError negativeIndexError -- Builtin . lessThan +xs0 !! n0 = go n0 xs0 + where + go :: Integer -> [a] -> a + go _ [] = traceError indexTooLargeError + go n (x : xs) = + if Builtins.equalsInteger n 0 + then x + else go (Builtins.subtractInteger n 1) xs +{-# INLINABLE (!!) #-} (!!) :: forall a. [a] -> Integer -> a _ !! n0 | n0 < 0 = traceError negativeIndexError @@ -378,6 +404,7 @@ nubBy eq l = nubBy' l [] {-# INLINEABLE nubBy #-} -- | Plutus Tx version of 'Data.List.zipWith'. +-- TODO loses elements if the lists are of different lengths zipWith :: forall a b c. (a -> b -> c) -> [a] -> [b] -> [c] zipWith f = go where From c4a0cc6058158cd2b34094296ed49d7e35e24d03 Mon Sep 17 00:00:00 2001 From: zeme Date: Mon, 12 May 2025 11:40:54 +0200 Subject: [PATCH 02/30] wip --- .../BuiltinList/Budget/9.6/cons.budget.golden | 2 + .../BuiltinList/Budget/9.6/cons.eval.golden | 1 + .../BuiltinList/Budget/9.6/cons.pir.golden | 1 + .../BuiltinList/Budget/9.6/cons.uplc.golden | 1 + .../BuiltinList/Budget/9.6/index.pir.golden | 4 +- .../BuiltinList/Budget/9.6/index.uplc.golden | 4 +- .../Budget/9.6/indexNegative.budget.golden | 5 + .../Budget/9.6/indexNegative.eval.golden | 2 + .../Budget/9.6/indexNegative.pir.golden | 37 ++ .../Budget/9.6/indexNegative.uplc.golden | 22 ++ .../Budget/9.6/indexTooLarge.budget.golden | 5 + .../Budget/9.6/indexTooLarge.eval.golden | 2 + .../Budget/9.6/indexTooLarge.pir.golden | 38 ++ .../Budget/9.6/indexTooLarge.uplc.golden | 21 ++ .../BuiltinList/Budget/9.6/map.pir.golden | 4 +- .../BuiltinList/Budget/9.6/map.uplc.golden | 26 +- .../Budget/9.6/unconsJust.budget.golden | 2 + .../Budget/9.6/unconsJust.eval.golden | 1 + .../Budget/9.6/unconsJust.pir.golden | 25 ++ .../Budget/9.6/unconsJust.uplc.golden | 10 + .../Budget/9.6/unconsNothing.budget.golden | 2 + .../Budget/9.6/unconsNothing.eval.golden | 1 + .../Budget/9.6/unconsNothing.pir.golden | 25 ++ .../Budget/9.6/unconsNothing.uplc.golden | 10 + .../test/BuiltinList/Budget/Spec.hs | 152 +++++++- plutus-tx/src/PlutusTx/BuiltinList.hs | 344 +++++++++--------- 26 files changed, 554 insertions(+), 193 deletions(-) create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.uplc.golden diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.budget.golden new file mode 100644 index 00000000000..bf007a20f49 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.budget.golden @@ -0,0 +1,2 @@ +({cpu: 216462 +| mem: 1032}) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden new file mode 100644 index 00000000000..d2d86960ed6 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden @@ -0,0 +1 @@ +(con (list integer) [0,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.pir.golden new file mode 100644 index 00000000000..ed3cc42f4cf --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.pir.golden @@ -0,0 +1 @@ +\(xs : list integer) -> mkCons {integer} 0 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.uplc.golden new file mode 100644 index 00000000000..f4626f1cdc2 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.uplc.golden @@ -0,0 +1 @@ +(program 1.1.0 (\xs -> force mkCons 0 xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden index 4017df54d7f..301600984c1 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden @@ -24,7 +24,7 @@ letrec !x : Unit = trace {Unit} "PT22" Unit in error {Unit -> integer}) - (\(x : integer) (xs : list integer) (ds : Unit) (eta : Unit) -> + (\(x : integer) (xs : list integer) (ds : Unit) (ds : Unit) -> Bool_match (ifThenElse {Bool} (equalsInteger 0 i) True False) {all dead. integer} @@ -35,4 +35,4 @@ letrec Unit Unit in -\(v : list integer) -> go v 5 \ No newline at end of file +\(xs : list integer) -> go xs 5 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden index fc263ab78aa..cb885ad5218 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden @@ -1,6 +1,6 @@ (program 1.1.0 - ((\go v -> go v 5) + ((\go xs -> go xs 5) ((\s -> s s) (\s xs i -> force @@ -9,7 +9,7 @@ (delay (\ds -> (\x -> error) (force trace "PT22" (constr 0 [])))) (delay - ((\x xs ds eta -> + ((\x xs ds ds -> force (force ifThenElse (equalsInteger 0 i) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.budget.golden new file mode 100644 index 00000000000..6fd7da844c9 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.budget.golden @@ -0,0 +1,5 @@ +An error has occurred: +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. +Final budget: ({cpu: 59598 +| mem: 132}) +Logs: PT21 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.eval.golden new file mode 100644 index 00000000000..f2c04fe10eb --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.eval.golden @@ -0,0 +1,2 @@ +An error has occurred: +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.pir.golden new file mode 100644 index 00000000000..d63dd6006a7 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.pir.golden @@ -0,0 +1,37 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool + data Unit | Unit_match where + Unit : Unit + !traceError : all a. string -> a + = /\a -> + \(str : string) -> let !x : Unit = trace {Unit} str Unit in error {a} +in +letrec + !go : list integer -> integer -> integer + = \(xs : list integer) (i : integer) -> + (let + r = Unit -> Unit -> integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + (\(ds : Unit) -> traceError {Unit -> integer} "PT22") + (\(x : integer) (xs : list integer) (ds : Unit) (ds : Unit) -> + Bool_match + (ifThenElse {Bool} (equalsInteger 0 i) True False) + {all dead. integer} + (/\dead -> x) + (/\dead -> go xs (subtractInteger i 1)) + {all dead. dead}) + xs + Unit + Unit +in +\(xs : list integer) -> traceError {integer} "PT21" \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden new file mode 100644 index 00000000000..66da482c999 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden @@ -0,0 +1,22 @@ +(program + 1.1.0 + ((\traceError -> + (\go xs -> traceError "PT21") + ((\s -> s s) + (\s xs i -> + force + (force (force chooseList) + xs + (delay (\ds -> traceError "PT22")) + (delay + ((\x xs ds ds -> + force + (force ifThenElse + (equalsInteger 0 i) + (delay x) + (delay (s s xs (subtractInteger i 1))))) + (force headList xs) + (force tailList xs)))) + (constr 0 []) + (constr 0 [])))) + (\str -> (\x -> error) (force trace str (constr 0 []))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.budget.golden new file mode 100644 index 00000000000..04ff5940af6 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.budget.golden @@ -0,0 +1,5 @@ +An error has occurred: +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. +Final budget: ({cpu: 11866562 +| mem: 41164}) +Logs: PT22 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.eval.golden new file mode 100644 index 00000000000..f2c04fe10eb --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.eval.golden @@ -0,0 +1,2 @@ +An error has occurred: +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.pir.golden new file mode 100644 index 00000000000..c099fd4aeb8 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.pir.golden @@ -0,0 +1,38 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool + data Unit | Unit_match where + Unit : Unit +in +letrec + !go : list integer -> integer -> integer + = \(xs : list integer) (i : integer) -> + (let + r = Unit -> Unit -> integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + (\(ds : Unit) -> + let + !x : Unit = trace {Unit} "PT22" Unit + in + error {Unit -> integer}) + (\(x : integer) (xs : list integer) (ds : Unit) (ds : Unit) -> + Bool_match + (ifThenElse {Bool} (equalsInteger 0 i) True False) + {all dead. integer} + (/\dead -> x) + (/\dead -> go xs (subtractInteger i 1)) + {all dead. dead}) + xs + Unit + Unit +in +\(xs : list integer) -> go xs 10 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden new file mode 100644 index 00000000000..ce84f14ce5e --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden @@ -0,0 +1,21 @@ +(program + 1.1.0 + ((\go xs -> go xs 10) + ((\s -> s s) + (\s xs i -> + force + (force (force chooseList) + xs + (delay + (\ds -> (\x -> error) (force trace "PT22" (constr 0 [])))) + (delay + ((\x xs ds ds -> + force + (force ifThenElse + (equalsInteger 0 i) + (delay x) + (delay (s s xs (subtractInteger i 1))))) + (force headList xs) + (force tailList xs)))) + (constr 0 []) + (constr 0 []))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.pir.golden index dd4133ae5f5..d5fd356b0b5 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.pir.golden @@ -12,7 +12,7 @@ letrec (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) {r}) [] - (\(x : integer) (x : list integer) -> - mkCons {integer} (addInteger 1 x) (go x)) + (\(x : integer) (xs : list integer) -> + mkCons {integer} (addInteger 1 x) (go xs)) in go \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden index 14981625938..5dd2d08364f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden @@ -1,12 +1,18 @@ (program 1.1.0 - ((\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay []) - (delay - ((\x -> - force mkCons (addInteger 1 (force headList xs)) (s s x)) - (force tailList xs))))))) \ No newline at end of file + (force + ((\s -> s s) + (\s arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay []) + (delay + ((\xs -> + force mkCons + (addInteger 1 (force headList xs)) + (force (s s (delay (\x -> x))) xs)) + (force tailList xs)))))) + (delay (\x -> x))))) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.budget.golden new file mode 100644 index 00000000000..59608b99532 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.budget.golden @@ -0,0 +1,2 @@ +({cpu: 665907 +| mem: 2496}) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden new file mode 100644 index 00000000000..ceae63c9d5a --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden @@ -0,0 +1 @@ +(constr 0 (constr 0 (con integer 1) (con (list integer) [2,3,4,5,6,7,8,9,10]))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.pir.golden new file mode 100644 index 00000000000..132ec1c1aa7 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.pir.golden @@ -0,0 +1,25 @@ +let + data (Tuple2 :: * -> * -> *) a b | Tuple2_match where + Tuple2 : a -> b -> Tuple2 a b + data (Maybe :: * -> *) a | Maybe_match where + Just : a -> Maybe a + Nothing : Maybe a +in +\(xs : list integer) -> + (let + r = Maybe (Tuple2 integer (list integer)) + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + (Nothing {Tuple2 integer (list integer)}) + (\(h : integer) (t : list integer) -> + Just + {Tuple2 integer (list integer)} + (Tuple2 {integer} {list integer} h t)) + xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.uplc.golden new file mode 100644 index 00000000000..a4563742bf5 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.uplc.golden @@ -0,0 +1,10 @@ +(program + 1.1.0 + (\xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + (constr 0 + [(constr 0 [(force headList xs), (force tailList xs)])]))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.budget.golden new file mode 100644 index 00000000000..8f2c634b339 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.budget.golden @@ -0,0 +1,2 @@ +({cpu: 357094 +| mem: 1532}) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden new file mode 100644 index 00000000000..f217693e82c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden @@ -0,0 +1 @@ +(constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.pir.golden new file mode 100644 index 00000000000..f9c38536296 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.pir.golden @@ -0,0 +1,25 @@ +let + data (Tuple2 :: * -> * -> *) a b | Tuple2_match where + Tuple2 : a -> b -> Tuple2 a b + data (Maybe :: * -> *) a | Maybe_match where + Just : a -> Maybe a + Nothing : Maybe a +in +\(ds : list integer) -> + (let + r = Maybe (Tuple2 integer (list integer)) + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + (Nothing {Tuple2 integer (list integer)}) + (\(h : integer) (t : list integer) -> + Just + {Tuple2 integer (list integer)} + (Tuple2 {integer} {list integer} h t)) + [] \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.uplc.golden new file mode 100644 index 00000000000..1facba8acf0 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.uplc.golden @@ -0,0 +1,10 @@ +(program + 1.1.0 + (\ds -> + force + (force (force chooseList) + [] + (delay (constr 1 [])) + (delay + (constr 0 + [(constr 0 [(force headList []), (force tailList [])])]))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index d9435fd0a54..ad2a5afb8d0 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -5,6 +5,7 @@ module BuiltinList.Budget.Spec where import Prelude hiding (all, any, elem, map) import System.FilePath +import Test.Tasty (TestName) import Test.Tasty.Extras import PlutusTx.BuiltinList qualified as L @@ -25,8 +26,22 @@ tests = , goldenBundle "any" any (any `unsafeApplyCode` l) , goldenBundle "all" all (all `unsafeApplyCode` l) , goldenBundle "index" index (index `unsafeApplyCode` l) + , goldenBundle "indexNegative" (index `unsafeApplyCode` indexNegative l) + , goldenBundle "indexTooLarge" (index `unsafeApplyCode` indexTooLarge l) + , goldenBundle "cons" (index `unsafeApplyCode` cons l) + , goldenBundle "unconsJust" (index `unsafeApplyCode` unconsJust l) + , goldenBundle "unconsNothing" (index `unsafeApplyCode` unconsNothing l) ] + +-- goldenBundle :: TestName -> _ -> _ -> TestNested +goldenBundle name f x = do + goldenPirReadable name f + goldenUPlcReadable name f + goldenEvalCekCatch name [f `unsafeApplyCode` x] + goldenBudget name (f `unsafeApplyCode` x) + + map :: CompiledCode (P.BuiltinList Integer -> P.BuiltinList Integer) map = $$(compile [||L.map (P.+ 1)||]) @@ -43,7 +58,142 @@ all :: CompiledCode (P.BuiltinList Integer -> (Bool, Bool)) all = $$(compile [||\xs -> (L.all (P.>= 8) xs, L.all (P.>= 0) xs)||]) index :: CompiledCode (P.BuiltinList Integer -> Integer) -index = $$(compile [||(L.!! 5)||]) +index = $$(compile [||\xs -> xs L.!! 5 ||]) + +indexNegative :: CompiledCode (P.BuiltinList Integer -> Integer) +indexNegative = $$(compile [||\xs -> xs L.!! (-1) ||]) + +indexTooLarge :: CompiledCode (P.BuiltinList Integer -> Integer) +indexTooLarge = $$(compile [||\xs -> xs L.!! 10 ||]) + +cons :: CompiledCode (P.BuiltinList Integer -> P.BuiltinList Integer) +cons = $$(compile [||\xs -> L.cons 0 xs||]) + +unconsJust :: CompiledCode (P.BuiltinList Integer -> Maybe (Integer, P.BuiltinList Integer)) +unconsJust = $$(compile [||\xs -> L.uncons xs||]) + +unconsNothing :: CompiledCode (P.BuiltinList Integer -> Maybe (Integer, P.BuiltinList Integer)) +unconsNothing = $$(compile [||\_ -> L.uncons L.empty||]) + +-- empty :: CompiledCode (P.BuiltinList Integer -> a) +-- empty = $$(compile [|| L.empty ||]) + +-- singleton :: CompiledCode (P.BuiltinList Integer -> a) +-- singleton = $$(compile [|| L.singleton ||]) + +-- null :: CompiledCode (P.BuiltinList Integer -> a) +-- null = $$(compile [|| L.null ||]) + +-- caseList' :: CompiledCode (P.BuiltinList Integer -> a) +-- caseList' = $$(compile [|| L.caseList' ||]) + +-- (++) :: CompiledCode (P.BuiltinList Integer -> a) +-- (++) = $$(compile [|| L.(++) ||]) + +-- (<|) :: CompiledCode (P.BuiltinList Integer -> a) +-- (<|) = $$(compile [|| L.(<|) ||]) + +-- append :: CompiledCode (P.BuiltinList Integer -> a) +-- append = $$(compile [|| L.append ||]) + +-- findIndices :: CompiledCode (P.BuiltinList Integer -> a) +-- findIndices = $$(compile [|| L.findIndices ||]) + +-- filter :: CompiledCode (P.BuiltinList Integer -> a) +-- filter = $$(compile [|| L.filter ||]) + +-- mapMaybe :: CompiledCode (P.BuiltinList Integer -> a) +-- mapMaybe = $$(compile [|| L.mapMaybe ||]) + +-- length :: CompiledCode (P.BuiltinList Integer -> a) +-- length = $$(compile [|| L.length ||]) + +-- and :: CompiledCode (P.BuiltinList Integer -> a) +-- and = $$(compile [|| L.and ||]) + +-- or :: CompiledCode (P.BuiltinList Integer -> a) +-- or = $$(compile [|| L.or ||]) + +-- notElem :: CompiledCode (P.BuiltinList Integer -> a) +-- notElem = $$(compile [|| L.notElem ||]) + +-- foldr :: CompiledCode (P.BuiltinList Integer -> a) +-- foldr = $$(compile [|| L.foldr ||]) + +-- foldl :: CompiledCode (P.BuiltinList Integer -> a) +-- foldl = $$(compile [|| L.foldl ||]) + +-- concat :: CompiledCode (P.BuiltinList Integer -> a) +-- concat = $$(compile [|| L.concat ||]) + +-- concatMap :: CompiledCode (P.BuiltinList Integer -> a) +-- concatMap = $$(compile [|| L.concatMap ||]) + +-- listToMaybe :: CompiledCode (P.BuiltinList Integer -> a) +-- listToMaybe = $$(compile [|| L.listToMaybe ||]) + +-- uniqueElement :: CompiledCode (P.BuiltinList Integer -> a) +-- uniqueElement = $$(compile [|| L.uniqueElement ||]) + +-- revAppend :: CompiledCode (P.BuiltinList Integer -> a) +-- revAppend = $$(compile [|| L.revAppend ||]) + +-- reverse :: CompiledCode (P.BuiltinList Integer -> a) +-- reverse = $$(compile [|| L.reverse ||]) + +-- replicate :: CompiledCode (P.BuiltinList Integer -> a) +-- replicate = $$(compile [|| L.replicate ||]) + +-- findIndex :: CompiledCode (P.BuiltinList Integer -> a) +-- findIndex = $$(compile [|| L.findIndex ||]) + +-- unzip :: CompiledCode (P.BuiltinList Integer -> a) +-- unzip = $$(compile [|| L.unzip ||]) + +-- zip :: CompiledCode (P.BuiltinList Integer -> a) +-- zip = $$(compile [|| L.zip ||]) + +-- zipWith :: CompiledCode (P.BuiltinList Integer -> a) +-- zipWith = $$(compile [|| L.zipWith ||]) + +-- head :: CompiledCode (P.BuiltinList Integer -> a) +-- head = $$(compile [|| L.head ||]) + +-- last :: CompiledCode (P.BuiltinList Integer -> a) +-- last = $$(compile [|| L.last ||]) + +-- tail :: CompiledCode (P.BuiltinList Integer -> a) +-- tail = $$(compile [|| L.tail ||]) + +-- take :: CompiledCode (P.BuiltinList Integer -> a) +-- take = $$(compile [|| L.take ||]) + +-- drop :: CompiledCode (P.BuiltinList Integer -> a) +-- drop = $$(compile [|| L.drop ||]) + +-- dropWhile :: CompiledCode (P.BuiltinList Integer -> a) +-- dropWhile = $$(compile [|| L.dropWhile ||]) + +-- splitAt :: CompiledCode (P.BuiltinList Integer -> a) +-- splitAt = $$(compile [|| L.splitAt ||]) + +-- elemBy :: CompiledCode (P.BuiltinList Integer -> a) +-- elemBy = $$(compile [|| L.elemBy ||]) + +-- partition :: CompiledCode (P.BuiltinList Integer -> a) +-- partition = $$(compile [|| L.partition ||]) + +-- sort :: CompiledCode (P.BuiltinList Integer -> a) +-- sort = $$(compile [|| L.sort ||]) + +-- sortBy :: CompiledCode (P.BuiltinList Integer -> a) +-- sortBy = $$(compile [|| L.sortBy ||]) + +-- nub :: CompiledCode (P.BuiltinList Integer -> a) +-- nub = $$(compile [|| L.nub ||]) + +-- nubBy :: CompiledCode (P.BuiltinList Integer -> a) +-- nubBy = $$(compile [|| L.nubBy ||]) l :: CompiledCode (P.BuiltinList Integer) l = liftCodeDef $ toBuiltin ([1 .. 10] :: [Integer]) diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index c369b3e60a4..21b52d1f1af 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -3,20 +3,58 @@ -- | Functions operating on `BuiltinList`. module PlutusTx.BuiltinList ( BuiltinList, - B.caseList, - B.caseList', - B.null, - B.uncons, + cons, + uncons, + empty, + singleton, + null, + caseList', + caseList, map, elem, find, any, all, (!!), -) -where - -import Prelude (Bool (..), Integer, Maybe (..), const, curry, id, not, otherwise, undefined, (.)) + (++), + (<|), + append, + findIndices, + filter, + mapMaybe, + length, + and, + or, + notElem, + foldr, + foldl, + concat, + concatMap, + listToMaybe, + uniqueElement, + revAppend, + reverse, + replicate, + findIndex, + unzip, + zip, + zipWith, + head, + last, + tail, + take, + drop, + dropWhile, + splitAt, + elemBy, + partition, + sort, + sortBy, + nub, + nubBy +) where + +import Prelude (Bool (..), Integer, Maybe (..), curry, id, not, otherwise, undefined, (.)) import PlutusTx.Builtins qualified as B import PlutusTx.Builtins.HasOpaque @@ -27,13 +65,51 @@ import PlutusTx.ErrorCodes import PlutusTx.Ord import PlutusTx.Trace (traceError) +-- | Plutus Tx version of 'Data.List.:' for 'BuiltinList'. +cons :: forall a. a -> BuiltinList a -> BuiltinList a +cons = BI.mkCons +{-# INLINEABLE cons #-} + +-- | Infix version of 'cons'. +infixr 5 <| +(<|) :: forall a. a -> BuiltinList a -> BuiltinList a +(<|) = cons +{-# INLINEABLE (<|) #-} + +-- | Plutus Tx version of 'Data.List.uncons' for 'BuiltinList'. +uncons :: forall a. BuiltinList a -> Maybe (a, BuiltinList a) +uncons = B.uncons +{-# INLINEABLE uncons #-} + +-- | Plutus Tx version of '[]' for 'BuiltinList'. +empty :: forall a. (MkNil a) => BuiltinList a +empty = B.mkNil +{-# INLINEABLE empty #-} + +-- | Plutus Tx version of 'Data.List.null' for 'BuiltinList'. +null :: forall a. BuiltinList a -> Bool +null = B.null +{-# INLINEABLE null #-} + +-- | Make a list with one element. +singleton :: forall a. (MkNil a) => a -> BuiltinList a +singleton x = x <| empty +{-# INLINEABLE singleton #-} + +caseList' :: forall a r. r -> (a -> BuiltinList a -> r) -> BuiltinList a -> r +caseList' = B.caseList' +{-# INLINABLE caseList' #-} + +caseList :: forall a r. (() -> r) -> (a -> BuiltinList a -> r) -> BuiltinList a -> r +caseList = B.caseList +{-# INLINABLE caseList #-} -- | Plutus Tx version of 'Data.List.map' for 'BuiltinList'. map :: forall a b. (MkNil b) => (a -> b) -> BuiltinList a -> BuiltinList b map f = go where go :: BuiltinList a -> BuiltinList b - go = B.caseList' B.mkNil ( \x xs -> f x `BI.mkCons` go xs ) + go = caseList' empty ( \x xs -> f x <| go xs ) {-# INLINEABLE map #-} -- | Plutus Tx version of 'Data.List.mapMaybe' for 'BuiltinList'. @@ -41,10 +117,10 @@ mapMaybe :: forall a b. (MkNil b) => (a -> Maybe b) -> BuiltinList a -> BuiltinL mapMaybe f = go where go :: BuiltinList a -> BuiltinList b - go = B.caseList' B.mkNil + go = caseList' empty ( \x xs -> case f x of Nothing -> go xs - Just y -> y `BI.mkCons` go xs + Just y -> y <| go xs ) {-# INLINEABLE mapMaybe #-} @@ -53,7 +129,7 @@ elem :: forall a. (Eq a) => a -> BuiltinList a -> Bool elem a = go where go :: BuiltinList a -> Bool - go = B.caseList' False ( \x xs -> if a == x then True else go xs ) + go = caseList' False ( \x xs -> if a == x then True else go xs ) {-# INLINEABLE elem #-} -- | Returns the leftmost element matching the predicate, or `Nothing` if there's no such element. @@ -61,7 +137,7 @@ find :: forall a. (a -> Bool) -> BuiltinList a -> Maybe a find p = go where go :: BuiltinList a -> Maybe a - go = B.caseList' Nothing ( \x xs -> if p x then Just x else go xs ) + go = caseList' Nothing ( \x xs -> if p x then Just x else go xs ) {-# INLINEABLE find #-} -- | Determines whether any element of the structure satisfies the predicate. @@ -69,7 +145,7 @@ any :: forall a. (a -> Bool) -> BuiltinList a -> Bool any p = go where go :: BuiltinList a -> Bool - go = B.caseList' False ( \x xs -> if p x then True else go xs ) + go = caseList' False ( \x xs -> if p x then True else go xs ) {-# INLINEABLE any #-} -- | Determines whether all elements of the list satisfy the predicate. @@ -77,7 +153,7 @@ all :: forall a. (a -> Bool) -> BuiltinList a -> Bool all p = go where go :: BuiltinList a -> Bool - go = B.caseList' True ( \x xs -> if p x then go xs else False ) + go = caseList' True ( \x xs -> if p x then go xs else False ) {-# INLINEABLE all #-} -- | Plutus Tx version of '(GHC.List.!!)' for 'BuiltinList'. @@ -86,16 +162,16 @@ infixl 9 !! (!!) :: forall a. BuiltinList a -> Integer -> a (!!) xs0 i0 | i0 `B.lessThanInteger` 0 = traceError builtinListNegativeIndexError - | otherwise = go i0 xs0 + | otherwise = go xs0 i0 where - go :: Integer -> BuiltinList a -> a - go i = B.caseList' - (traceError builtinListIndexTooLargeError) - ( \y ys -> + go :: BuiltinList a -> Integer -> a + go xs i = caseList + ( \_ -> traceError builtinListIndexTooLargeError ) + ( \y ys _ -> if i `B.equalsInteger` 0 then y - else go (B.subtractInteger i 1) ys - ) + else go ys (B.subtractInteger i 1) + ) xs () {-# INLINEABLE (!!) #-} -- TODO add tests and changelog for Data.List @@ -124,7 +200,7 @@ foldr :: forall a b. (a -> b -> b) -> b -> BuiltinList a -> b foldr f acc = go where go :: BuiltinList a -> b - go = B.caseList' acc ( \x xs -> f x (go xs) ) + go = caseList' acc ( \x xs -> f x (go xs) ) {-# INLINABLE foldr #-} -- | Plutus Tx velsion of 'Data.List.foldl' for 'BuiltinList'. @@ -132,39 +208,44 @@ foldl :: forall a b. (b -> a -> b) -> b -> BuiltinList a -> b foldl f = go where go :: b -> BuiltinList a -> b - go acc = B.caseList' acc ( \x xs -> go (f acc x) xs ) + go acc = caseList' acc ( \x xs -> go (f acc x) xs ) {-# INLINABLE foldl #-} -- | Plutus Tx version of '(Data.List.++)' for 'BuiltinList'. infixr 5 ++ (++) :: forall a. BuiltinList a -> BuiltinList a -> BuiltinList a -(++) l r = foldr BI.mkCons r l +(++) l r = foldr (<|) r l {-# INLINABLE (++) #-} +-- | Plutus Tx version of '(Data.List.append)' for 'BuiltinList'. +append :: forall a. BuiltinList a -> BuiltinList a -> BuiltinList a +append = (++) +{-# INLINABLE append #-} + -- | Plutus Tx version of 'Data.List.concat' for 'BuiltinList'. concat :: forall a. (MkNil a) => BuiltinList (BuiltinList a) -> BuiltinList a -concat = foldr (++) B.mkNil +concat = foldr (++) empty {-# INLINABLE concat #-} -- | Plutus Tx version of 'Data.List.concatMap' for 'BuiltinList'. concatMap :: forall a b. (MkNil b) => (a -> BuiltinList b) -> BuiltinList a -> BuiltinList b -concatMap f = foldr ( \x ys -> f x ++ ys ) B.mkNil +concatMap f = foldr ( \x ys -> f x ++ ys ) empty {-# INLINABLE concatMap #-} -- | Plutus Tx version of 'Data.List.filter' for 'BuiltinList'. filter :: forall a. (MkNil a) => (a -> Bool) -> BuiltinList a -> BuiltinList a -filter p = foldr ( \x xs -> if p x then x `BI.mkCons` xs else xs ) B.mkNil +filter p = foldr ( \x xs -> if p x then x <| xs else xs ) empty {-# INLINABLE filter #-} -- | Plutus Tx version of 'Data.List.listToMaybe' for 'BuiltinList'. listToMaybe :: forall a. BuiltinList a -> Maybe a -listToMaybe = BI.caseList' Nothing ( \x _ -> Just x ) +listToMaybe = caseList' Nothing ( \x _ -> Just x ) {-# INLINABLE listToMaybe #-} -- | Return the element in the list, if there is precisely one. uniqueElement :: forall a. BuiltinList a -> Maybe a -uniqueElement = BI.caseList' Nothing - ( \x -> BI.caseList' (Just x) ( \_ _ -> Nothing ) +uniqueElement = caseList' Nothing + ( \x -> caseList' (Just x) ( \_ _ -> Nothing ) ) {-# INLINABLE uniqueElement #-} @@ -173,10 +254,10 @@ findIndices :: forall a. (a -> Bool) -> BuiltinList a -> BuiltinList Integer findIndices p = go 0 where go :: Integer -> BuiltinList a -> BuiltinList Integer - go i = BI.caseList' B.mkNil + go i = caseList' empty ( \x xs -> let indices = go (B.addInteger i 1) xs - in if p x then BI.mkCons i indices else indices + in if p x then i <| indices else indices ) {-# INLINABLE findIndices #-} @@ -185,7 +266,7 @@ findIndex :: forall a. (a -> Bool) -> BuiltinList a -> Maybe Integer findIndex f = go 0 where go :: Integer -> BuiltinList a -> Maybe Integer - go i = BI.caseList' Nothing + go i = caseList' Nothing ( \x xs -> if f x then Just i else go (B.addInteger i 1) xs ) {-# INLINABLE findIndex #-} @@ -195,12 +276,12 @@ findIndex f = go 0 -- -- > revAppend xs ys === reverse xs ++ ys revAppend :: forall a. BuiltinList a -> BuiltinList a -> BuiltinList a -revAppend l r = BI.caseList' r ( \x xs -> revAppend xs (x `BI.mkCons` r) ) l +revAppend l r = caseList' r ( \x xs -> revAppend xs (x <| r) ) l {-# INLINABLE revAppend #-} -- | Plutus Tx version of 'Data.List.reverse' for 'BuiltinList'. reverse :: forall a. (MkNil a) => BuiltinList a -> BuiltinList a -reverse xs = revAppend xs B.mkNil +reverse xs = revAppend xs empty {-# INLINABLE reverse #-} -- | Plutus Tx version of 'Data.List.zip' for 'BuiltinList'. @@ -217,73 +298,69 @@ unzip :: forall a b. (MkNil a, MkNil b) => BuiltinList (BuiltinPair a b) -> BuiltinPair (BuiltinList a) (BuiltinList b) -unzip = B.caseList' emptyPair +unzip = caseList' emptyPair ( \p l -> do let BI.BuiltinPair (x, y) = p let BI.BuiltinPair (xs', ys') = unzip l - BI.BuiltinPair (x `BI.mkCons` xs', y `BI.mkCons` ys') + BI.BuiltinPair (x <| xs', y <| ys') ) where emptyPair :: BuiltinPair (BuiltinList a) (BuiltinList b) - emptyPair = BI.BuiltinPair (B.mkNil, B.mkNil) + emptyPair = BI.BuiltinPair (empty, empty) {-# INLINABLE unzip #-} -- | Plutus Tx version of 'Data.List.head' for 'BuiltinList'. head :: forall a. BuiltinList a -> a -head = B.caseList' (traceError headEmptyBuiltinListError) ( \x _ -> x ) +head = caseList + ( \_ -> traceError headEmptyBuiltinListError ) + ( \x _ -> x ) {-# INLINABLE head #-} -- | Plutus Tx version of 'Data.List.last' for 'BuiltinList'. last :: forall a. BuiltinList a -> a -last = B.caseList' (traceError lastEmptyBuiltinListError) - ( \x -> B.caseList' x ( \_ -> last ) +last = caseList + ( \_ -> traceError lastEmptyBuiltinListError ) + ( \x -> caseList' x ( \_ -> last ) ) {-# INLINABLE last #-} -- | Plutus Tx version of 'Data.List.tail' for 'BuiltinList'. tail :: forall a. BuiltinList a -> BuiltinList a -tail = B.caseList' (traceError lastEmptyBuiltinListError) ( \_ xs -> xs ) +tail = caseList ( \_ -> traceError lastEmptyBuiltinListError ) ( \_ xs -> xs ) {-# INLINABLE tail #-} -- | Plutus Tx version of 'Data.List.take' for 'BuiltinList'. take :: forall a. (MkNil a) => Integer -> BuiltinList a -> BuiltinList a take n l - | n `B.lessThanInteger` 0 = B.mkNil - | otherwise = B.caseList' B.mkNil - ( \x xs -> x `BI.mkCons` take (B.subtractInteger n 1) xs + | n `B.lessThanEqualsInteger` 0 = empty + | otherwise = caseList' empty + ( \x xs -> x <| take (B.subtractInteger n 1) xs ) l {-# INLINABLE take #-} -- | Plutus Tx version of 'Data.List.drop' for 'BuiltinList'. drop :: forall a. (MkNil a) => Integer -> BuiltinList a -> BuiltinList a drop n l - | n `B.lessThanEqualsInteger` 0 = B.mkNil - | otherwise = B.caseList' B.mkNil + | n `B.lessThanEqualsInteger` 0 = empty + | otherwise = caseList' empty ( \_ xs -> drop (B.subtractInteger n 1) xs ) l {-# INLINABLE drop #-} --- -- | Plutus Tx version of 'Data.List.splitAt'. --- splitAt :: forall a. Integer -> BuiltinList a -> BuiltinPair (BuiltinList a) (BuiltinList a) --- splitAt n xs --- | n `B.lessThanEqualInteger` 0 = BI.BuiltinPair (B.mkNil, xs) --- | otherwise = go n xs --- where --- go :: Integer -> BuiltinList a -> (BuiltinList a, BuiltinList a) --- go m = B.caseList' (BI.BuiltinPair (B.mkNil, B.mkNil)) (\x xs -> --- if m `B.equalsInteger` 0 --- then BI.BuiltinPair (B.mkNil, xs) --- else let BI.BuiltinPair (zs, ws) = go (B.subtractInteger m 1) xs --- in BI.BuiltinPair (BI.mkCons x zs, ws) --- ) - - --- [] = ([], []) --- go m (y:ys) --- | m == 1 = ([y], ys) --- | otherwise = case go (Builtins.subtractInteger m 1) ys of --- (zs, ws) -> (y:zs, ws) --- {-# INLINABLE splitAt #-} +-- | Plutus Tx version of 'Data.List.splitAt' for 'BuiltinList'. +splitAt + :: forall a. (MkNil a) + => Integer + -> BuiltinList a + -> BuiltinPair (BuiltinList a) (BuiltinList a) +splitAt n xs + | n `B.lessThanEqualsInteger` 0 = BI.BuiltinPair (empty, xs) + | B.null xs = BI.BuiltinPair (empty, empty) + | otherwise = do + let (x, xs') = B.unsafeUncons xs + let BI.BuiltinPair (xs'', xs''') = splitAt (n `B.subtractInteger` 1) xs' + BI.BuiltinPair (x <| xs'', xs''') +{-# INLINABLE splitAt #-} -- | Plutus Tx version of 'Data.List.nub' for 'BuiltinList'. nub :: forall a. (Eq a, MkNil a) => BuiltinList a -> BuiltinList a @@ -295,19 +372,19 @@ elemBy :: forall a. (a -> a -> Bool) -> a -> BuiltinList a -> Bool elemBy eq y = go where go :: BuiltinList a -> Bool - go = B.caseList' False ( \x xs -> if eq x y then True else go xs ) + go = caseList' False ( \x xs -> if eq x y then True else go xs ) {-# INLINABLE elemBy #-} -- | Plutus Tx version of 'Data.List.nubBy' for 'BuiltinList'. nubBy :: forall a. (MkNil a) => (a -> a -> Bool) -> BuiltinList a -> BuiltinList a -nubBy eq = go B.mkNil +nubBy eq = go empty where go :: BuiltinList a -> BuiltinList a -> BuiltinList a - go xs = B.caseList' B.mkNil + go xs = caseList' empty ( \y ys -> if elemBy eq y xs then go xs ys - else y `BI.mkCons` go ys (y `BI.mkCons` xs) + else y <| go ys (y <| xs) ) {-# INLINABLE nubBy #-} @@ -322,10 +399,10 @@ zipWith f = go where go :: BuiltinList a -> BuiltinList b -> BuiltinList c go xs ys = - B.caseList' B.mkNil + caseList' empty ( \x xs' -> - B.caseList' B.mkNil - ( \y ys' -> f x y `BI.mkCons` go xs' ys' + caseList' empty + ( \y ys' -> f x y <| go xs' ys' ) ys ) xs {-# INLINABLE zipWith #-} @@ -335,7 +412,7 @@ dropWhile :: forall a. (MkNil a) => (a -> Bool) -> BuiltinList a -> BuiltinList dropWhile p = go where go :: BuiltinList a -> BuiltinList a - go xs = B.caseList' B.mkNil ( \x xs' -> if p x then go xs' else xs ) xs + go xs = caseList' empty ( \x xs' -> if p x then go xs' else xs ) xs {-# INLINABLE dropWhile #-} -- | Plutus Tx version of 'Data.List.replicate' for 'BuiltinList'. @@ -344,8 +421,8 @@ replicate n0 x = go n0 where go :: Integer -> BuiltinList a go n - | n `B.lessThanEqualsInteger` 0 = B.mkNil - | otherwise = x `BI.mkCons` go (B.subtractInteger n 1) + | n `B.lessThanEqualsInteger` 0 = empty + | otherwise = x <| go (B.subtractInteger n 1) {-# INLINABLE replicate #-} -- | Plutus Tx version of 'Data.List.partition' for 'BuiltinList'. @@ -354,105 +431,20 @@ partition => (a -> Bool) -> BuiltinList a -> BuiltinPair (BuiltinList a) (BuiltinList a) -partition p = BI.BuiltinPair . foldr select (B.mkNil, B.mkNil) +partition p = BI.BuiltinPair . foldr select (empty, empty) where select :: a -> (BuiltinList a, BuiltinList a) -> (BuiltinList a, BuiltinList a) select x ~(ts, fs) - | p x = (x `BI.mkCons` ts, fs) - | otherwise = (ts, x `BI.mkCons` fs) + | p x = (x <| ts, fs) + | otherwise = (ts, x <| fs) {-# INLINABLE partition #-} --- -- | Plutus Tx version of 'Data.List.nubBy' for 'BuiltinList'. --- nubByFast :: forall a. (MkNil a) => (a -> a -> Bool) -> BuiltinList a -> BuiltinList a --- nubByFast eq = toBuiltinList (Prelude.nubBy eq (fromBuiltinList)) --- where --- go :: BuiltinList a -> BuiltinList a -> BuiltinList a --- go xs = B.caseList' B.mkNil --- ( \y ys -> --- if elemBy eq y xs then --- go xs ys --- else --- y `BI.mkCons` go ys (y `BI.mkCons` xs) --- ) --- {-# INLINABLE nubBy #-} --- | Plutus Tx version of 'Data.List.sort'. --- sort :: Ord a => BuiltinList a -> BuiltinList a --- sort = sortBy compare --- {-# INLINABLE sort #-} - --- sortBy = undefined --- -- | Plutus Tx version of 'Data.List.sortBy'. --- sortBy :: (a -> a -> Ordering) -> BuiltinList a -> BuiltinList a --- sortBy cmp l = mergeAll (sequences l) --- where --- sequences (a:b:xs) --- | a `cmp` b == GT = descending b BuiltinList a xs --- | otherwise = ascending b (a:) xs --- sequences xs = [xs] - --- descending a as (b:bs) --- | a `cmp` b == GT = descending b (a:as) bs --- descending a as bs = (a:as): sequences bs - --- ascending a as (b:bs) --- | a `cmp` b /= GT = ascending b (\ys -> as (a:ys)) bs --- ascending a as bs = let x = as BuiltinList a --- in x : sequences bs - --- mergeAll [x] = x --- mergeAll xs = mergeAll (mergePairs xs) - --- mergePairs (a:b:xs) = let x = merge a b --- in x : mergePairs xs --- mergePairs xs = xs - --- merge as@(a:as') bs@(b:bs') --- | a `cmp` b == GT = b:merge as bs' --- | otherwise = a:merge as' bs --- merge [] bs = bs --- merge as [] = as --- {-# INLINABLE sortBy #-} - - --- -- append, --- -- findIndices, --- -- filter, --- -- mapMaybe, --- -- foldMap, --- -- length, --- -- mconcat, --- -- (<|), --- -- cons, --- -- nil, --- -- singleton, --- -- uncons, --- -- and, --- -- or, --- -- notElem, --- -- foldr, --- -- foldl, --- -- concat, --- -- concatMap, --- -- listToMaybe, --- -- uniqueElement, --- -- revAppend, --- -- reverse, --- -- replicate, --- -- findIndex, --- -- unzip, --- -- zipWith, --- -- head, --- -- last, --- -- tail, --- -- take, --- -- drop, --- -- dropWhile, --- -- splitAt, --- -- elemBy, --- -- nubBy, --- -- nub, --- -- partition, --- -- toBuiltinList, --- -- fromBuiltinList, --- -- toSOP, --- -- fromSOP, +-- | Plutus Tx version of 'Data.List.sort' for 'BuiltinList'. +sort :: Ord a => BuiltinList a -> BuiltinList a +sort = sortBy compare +{-# INLINABLE sort #-} + +-- | Plutus Tx version of 'Data.List.sortBy' for 'BuiltinList'. +sortBy :: (a -> a -> Ordering) -> BuiltinList a -> BuiltinList a +sortBy cmp l = undefined +{-# INLINABLE sortBy #-} From efef2d222f58fe37a0e3a5cd2a1a92db33c86938 Mon Sep 17 00:00:00 2001 From: zeme Date: Mon, 19 May 2025 16:22:15 +0200 Subject: [PATCH 03/30] wip --- .../src/PlutusLedgerApi/V1/Contexts.hs | 2 +- .../src/PlutusLedgerApi/V2/Contexts.hs | 2 +- .../src/PlutusTx/Compiler/Expr.hs | 8 + .../test/BuiltinList/Budget/Spec.hs | 289 +++++++++++------- plutus-tx/src/PlutusTx/BuiltinList.hs | 17 +- plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs | 1 + 6 files changed, 192 insertions(+), 127 deletions(-) diff --git a/plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs b/plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs index 9b1394edd4d..dc963b958a3 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs @@ -42,7 +42,7 @@ module PlutusLedgerApi.V1.Contexts import PlutusTx import PlutusTx.Foldable qualified as F -import PlutusTx.List +import PlutusTx.List hiding (mapMaybe) import PlutusTx.Prelude import GHC.Generics (Generic) diff --git a/plutus-ledger-api/src/PlutusLedgerApi/V2/Contexts.hs b/plutus-ledger-api/src/PlutusLedgerApi/V2/Contexts.hs index e1387212652..56730b57baa 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/V2/Contexts.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/V2/Contexts.hs @@ -60,7 +60,7 @@ import PlutusTx.Blueprint.Definition.Derive (definitionRef) import PlutusTx.Blueprint.TH (makeIsDataSchemaIndexed) import PlutusTx.Foldable qualified as F import PlutusTx.Lift (makeLift) -import PlutusTx.List +import PlutusTx.List hiding (mapMaybe) import Prettyprinter (Pretty (..), nest, vsep, (<+>)) -- | An input of a pending transaction. diff --git a/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs b/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs index c6462c4d3dc..01a01e2619f 100644 --- a/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs +++ b/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs @@ -843,6 +843,7 @@ compileExpr e = traceCompilation 2 ("Compiling expr:" GHC.<+> GHC.ppr e) $ do builtinBoolTyCon <- lookupGhcTyCon ''BI.BuiltinBool builtinDataTyCon <- lookupGhcTyCon ''Builtins.BuiltinData builtinPairTyCon <- lookupGhcTyCon ''BI.BuiltinPair + builtinListTyCon <- lookupGhcTyCon ''BI.BuiltinList stringTyName <- lookupGhcName ''Builtins.BuiltinString stringToBuiltinStringName <- lookupGhcName 'Builtins.stringToBuiltinString builtinByteStringTyName <- lookupGhcName ''Builtins.BuiltinByteString @@ -1013,6 +1014,13 @@ compileExpr e = traceCompilation 2 ("Compiling expr:" GHC.<+> GHC.ppr e) $ do GHC.TyConApp tyCon [GHC.TyConApp tyArg1 [], GHC.TyConApp tyArg2 []] | (tyCon, tyArg1, tyArg2) == (builtinPairTyCon, builtinDataTyCon, builtinDataTyCon) -> pure $ PLC.mkConstant annMayInline ([] @(PLC.Data, PLC.Data)) + GHC.TyConApp tyCon [GHC.TyConApp tyArg1 []] + | (tyCon, tyArg1) == (builtinListTyCon, builtinIntegerTyCon) -> + pure $ PLC.mkConstant annMayInline ([] @[Integer]) + | (tyCon, tyArg1) == (builtinListTyCon, builtinBoolTyCon) -> + pure $ PLC.mkConstant annMayInline ([] @[Bool]) + | (tyCon, tyArg1) == (builtinListTyCon, builtinDataTyCon) -> + pure $ PLC.mkConstant annMayInline ([] @[PLC.Data]) _ -> throwPlain $ CompilationError "'mkNil' applied to an unknown type" GHC.Var n | GHC.getName n == useToOpaqueName -> diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index ad2a5afb8d0..f3f50fe9b42 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -3,9 +3,8 @@ module BuiltinList.Budget.Spec where -import Prelude hiding (all, any, elem, map) +import Prelude (Bool (..), Integer, Maybe (..), pure, undefined, ($), (.)) import System.FilePath -import Test.Tasty (TestName) import Test.Tasty.Extras import PlutusTx.BuiltinList qualified as L @@ -20,180 +19,240 @@ tests :: TestNested tests = testNested ("BuiltinList" "Budget") . pure $ testNestedGhc - [ goldenBundle "map" map (map `unsafeApplyCode` l) - , goldenBundle "elem" elem (elem `unsafeApplyCode` l) - , goldenBundle "find" find (find `unsafeApplyCode` l) - , goldenBundle "any" any (any `unsafeApplyCode` l) - , goldenBundle "all" all (all `unsafeApplyCode` l) - , goldenBundle "index" index (index `unsafeApplyCode` l) - , goldenBundle "indexNegative" (index `unsafeApplyCode` indexNegative l) - , goldenBundle "indexTooLarge" (index `unsafeApplyCode` indexTooLarge l) - , goldenBundle "cons" (index `unsafeApplyCode` cons l) - , goldenBundle "unconsJust" (index `unsafeApplyCode` unconsJust l) - , goldenBundle "unconsNothing" (index `unsafeApplyCode` unconsNothing l) + [ goldenBundle "map" map (map `unsafeApplyCode` l1) + , goldenBundle "elem" elem (elem `unsafeApplyCode` l1) + , goldenBundle "find" find (find `unsafeApplyCode` l1) + , goldenBundle "any" any (any `unsafeApplyCode` l1) + , goldenBundle "all" all (all `unsafeApplyCode` l1) + , goldenBundle "index" index (index `unsafeApplyCode` l1) + , goldenBundle "indexNegative" indexNegative (indexNegative `unsafeApplyCode` l1) + , goldenBundle "indexTooLarge" indexTooLarge (indexTooLarge `unsafeApplyCode` l1) + , goldenBundle "cons" cons (cons `unsafeApplyCode` l1) + , goldenBundle "unconsJust" unconsJust (unconsJust `unsafeApplyCode` l1) + , goldenBundle "unconsNothing" unconsNothing (unconsNothing `unsafeApplyCode` l1) + , goldenBundle "empty" empty (empty `unsafeApplyCode` l1) + , goldenBundle "singleton" singleton (singleton `unsafeApplyCode` l1) + , goldenBundle "null" null (null `unsafeApplyCode` l1) + , goldenBundle "(++)" (++) ((++) `unsafeApplyCode` l1) + , goldenBundle "(<|)" (<|) ((<|) `unsafeApplyCode` l1) + , goldenBundle "append" append (append `unsafeApplyCode` l1) + , goldenBundle "findIndices" findIndices (findIndices `unsafeApplyCode` l1) + , goldenBundle "filter" filter (filter `unsafeApplyCode` l1) + , goldenBundle "mapMaybe" mapMaybe (mapMaybe `unsafeApplyCode` l1) + , goldenBundle "length" length (length `unsafeApplyCode` l1) + , goldenBundle "and" and (and `unsafeApplyCode` l2) + , goldenBundle "or" or (or `unsafeApplyCode` l2) + , goldenBundle "notElem" notElem (notElem `unsafeApplyCode` l1) + , goldenBundle "foldr" foldr (foldr `unsafeApplyCode` l1) + , goldenBundle "foldl" foldl (foldl `unsafeApplyCode` l1) + , goldenBundle "concat" concat (concat `unsafeApplyCode` l1) + , goldenBundle "concatMap" concatMap (concatMap `unsafeApplyCode` l1) + , goldenBundle "listToMaybeJust" listToMaybeJust (listToMaybeJust `unsafeApplyCode` l1) + , goldenBundle "listToMaybeNothing" + listToMaybeNothing (listToMaybeNothing `unsafeApplyCode` l1) + , goldenBundle "uniqueElementJust" uniqueElementJust (uniqueElementJust `unsafeApplyCode` l1) + , goldenBundle "uniqueElementNothing" + uniqueElementNothing (uniqueElementNothing `unsafeApplyCode` l1) + , goldenBundle "revAppend" revAppend (revAppend `unsafeApplyCode` l1) + , goldenBundle "reverse" reverse (reverse `unsafeApplyCode` l1) + , goldenBundle "replicate" replicate (replicate `unsafeApplyCode` l1) + , goldenBundle "findIndexJust" findIndexJust (findIndexJust `unsafeApplyCode` l1) + , goldenBundle "findIndexNothing" findIndexNothing (findIndexNothing `unsafeApplyCode` l1) + , goldenBundle "unzip" unzip (unzip `unsafeApplyCode` l3) + , goldenBundle "zip" zip (zip `unsafeApplyCode` l1) + , goldenBundle "zipWith" zipWith (zipWith `unsafeApplyCode` l1) + , goldenBundle "headOk" headOk (headOk `unsafeApplyCode` l1) + , goldenBundle "headEmpty" headEmpty (headEmpty `unsafeApplyCode` l1) + , goldenBundle "lastOk" lastOk (lastOk `unsafeApplyCode` l1) + , goldenBundle "lastEmpty" lastEmpty (lastEmpty `unsafeApplyCode` l1) + , goldenBundle "tailOk" tailOk (tailOk `unsafeApplyCode` l1) + , goldenBundle "tailEmpty" tailEmpty (tailEmpty `unsafeApplyCode` l1) + , goldenBundle "take" take (take `unsafeApplyCode` l1) + , goldenBundle "drop" drop (drop `unsafeApplyCode` l1) + , goldenBundle "dropWhile" dropWhile (dropWhile `unsafeApplyCode` l1) + , goldenBundle "splitAt" splitAt (splitAt `unsafeApplyCode` l1) + , goldenBundle "elemBy" elemBy (elemBy `unsafeApplyCode` l1) + , goldenBundle "partition" partition (partition `unsafeApplyCode` l1) + , goldenBundle "sort" sort (sort `unsafeApplyCode` l1) + , goldenBundle "sortBy" sortBy (sortBy `unsafeApplyCode` l1) + , goldenBundle "nub" nub (nub `unsafeApplyCode` l1) + , goldenBundle "nubBy" nubBy (nubBy `unsafeApplyCode` l1) ] - --- goldenBundle :: TestName -> _ -> _ -> TestNested -goldenBundle name f x = do - goldenPirReadable name f - goldenUPlcReadable name f - goldenEvalCekCatch name [f `unsafeApplyCode` x] - goldenBudget name (f `unsafeApplyCode` x) - - -map :: CompiledCode (P.BuiltinList Integer -> P.BuiltinList Integer) +map :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) map = $$(compile [||L.map (P.+ 1)||]) -elem :: CompiledCode (P.BuiltinList Integer -> (Bool, Bool)) +elem :: CompiledCode (L.BuiltinList Integer -> (Bool, Bool)) elem = $$(compile [||\xs -> (L.elem 8 xs, L.elem 12 xs)||]) -find :: CompiledCode (P.BuiltinList Integer -> (Maybe Integer, Maybe Integer)) +find :: CompiledCode (L.BuiltinList Integer -> (Maybe Integer, Maybe Integer)) find = $$(compile [||\xs -> (L.find (P.>= 8) xs, L.find (P.>= 12) xs)||]) -any :: CompiledCode (P.BuiltinList Integer -> (Bool, Bool)) +any :: CompiledCode (L.BuiltinList Integer -> (Bool, Bool)) any = $$(compile [||\xs -> (L.any (P.>= 8) xs, L.any (P.>= 12) xs)||]) -all :: CompiledCode (P.BuiltinList Integer -> (Bool, Bool)) +all :: CompiledCode (L.BuiltinList Integer -> (Bool, Bool)) all = $$(compile [||\xs -> (L.all (P.>= 8) xs, L.all (P.>= 0) xs)||]) -index :: CompiledCode (P.BuiltinList Integer -> Integer) +index :: CompiledCode (L.BuiltinList Integer -> Integer) index = $$(compile [||\xs -> xs L.!! 5 ||]) -indexNegative :: CompiledCode (P.BuiltinList Integer -> Integer) +indexNegative :: CompiledCode (L.BuiltinList Integer -> Integer) indexNegative = $$(compile [||\xs -> xs L.!! (-1) ||]) -indexTooLarge :: CompiledCode (P.BuiltinList Integer -> Integer) +indexTooLarge :: CompiledCode (L.BuiltinList Integer -> Integer) indexTooLarge = $$(compile [||\xs -> xs L.!! 10 ||]) -cons :: CompiledCode (P.BuiltinList Integer -> P.BuiltinList Integer) +cons :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) cons = $$(compile [||\xs -> L.cons 0 xs||]) -unconsJust :: CompiledCode (P.BuiltinList Integer -> Maybe (Integer, P.BuiltinList Integer)) +unconsJust :: CompiledCode (L.BuiltinList Integer -> Maybe (Integer, L.BuiltinList Integer)) unconsJust = $$(compile [||\xs -> L.uncons xs||]) -unconsNothing :: CompiledCode (P.BuiltinList Integer -> Maybe (Integer, P.BuiltinList Integer)) +unconsNothing :: CompiledCode (L.BuiltinList Integer -> Maybe (Integer, L.BuiltinList Integer)) unconsNothing = $$(compile [||\_ -> L.uncons L.empty||]) --- empty :: CompiledCode (P.BuiltinList Integer -> a) --- empty = $$(compile [|| L.empty ||]) +empty :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +empty = $$(compile [|| \_ -> L.empty ||]) + +singleton :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +singleton = $$(compile [|| \_ -> L.singleton 1 ||]) + +null :: CompiledCode (L.BuiltinList Integer -> Bool) +null = $$(compile [|| \xs -> L.null xs ||]) + +(++) :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +(++) = $$(compile [|| \xs -> xs L.++ xs ||]) + +(<|) :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +(<|) = $$(compile [|| \xs -> 42 L.<| xs ||]) + +append :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +append = $$(compile [|| \xs -> L.append xs xs ||]) + +findIndices :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +findIndices = $$(compile [|| \xs -> L.findIndices P.odd xs ||]) + +filter :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +filter = $$(compile [|| \xs -> L.filter P.even xs ||]) --- singleton :: CompiledCode (P.BuiltinList Integer -> a) --- singleton = $$(compile [|| L.singleton ||]) +mapMaybe :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +mapMaybe = $$(compile [|| \xs -> L.mapMaybe (\x -> if P.odd x then Just x else Nothing) xs ||]) --- null :: CompiledCode (P.BuiltinList Integer -> a) --- null = $$(compile [|| L.null ||]) +length :: CompiledCode (L.BuiltinList Integer -> Integer) +length = $$(compile [|| \xs -> L.length xs ||]) --- caseList' :: CompiledCode (P.BuiltinList Integer -> a) --- caseList' = $$(compile [|| L.caseList' ||]) +and :: CompiledCode (L.BuiltinList P.BuiltinBool -> Bool) +and = $$(compile [|| \xs -> L.and xs ||]) --- (++) :: CompiledCode (P.BuiltinList Integer -> a) --- (++) = $$(compile [|| L.(++) ||]) +or :: CompiledCode (L.BuiltinList P.BuiltinBool -> Bool) +or = $$(compile [|| \xs -> L.or xs ||]) --- (<|) :: CompiledCode (P.BuiltinList Integer -> a) --- (<|) = $$(compile [|| L.(<|) ||]) +notElem :: CompiledCode (L.BuiltinList Integer -> Bool) +notElem = $$(compile [|| \xs -> L.notElem 42 xs||]) --- append :: CompiledCode (P.BuiltinList Integer -> a) --- append = $$(compile [|| L.append ||]) +foldr :: CompiledCode (L.BuiltinList Integer -> Integer) +foldr = $$(compile [|| \xs -> L.foldr (P.+) 0 xs ||]) --- findIndices :: CompiledCode (P.BuiltinList Integer -> a) --- findIndices = $$(compile [|| L.findIndices ||]) +foldl :: CompiledCode (L.BuiltinList Integer -> Integer) +foldl = $$(compile [|| \xs -> L.foldl (P.*) 0 xs ||]) --- filter :: CompiledCode (P.BuiltinList Integer -> a) --- filter = $$(compile [|| L.filter ||]) +concat :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +concat = $$(compile [|| \xs -> L.concat (xs L.<| (L.singleton (L.singleton 1))) ||]) --- mapMaybe :: CompiledCode (P.BuiltinList Integer -> a) --- mapMaybe = $$(compile [|| L.mapMaybe ||]) +concatMap :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +concatMap = undefined -- $$(compile [|| L.concatMap ||]) --- length :: CompiledCode (P.BuiltinList Integer -> a) --- length = $$(compile [|| L.length ||]) +listToMaybeJust :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) +listToMaybeJust = $$(compile [|| \xs -> L.listToMaybe xs ||]) --- and :: CompiledCode (P.BuiltinList Integer -> a) --- and = $$(compile [|| L.and ||]) +listToMaybeNothing :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) +listToMaybeNothing = $$(compile [|| \_ -> L.listToMaybe L.empty ||]) --- or :: CompiledCode (P.BuiltinList Integer -> a) --- or = $$(compile [|| L.or ||]) +uniqueElementJust :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) +uniqueElementJust = $$(compile [|| \xs -> L.uniqueElement xs ||]) --- notElem :: CompiledCode (P.BuiltinList Integer -> a) --- notElem = $$(compile [|| L.notElem ||]) +uniqueElementNothing :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) +uniqueElementNothing = $$(compile [|| \_ -> L.uniqueElement L.empty ||]) --- foldr :: CompiledCode (P.BuiltinList Integer -> a) --- foldr = $$(compile [|| L.foldr ||]) +revAppend :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +revAppend = $$(compile [|| \xs -> L.revAppend xs xs ||]) --- foldl :: CompiledCode (P.BuiltinList Integer -> a) --- foldl = $$(compile [|| L.foldl ||]) +reverse :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +reverse = $$(compile [|| \xs -> L.reverse xs ||]) --- concat :: CompiledCode (P.BuiltinList Integer -> a) --- concat = $$(compile [|| L.concat ||]) +replicate :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +replicate = $$(compile [|| \_ -> L.replicate 10 0 ||]) --- concatMap :: CompiledCode (P.BuiltinList Integer -> a) --- concatMap = $$(compile [|| L.concatMap ||]) +findIndexJust :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) +findIndexJust = $$(compile [|| \xs -> L.findIndex (P.== 4) xs ||]) --- listToMaybe :: CompiledCode (P.BuiltinList Integer -> a) --- listToMaybe = $$(compile [|| L.listToMaybe ||]) +findIndexNothing :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) +findIndexNothing = $$(compile [|| \xs -> L.findIndex (P.== 99) xs ||]) --- uniqueElement :: CompiledCode (P.BuiltinList Integer -> a) --- uniqueElement = $$(compile [|| L.uniqueElement ||]) +unzip :: CompiledCode (L.BuiltinList (P.BuiltinPair a b) -> L.BuiltinList Integer) +unzip = undefined -- $$(compile [|| \xs -> L.unzip xs ||]) --- revAppend :: CompiledCode (P.BuiltinList Integer -> a) --- revAppend = $$(compile [|| L.revAppend ||]) +zip :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList (P.BuiltinPair Integer Integer)) +zip = undefined -- $$(compile [|| \xs -> L.zip xs xs ||]) --- reverse :: CompiledCode (P.BuiltinList Integer -> a) --- reverse = $$(compile [|| L.reverse ||]) +zipWith :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +zipWith = undefined -- $$(compile [|| L.zipWith ||]) --- replicate :: CompiledCode (P.BuiltinList Integer -> a) --- replicate = $$(compile [|| L.replicate ||]) +headOk :: CompiledCode (L.BuiltinList Integer -> Integer) +headOk = $$(compile [|| \xs -> L.head xs ||]) --- findIndex :: CompiledCode (P.BuiltinList Integer -> a) --- findIndex = $$(compile [|| L.findIndex ||]) +headEmpty :: CompiledCode (L.BuiltinList Integer -> Integer) +headEmpty = $$(compile [|| \_ -> L.head L.empty ||]) --- unzip :: CompiledCode (P.BuiltinList Integer -> a) --- unzip = $$(compile [|| L.unzip ||]) +lastOk :: CompiledCode (L.BuiltinList Integer -> Integer) +lastOk = $$(compile [|| \xs -> L.last xs ||]) --- zip :: CompiledCode (P.BuiltinList Integer -> a) --- zip = $$(compile [|| L.zip ||]) +lastEmpty :: CompiledCode (L.BuiltinList Integer -> Integer) +lastEmpty = $$(compile [|| \_ -> L.last L.empty ||]) --- zipWith :: CompiledCode (P.BuiltinList Integer -> a) --- zipWith = $$(compile [|| L.zipWith ||]) +tailOk :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +tailOk = $$(compile [|| \xs -> L.tail xs ||]) --- head :: CompiledCode (P.BuiltinList Integer -> a) --- head = $$(compile [|| L.head ||]) +tailEmpty :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +tailEmpty = $$(compile [|| \_ -> L.tail L.empty ||]) --- last :: CompiledCode (P.BuiltinList Integer -> a) --- last = $$(compile [|| L.last ||]) +take :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +take = $$(compile [|| \xs -> L.take 5 xs ||]) --- tail :: CompiledCode (P.BuiltinList Integer -> a) --- tail = $$(compile [|| L.tail ||]) +drop :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +drop = $$(compile [|| \xs -> L.drop 5 xs ||]) --- take :: CompiledCode (P.BuiltinList Integer -> a) --- take = $$(compile [|| L.take ||]) +dropWhile :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +dropWhile = $$(compile [|| \xs -> L.dropWhile (P.< 5) xs ||]) --- drop :: CompiledCode (P.BuiltinList Integer -> a) --- drop = $$(compile [|| L.drop ||]) +splitAt :: CompiledCode (L.BuiltinList Integer -> + P.BuiltinPair (L.BuiltinList Integer) (L.BuiltinList Integer)) +splitAt = undefined -- $$(compile [|| \xs -> L.splitAt 2 xs ||]) --- dropWhile :: CompiledCode (P.BuiltinList Integer -> a) --- dropWhile = $$(compile [|| L.dropWhile ||]) +elemBy :: CompiledCode (L.BuiltinList Integer -> Bool) +elemBy = $$(compile [|| \xs -> L.elemBy (P.<=) 0 xs ||]) --- splitAt :: CompiledCode (P.BuiltinList Integer -> a) --- splitAt = $$(compile [|| L.splitAt ||]) +partition :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +partition = undefined -- $$(compile [|| L.partition ||]) --- elemBy :: CompiledCode (P.BuiltinList Integer -> a) --- elemBy = $$(compile [|| L.elemBy ||]) +sort :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +sort = undefined -- $$(compile [|| L.sort ||]) --- partition :: CompiledCode (P.BuiltinList Integer -> a) --- partition = $$(compile [|| L.partition ||]) +sortBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +sortBy = undefined -- $$(compile [|| L.sortBy ||]) --- sort :: CompiledCode (P.BuiltinList Integer -> a) --- sort = $$(compile [|| L.sort ||]) +nub :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +nub = undefined -- $$(compile [|| L.nub ||]) --- sortBy :: CompiledCode (P.BuiltinList Integer -> a) --- sortBy = $$(compile [|| L.sortBy ||]) +nubBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +nubBy = undefined -- $$(compile [|| L.nubBy ||]) --- nub :: CompiledCode (P.BuiltinList Integer -> a) --- nub = $$(compile [|| L.nub ||]) +l1 :: CompiledCode (L.BuiltinList Integer) +l1 = liftCodeDef $ toBuiltin ([1 .. 10] :: [Integer]) --- nubBy :: CompiledCode (P.BuiltinList Integer -> a) --- nubBy = $$(compile [|| L.nubBy ||]) +l2 :: CompiledCode (L.BuiltinList P.BuiltinBool) +l2 = liftCodeDef $ toBuiltin ([True, False] :: [Bool]) -l :: CompiledCode (P.BuiltinList Integer) -l = liftCodeDef $ toBuiltin ([1 .. 10] :: [Integer]) +l3 :: CompiledCode (L.BuiltinList (P.BuiltinPair Integer Integer)) +l3 = liftCodeDef $ toBuiltin ([ (1, 2), (3, 4), (5, 6) ] :: [(Integer, Integer)]) diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index 21b52d1f1af..93243ff9bc3 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -54,16 +54,15 @@ module PlutusTx.BuiltinList ( nubBy ) where -import Prelude (Bool (..), Integer, Maybe (..), curry, id, not, otherwise, undefined, (.)) +import Prelude (undefined) import PlutusTx.Builtins qualified as B import PlutusTx.Builtins.HasOpaque -import PlutusTx.Builtins.Internal (BuiltinList, BuiltinPair) import PlutusTx.Builtins.Internal qualified as BI import PlutusTx.Eq import PlutusTx.ErrorCodes import PlutusTx.Ord -import PlutusTx.Trace (traceError) +import PlutusTx.Prelude hiding (mapMaybe) -- | Plutus Tx version of 'Data.List.:' for 'BuiltinList'. cons :: forall a. a -> BuiltinList a -> BuiltinList a @@ -182,12 +181,12 @@ length = foldr ( \_ -> B.addInteger 1 ) 0 {-# INLINABLE length #-} -- | Returns the conjunction of a list of Bools. -and :: BuiltinList Bool -> Bool -and = all id +and :: BuiltinList BuiltinBool -> Bool +and = all (\x -> BI.ifThenElse x True False) -- | Returns the disjunction of a list of Bools. -or :: BuiltinList Bool -> Bool -or = any id +or :: BuiltinList BuiltinBool -> Bool +or = any (\x -> BI.ifThenElse x True False) {-# INLINABLE or #-} -- | The negation of `elem`. @@ -434,9 +433,7 @@ partition partition p = BI.BuiltinPair . foldr select (empty, empty) where select :: a -> (BuiltinList a, BuiltinList a) -> (BuiltinList a, BuiltinList a) - select x ~(ts, fs) - | p x = (x <| ts, fs) - | otherwise = (ts, x <| fs) + select x ~(ts, fs) = if p x then (x <| ts, fs) else (ts, x <| fs) {-# INLINABLE partition #-} -- | Plutus Tx version of 'Data.List.sort' for 'BuiltinList'. diff --git a/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs b/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs index 93e26aab5e0..73249224495 100644 --- a/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs +++ b/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs @@ -274,6 +274,7 @@ class MkNil arep where instance MkNil BuiltinInteger instance MkNil BuiltinBool instance MkNil BuiltinData +instance (MkNil a) => MkNil (BuiltinList a) instance (MkNil a, MkNil b) => MkNil (BuiltinPair a b) instance (HasToOpaque a arep, MkNil arep) => HasToOpaque [a] (BuiltinList arep) where From 266026a5dde8661857a3884af0159f543efac47f Mon Sep 17 00:00:00 2001 From: zeme Date: Tue, 20 May 2025 14:30:25 +0200 Subject: [PATCH 04/30] wip --- out.html | 563 ++++++++++++++++++ .../src/PlutusTx/Compiler/Expr.hs | 17 +- .../BuiltinList/Budget/9.6/(++).budget.golden | 3 + .../BuiltinList/Budget/9.6/(++).eval.golden | 1 + .../BuiltinList/Budget/9.6/(++).pir.golden | 25 + .../BuiltinList/Budget/9.6/(++).uplc.golden | 14 + .../BuiltinList/Budget/9.6/(<|).budget.golden | 3 + .../BuiltinList/Budget/9.6/(<|).eval.golden | 1 + .../BuiltinList/Budget/9.6/(<|).pir.golden | 1 + .../BuiltinList/Budget/9.6/(<|).uplc.golden | 1 + .../BuiltinList/Budget/9.6/and.budget.golden | 3 + .../BuiltinList/Budget/9.6/and.eval.golden | 1 + .../BuiltinList/Budget/9.6/and.pir.golden | 27 + .../BuiltinList/Budget/9.6/and.uplc.golden | 19 + .../Budget/9.6/append.budget.golden | 3 + .../BuiltinList/Budget/9.6/append.eval.golden | 1 + .../BuiltinList/Budget/9.6/append.pir.golden | 25 + .../BuiltinList/Budget/9.6/append.uplc.golden | 14 + .../Budget/9.6/concat.budget.golden | 3 + .../BuiltinList/Budget/9.6/concat.eval.golden | 1 + .../BuiltinList/Budget/9.6/concat.pir.golden | 51 ++ .../BuiltinList/Budget/9.6/concat.uplc.golden | 22 + .../BuiltinList/Budget/9.6/cons.budget.golden | 5 +- .../BuiltinList/Budget/9.6/drop.budget.golden | 3 + .../BuiltinList/Budget/9.6/drop.eval.golden | 1 + .../BuiltinList/Budget/9.6/drop.pir.golden | 32 + .../BuiltinList/Budget/9.6/drop.uplc.golden | 25 + .../Budget/9.6/dropWhile.budget.golden | 3 + .../Budget/9.6/dropWhile.eval.golden | 1 + .../Budget/9.6/dropWhile.pir.golden | 30 + .../Budget/9.6/dropWhile.uplc.golden | 17 + .../Budget/9.6/elemBy.budget.golden | 3 + .../BuiltinList/Budget/9.6/elemBy.eval.golden | 1 + .../BuiltinList/Budget/9.6/elemBy.pir.golden | 27 + .../BuiltinList/Budget/9.6/elemBy.uplc.golden | 19 + .../Budget/9.6/empty.budget.golden | 3 + .../BuiltinList/Budget/9.6/empty.eval.golden | 1 + .../BuiltinList/Budget/9.6/empty.pir.golden | 1 + .../BuiltinList/Budget/9.6/empty.uplc.golden | 1 + .../Budget/9.6/filter.budget.golden | 3 + .../BuiltinList/Budget/9.6/filter.eval.golden | 1 + .../BuiltinList/Budget/9.6/filter.pir.golden | 37 ++ .../BuiltinList/Budget/9.6/filter.uplc.golden | 20 + .../Budget/9.6/findIndexJust.budget.golden | 3 + .../Budget/9.6/findIndexJust.eval.golden | 1 + .../Budget/9.6/findIndexJust.pir.golden | 32 + .../Budget/9.6/findIndexJust.uplc.golden | 17 + .../Budget/9.6/findIndexNothing.budget.golden | 3 + .../Budget/9.6/findIndexNothing.eval.golden | 1 + .../Budget/9.6/findIndexNothing.pir.golden | 32 + .../Budget/9.6/findIndexNothing.uplc.golden | 17 + .../Budget/9.6/findIndices.budget.golden | 3 + .../Budget/9.6/findIndices.eval.golden | 1 + .../Budget/9.6/findIndices.pir.golden | 41 ++ .../Budget/9.6/findIndices.uplc.golden | 20 + .../Budget/9.6/foldl.budget.golden | 3 + .../BuiltinList/Budget/9.6/foldl.eval.golden | 1 + .../BuiltinList/Budget/9.6/foldl.pir.golden | 17 + .../BuiltinList/Budget/9.6/foldl.uplc.golden | 14 + .../Budget/9.6/foldr.budget.golden | 3 + .../BuiltinList/Budget/9.6/foldr.eval.golden | 1 + .../BuiltinList/Budget/9.6/foldr.pir.golden | 13 + .../BuiltinList/Budget/9.6/foldr.uplc.golden | 13 + .../Budget/9.6/headEmpty.budget.golden | 5 + .../Budget/9.6/headEmpty.eval.golden | 2 + .../Budget/9.6/headEmpty.pir.golden | 24 + .../Budget/9.6/headEmpty.uplc.golden | 9 + .../Budget/9.6/headOk.budget.golden | 3 + .../BuiltinList/Budget/9.6/headOk.eval.golden | 1 + .../BuiltinList/Budget/9.6/headOk.pir.golden | 24 + .../BuiltinList/Budget/9.6/headOk.uplc.golden | 9 + .../Budget/9.6/lastEmpty.budget.golden | 5 + .../Budget/9.6/lastEmpty.eval.golden | 2 + .../Budget/9.6/lastEmpty.pir.golden | 32 + .../Budget/9.6/lastEmpty.uplc.golden | 21 + .../Budget/9.6/lastOk.budget.golden | 5 + .../BuiltinList/Budget/9.6/lastOk.eval.golden | 2 + .../BuiltinList/Budget/9.6/lastOk.pir.golden | 32 + .../BuiltinList/Budget/9.6/lastOk.uplc.golden | 21 + .../Budget/9.6/length.budget.golden | 3 + .../BuiltinList/Budget/9.6/length.eval.golden | 1 + .../BuiltinList/Budget/9.6/length.pir.golden | 16 + .../BuiltinList/Budget/9.6/length.uplc.golden | 12 + .../Budget/9.6/listToMaybeJust.budget.golden | 3 + .../Budget/9.6/listToMaybeJust.eval.golden | 1 + .../Budget/9.6/listToMaybeJust.pir.golden | 20 + .../Budget/9.6/listToMaybeJust.uplc.golden | 9 + .../9.6/listToMaybeNothing.budget.golden | 3 + .../Budget/9.6/listToMaybeNothing.eval.golden | 1 + .../Budget/9.6/listToMaybeNothing.pir.golden | 20 + .../Budget/9.6/listToMaybeNothing.uplc.golden | 9 + .../BuiltinList/Budget/9.6/map.uplc.golden | 26 +- .../Budget/9.6/mapMaybe.budget.golden | 3 + .../Budget/9.6/mapMaybe.eval.golden | 1 + .../Budget/9.6/mapMaybe.pir.golden | 48 ++ .../Budget/9.6/mapMaybe.uplc.golden | 23 + .../Budget/9.6/notElem.budget.golden | 3 + .../Budget/9.6/notElem.eval.golden | 1 + .../BuiltinList/Budget/9.6/notElem.pir.golden | 33 + .../Budget/9.6/notElem.uplc.golden | 20 + .../BuiltinList/Budget/9.6/nub.pir.golden | 50 ++ .../BuiltinList/Budget/9.6/nub.uplc.golden | 33 + .../Budget/9.6/nubBy.budget.golden | 3 + .../BuiltinList/Budget/9.6/nubBy.eval.golden | 1 + .../BuiltinList/Budget/9.6/nubBy.pir.golden | 50 ++ .../BuiltinList/Budget/9.6/nubBy.uplc.golden | 33 + .../BuiltinList/Budget/9.6/null.budget.golden | 3 + .../BuiltinList/Budget/9.6/null.eval.golden | 1 + .../BuiltinList/Budget/9.6/null.pir.golden | 6 + .../BuiltinList/Budget/9.6/null.uplc.golden | 3 + .../BuiltinList/Budget/9.6/or.budget.golden | 3 + .../BuiltinList/Budget/9.6/or.eval.golden | 1 + .../test/BuiltinList/Budget/9.6/or.pir.golden | 27 + .../BuiltinList/Budget/9.6/or.uplc.golden | 19 + .../Budget/9.6/replicate.budget.golden | 3 + .../Budget/9.6/replicate.eval.golden | 1 + .../Budget/9.6/replicate.pir.golden | 16 + .../Budget/9.6/replicate.uplc.golden | 11 + .../Budget/9.6/revAppend.budget.golden | 3 + .../Budget/9.6/revAppend.eval.golden | 1 + .../Budget/9.6/revAppend.pir.golden | 20 + .../Budget/9.6/revAppend.uplc.golden | 19 + .../Budget/9.6/reverse.budget.golden | 3 + .../Budget/9.6/reverse.eval.golden | 1 + .../BuiltinList/Budget/9.6/reverse.pir.golden | 20 + .../Budget/9.6/reverse.uplc.golden | 19 + .../Budget/9.6/singleton.budget.golden | 3 + .../Budget/9.6/singleton.eval.golden | 1 + .../Budget/9.6/singleton.pir.golden | 1 + .../Budget/9.6/singleton.uplc.golden | 1 + .../Budget/9.6/tailEmpty.budget.golden | 5 + .../Budget/9.6/tailEmpty.eval.golden | 2 + .../Budget/9.6/tailEmpty.pir.golden | 33 + .../Budget/9.6/tailEmpty.uplc.golden | 9 + .../Budget/9.6/tailOk.budget.golden | 3 + .../BuiltinList/Budget/9.6/tailOk.eval.golden | 1 + .../BuiltinList/Budget/9.6/tailOk.pir.golden | 33 + .../BuiltinList/Budget/9.6/tailOk.uplc.golden | 9 + .../BuiltinList/Budget/9.6/take.budget.golden | 3 + .../BuiltinList/Budget/9.6/take.eval.golden | 1 + .../BuiltinList/Budget/9.6/take.pir.golden | 32 + .../BuiltinList/Budget/9.6/take.uplc.golden | 26 + .../Budget/9.6/unconsJust.budget.golden | 5 +- .../Budget/9.6/unconsNothing.budget.golden | 5 +- .../9.6/uniqueElementJust.budget.golden | 3 + .../Budget/9.6/uniqueElementJust.eval.golden | 1 + .../Budget/9.6/uniqueElementJust.pir.golden | 27 + .../Budget/9.6/uniqueElementJust.uplc.golden | 14 + .../9.6/uniqueElementNothing.budget.golden | 3 + .../9.6/uniqueElementNothing.eval.golden | 1 + .../9.6/uniqueElementNothing.pir.golden | 27 + .../9.6/uniqueElementNothing.uplc.golden | 14 + .../test/BuiltinList/Budget/Spec.hs | 41 +- plutus-tx/src/PlutusTx/BuiltinList.hs | 58 +- 154 files changed, 2382 insertions(+), 52 deletions(-) create mode 100644 out.html create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.budget.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.uplc.golden diff --git a/out.html b/out.html new file mode 100644 index 00000000000..d40f8b832bc --- /dev/null +++ b/out.html @@ -0,0 +1,563 @@ + + +{-# INLINEABLE sortBy #-} +sortBy :: forall a. (a -> a -> Ordering) -> [a] -> [a] +sortBy a -> a -> Ordering +cmp = (a -> a -> Bool) -> [a] -> [a] +forall a. (a -> a -> Bool) -> [a] -> [a] +actualSort (\a +x a +y -> a -> a -> Ordering +cmp a +x a +y Ordering -> Ordering -> Bool +forall a. Eq a => a -> a -> Bool +== Ordering +GT) + +actualSort :: (a -> a -> Bool) -> [a] -> [a] +actualSort :: forall a. (a -> a -> Bool) -> [a] -> [a] +actualSort a -> a -> Bool +gt [a] +ns + | [] <- [a] +ns = [] + | [a +a] <- [a] +ns = [a +a] + | [a +a,a +b] <- [a] +ns = [a] -> [a] -> [a] +merge [a +a] [a +b] + | [a +a,a +b,a +c] <- [a] +ns = [a] -> [a] -> [a] -> [a] +merge3 [a +a] [a +b] [a +c] + | [a +a,a +b,a +c,a +d] <- [a] +ns = [a] -> [a] -> [a] -> [a] -> [a] +merge4 [a +a] [a +b] [a +c] [a +d] + | Bool +otherwise = [[a]] -> [a] +merge_all ([a] -> [[a]] +sequences [a] +ns) + where + sequences :: [a] -> [[a]] +sequences (a +a:a +b:[a] +xs) + | a +a a -> a -> Bool +`gt` a +b = a -> [a] -> [a] -> [[a]] +descending a +b [a +a] [a] +xs + | Bool +otherwise = a -> ([a] -> [a]) -> [a] -> [[a]] +ascending a +b (a +aa -> [a] -> [a] +forall a. a -> [a] -> [a] +:) [a] +xs + sequences [a] +xs = [[a] +xs] + + descending :: a -> [a] -> [a] -> [[a]] +descending a +a [a] +as (a +b:[a] +bs) + | a +a a -> a -> Bool +`gt` a +b = a -> [a] -> [a] -> [[a]] +descending a +b (a +aa -> [a] -> [a] +forall a. a -> [a] -> [a] +:[a] +as) [a] +bs + descending a +a [a] +as [a] +bs = (a +aa -> [a] -> [a] +forall a. a -> [a] -> [a] +:[a] +as)[a] -> [[a]] -> [[a]] +forall a. a -> [a] -> [a] +: [a] -> [[a]] +sequences [a] +bs + + ascending :: a -> ([a] -> [a]) -> [a] -> [[a]] +ascending a +a [a] -> [a] +as (a +b:[a] +bs) + | Bool -> Bool +not (a +a a -> a -> Bool +`gt` a +b) = a -> ([a] -> [a]) -> [a] -> [[a]] +ascending a +b (\[a] +ys -> [a] -> [a] +as (a +aa -> [a] -> [a] +forall a. a -> [a] -> [a] +:[a] +ys)) [a] +bs + ascending a +a [a] -> [a] +as [a] +bs = let !x :: [a] +x = [a] -> [a] +as [a +a] + in [a] +x [a] -> [[a]] -> [[a]] +forall a. a -> [a] -> [a] +: [a] -> [[a]] +sequences [a] +bs + + merge_all :: [[a]] -> [a] +merge_all [[a] +x] = [a] +x + merge_all [[a]] +xs = [[a]] -> [a] +merge_all ([[a]] -> [[a]] +reduce_once [[a]] +xs) + + reduce_once :: [[a]] -> [[a]] +reduce_once [] = [] + reduce_once [[a] +a] = [[a] +a] + reduce_once [[a] +a,[a] +b] = [[a] -> [a] -> [a] +merge [a] +a [a] +b] + reduce_once [[a] +a,[a] +b,[a] +c] = [[a] -> [a] -> [a] -> [a] +merge3 [a] +a [a] +b [a] +c] + reduce_once [[a] +a,[a] +b,[a] +c,[a] +d,[a] +e] = [[a] -> [a] -> [a] +merge [a] +a [a] +b, [a] -> [a] -> [a] -> [a] +merge3 [a] +c [a] +d [a] +e] + reduce_once [[a] +a,[a] +b,[a] +c,[a] +d,[a] +e,[a] +f] = [[a] -> [a] -> [a] -> [a] +merge3 [a] +a [a] +b [a] +c, [a] -> [a] -> [a] -> [a] +merge3 [a] +d [a] +e [a] +f] + reduce_once ([a] +a:[a] +b:[a] +c:[a] +d:[[a]] +xs) = let !x :: [a] +x = [a] -> [a] -> [a] -> [a] -> [a] +merge4 [a] +a [a] +b [a] +c [a] +d + in [a] +x [a] -> [[a]] -> [[a]] +forall a. a -> [a] -> [a] +: [[a]] -> [[a]] +reduce_once [[a]] +xs + + merge :: [a] -> [a] -> [a] +merge as :: [a] +as@(a +a:[a] +as') bs :: [a] +bs@(a +b:[a] +bs') + | a +a a -> a -> Bool +`gt` a +b = a +b a -> [a] -> [a] +forall a. a -> [a] -> [a] +: [a] -> [a] -> [a] +merge [a] +as [a] +bs' + | Bool +otherwise = a +a a -> [a] -> [a] +forall a. a -> [a] -> [a] +: [a] -> [a] -> [a] +merge [a] +as' [a] +bs + merge [] [a] +bs = [a] +bs + merge [a] +as [] = [a] +as + + -- `merge3` is a manually fused version of `merge (merge as bs) cs` + merge3 :: [a] -> [a] -> [a] -> [a] +merge3 as :: [a] +as@(a +a:[a] +as') bs :: [a] +bs@(a +b:[a] +bs') [a] +cs + | a +a a -> a -> Bool +`gt` a +b = a -> [a] -> [a] -> [a] -> [a] +merge3X a +b [a] +as [a] +bs' [a] +cs + | Bool +otherwise = a -> [a] -> [a] -> [a] -> [a] +merge3X a +a [a] +as' [a] +bs [a] +cs + merge3 [] [a] +bs [a] +cs = [a] -> [a] -> [a] +merge [a] +bs [a] +cs + merge3 [a] +as [] [a] +cs = [a] -> [a] -> [a] +merge [a] +as [a] +cs + + merge3X :: a -> [a] -> [a] -> [a] -> [a] +merge3X a +x [a] +as [a] +bs cs :: [a] +cs@(a +c:[a] +cs') + | a +x a -> a -> Bool +`gt` a +c = a +c a -> [a] -> [a] +forall a. a -> [a] -> [a] +: a -> [a] -> [a] -> [a] -> [a] +merge3X a +x [a] +as [a] +bs [a] +cs' + | Bool +otherwise = a +x a -> [a] -> [a] +forall a. a -> [a] -> [a] +: [a] -> [a] -> [a] -> [a] +merge3 [a] +as [a] +bs [a] +cs + merge3X a +x [a] +as [a] +bs [] = a +x a -> [a] -> [a] +forall a. a -> [a] -> [a] +: [a] -> [a] -> [a] +merge [a] +as [a] +bs + + merge3Y :: [a] -> a -> [a] -> [a] -> [a] +merge3Y as :: [a] +as@(a +a:[a] +as') a +y [a] +bs [a] +cs + | a +a a -> a -> Bool +`gt` a +y = a +y a -> [a] -> [a] +forall a. a -> [a] -> [a] +: [a] -> [a] -> [a] -> [a] +merge3 [a] +as [a] +bs [a] +cs + | Bool +otherwise = a +a a -> [a] -> [a] +forall a. a -> [a] -> [a] +: [a] -> a -> [a] -> [a] -> [a] +merge3Y [a] +as' a +y [a] +bs [a] +cs + merge3Y [] a +x [a] +bs [a] +cs = a +x a -> [a] -> [a] +forall a. a -> [a] -> [a] +: [a] -> [a] -> [a] +merge [a] +bs [a] +cs + + -- `merge4 as bs cs ds` is (essentially) a manually fused version of + -- `merge (merge as bs) (merge cs ds)` + merge4 :: [a] -> [a] -> [a] -> [a] -> [a] +merge4 as :: [a] +as@(a +a:[a] +as') bs :: [a] +bs@(a +b:[a] +bs') [a] +cs [a] +ds + | a +a a -> a -> Bool +`gt` a +b = a -> [a] -> [a] -> [a] -> [a] -> [a] +merge4X a +b [a] +as [a] +bs' [a] +cs [a] +ds + | Bool +otherwise = a -> [a] -> [a] -> [a] -> [a] -> [a] +merge4X a +a [a] +as' [a] +bs [a] +cs [a] +ds + merge4 [] [a] +bs [a] +cs [a] +ds = [a] -> [a] -> [a] -> [a] +merge3 [a] +bs [a] +cs [a] +ds + merge4 [a] +as [] [a] +cs [a] +ds = [a] -> [a] -> [a] -> [a] +merge3 [a] +as [a] +cs [a] +ds + + merge4X :: a -> [a] -> [a] -> [a] -> [a] -> [a] +merge4X a +x [a] +as [a] +bs cs :: [a] +cs@(a +c:[a] +cs') ds :: [a] +ds@(a +d:[a] +ds') + | a +c a -> a -> Bool +`gt` a +d = a -> [a] -> [a] -> a -> [a] -> [a] -> [a] +merge4XY a +x [a] +as [a] +bs a +d [a] +cs [a] +ds' + | Bool +otherwise = a -> [a] -> [a] -> a -> [a] -> [a] -> [a] +merge4XY a +x [a] +as [a] +bs a +c [a] +cs' [a] +ds + merge4X a +x [a] +as [a] +bs [] [a] +ds = a -> [a] -> [a] -> [a] -> [a] +merge3X a +x [a] +as [a] +bs [a] +ds + merge4X a +x [a] +as [a] +bs [a] +cs [] = a -> [a] -> [a] -> [a] -> [a] +merge3X a +x [a] +as [a] +bs [a] +cs + + merge4Y :: [a] -> [a] -> a -> [a] -> [a] -> [a] +merge4Y as :: [a] +as@(a +a:[a] +as') bs :: [a] +bs@(a +b:[a] +bs') a +y [a] +cs [a] +ds + | a +a a -> a -> Bool +`gt` a +b = a -> [a] -> [a] -> a -> [a] -> [a] -> [a] +merge4XY a +b [a] +as [a] +bs' a +y [a] +cs [a] +ds + | Bool +otherwise = a -> [a] -> [a] -> a -> [a] -> [a] -> [a] +merge4XY a +a [a] +as' [a] +bs a +y [a] +cs [a] +ds + merge4Y [a] +as [] a +y [a] +cs [a] +ds = [a] -> a -> [a] -> [a] -> [a] +merge3Y [a] +as a +y [a] +cs [a] +ds + merge4Y [] [a] +bs a +y [a] +cs [a] +ds = [a] -> a -> [a] -> [a] -> [a] +merge3Y [a] +bs a +y [a] +cs [a] +ds + + merge4XY :: a -> [a] -> [a] -> a -> [a] -> [a] -> [a] +merge4XY a +x [a] +as [a] +bs a +y [a] +cs [a] +ds + | a +x a -> a -> Bool +`gt` a +y = a +y a -> [a] -> [a] +forall a. a -> [a] -> [a] +: a -> [a] -> [a] -> [a] -> [a] -> [a] +merge4X a +x [a] +as [a] +bs [a] +cs [a] +ds + | Bool +otherwise = a +x a -> [a] -> [a] +forall a. a -> [a] -> [a] +: [a] -> [a] -> a -> [a] -> [a] -> [a] +merge4Y [a] +as [a] +bs a +y [a] +cs [a] +ds + + \ No newline at end of file diff --git a/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs b/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs index 01a01e2619f..f48ef912318 100644 --- a/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs +++ b/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs @@ -1004,16 +1004,21 @@ compileExpr e = traceCompilation 2 ("Compiling expr:" GHC.<+> GHC.ppr e) $ do -- GHC.Var (isErrorId -> True) `GHC.App` GHC.Type t `GHC.App` _ -> PIR.TyInst annMayInline <$> errorFunc <*> compileTypeNorm t - (strip -> GHC.Var n) `GHC.App` GHC.Type ty - | GHC.getName n == mkNilOpaqueName -> case ty of + + (strip -> GHC.Var n) `GHC.App` GHC.Type ty | GHC.getName n == mkNilOpaqueName -> + case ty of GHC.TyConApp tyCon [] | tyCon == GHC.integerTyCon || tyCon == builtinIntegerTyCon -> pure $ PLC.mkConstant annMayInline ([] @Integer) - | tyCon == builtinBoolTyCon -> pure $ PLC.mkConstant annMayInline ([] @Bool) - | tyCon == builtinDataTyCon -> pure $ PLC.mkConstant annMayInline ([] @PLC.Data) + | tyCon == builtinBoolTyCon -> + pure $ PLC.mkConstant annMayInline ([] @Bool) + | tyCon == builtinDataTyCon -> + pure $ PLC.mkConstant annMayInline ([] @PLC.Data) + GHC.TyConApp tyCon [GHC.TyConApp tyArg1 [], GHC.TyConApp tyArg2 []] | (tyCon, tyArg1, tyArg2) == (builtinPairTyCon, builtinDataTyCon, builtinDataTyCon) -> pure $ PLC.mkConstant annMayInline ([] @(PLC.Data, PLC.Data)) + GHC.TyConApp tyCon [GHC.TyConApp tyArg1 []] | (tyCon, tyArg1) == (builtinListTyCon, builtinIntegerTyCon) -> pure $ PLC.mkConstant annMayInline ([] @[Integer]) @@ -1021,7 +1026,9 @@ compileExpr e = traceCompilation 2 ("Compiling expr:" GHC.<+> GHC.ppr e) $ do pure $ PLC.mkConstant annMayInline ([] @[Bool]) | (tyCon, tyArg1) == (builtinListTyCon, builtinDataTyCon) -> pure $ PLC.mkConstant annMayInline ([] @[PLC.Data]) - _ -> throwPlain $ CompilationError "'mkNil' applied to an unknown type" + _ -> + throwPlain $ CompilationError "'mkNil' applied to an unknown type" + GHC.Var n | GHC.getName n == useToOpaqueName -> throwPlain $ diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).budget.golden new file mode 100644 index 00000000000..3f0532d9475 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).budget.golden @@ -0,0 +1,3 @@ +cpu: 9002784 +mem: 33712 +size: 42 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden new file mode 100644 index 00000000000..3ee1061d2d0 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden @@ -0,0 +1 @@ +(con (list integer) [1,2,3,4,5,6,7,8,9,10,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).pir.golden new file mode 100644 index 00000000000..2cb7c10b472 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).pir.golden @@ -0,0 +1,25 @@ +\(xs : list integer) -> + (let + b = list integer + in + \(f : integer -> b -> b) (acc : b) -> + letrec + !go : list integer -> b + = \(xs : list integer) -> + chooseList + {integer} + {all dead. b} + xs + (/\dead -> acc) + (/\dead -> + let + !x : integer = headList {integer} xs + !xs : list integer = tailList {integer} xs + in + f x (go xs)) + {b} + in + go) + (mkCons {integer}) + xs + xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).uplc.golden new file mode 100644 index 00000000000..96fab57f85d --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).uplc.golden @@ -0,0 +1,14 @@ +(program + 1.1.0 + (\xs -> + (\s -> s s) + (\s xs -> + force + (force (force chooseList) + xs + (delay xs) + (delay + (force mkCons + (force headList xs) + ((\x -> s s x) (force tailList xs)))))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).budget.golden new file mode 100644 index 00000000000..42417de0de0 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).budget.golden @@ -0,0 +1,3 @@ +cpu: 216462 +mem: 1032 +size: 9 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden new file mode 100644 index 00000000000..6c5264d56a4 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden @@ -0,0 +1 @@ +(con (list integer) [42,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).pir.golden new file mode 100644 index 00000000000..71090410f42 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).pir.golden @@ -0,0 +1 @@ +\(xs : list integer) -> mkCons {integer} 42 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).uplc.golden new file mode 100644 index 00000000000..5d97b79876d --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).uplc.golden @@ -0,0 +1 @@ +(program 1.1.0 (\xs -> force mkCons 42 xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.budget.golden new file mode 100644 index 00000000000..aebcc3f4057 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.budget.golden @@ -0,0 +1,3 @@ +cpu: 2091812 +mem: 8694 +size: 53 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden new file mode 100644 index 00000000000..f217693e82c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden @@ -0,0 +1 @@ +(constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.pir.golden new file mode 100644 index 00000000000..b4f4af65b83 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.pir.golden @@ -0,0 +1,27 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool +in +letrec + !go : list bool -> Bool + = \(xs : list bool) -> + chooseList + {bool} + {all dead. Bool} + xs + (/\dead -> True) + (/\dead -> + let + !x : bool = headList {bool} xs + !xs : list bool = tailList {bool} xs + in + Bool_match + (ifThenElse {Bool} x True False) + {all dead. Bool} + (/\dead -> go xs) + (/\dead -> False) + {all dead. dead}) + {Bool} +in +\(xs : list bool) -> go xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.uplc.golden new file mode 100644 index 00000000000..196bca20f03 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.uplc.golden @@ -0,0 +1,19 @@ +(program + 1.1.0 + ((\go xs -> go xs) + ((\s -> s s) + (\s xs -> + force + (force (force chooseList) + xs + (delay (constr 0 [])) + (delay + ((\x -> + (\xs -> + force + (force ifThenElse + x + (delay (s s xs)) + (delay (constr 1 [])))) + (force tailList xs)) + (force headList xs)))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.budget.golden new file mode 100644 index 00000000000..3f0532d9475 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.budget.golden @@ -0,0 +1,3 @@ +cpu: 9002784 +mem: 33712 +size: 42 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden new file mode 100644 index 00000000000..3ee1061d2d0 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden @@ -0,0 +1 @@ +(con (list integer) [1,2,3,4,5,6,7,8,9,10,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.pir.golden new file mode 100644 index 00000000000..2cb7c10b472 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.pir.golden @@ -0,0 +1,25 @@ +\(xs : list integer) -> + (let + b = list integer + in + \(f : integer -> b -> b) (acc : b) -> + letrec + !go : list integer -> b + = \(xs : list integer) -> + chooseList + {integer} + {all dead. b} + xs + (/\dead -> acc) + (/\dead -> + let + !x : integer = headList {integer} xs + !xs : list integer = tailList {integer} xs + in + f x (go xs)) + {b} + in + go) + (mkCons {integer}) + xs + xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.uplc.golden new file mode 100644 index 00000000000..96fab57f85d --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.uplc.golden @@ -0,0 +1,14 @@ +(program + 1.1.0 + (\xs -> + (\s -> s s) + (\s xs -> + force + (force (force chooseList) + xs + (delay xs) + (delay + (force mkCons + (force headList xs) + ((\x -> s s x) (force tailList xs)))))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.budget.golden new file mode 100644 index 00000000000..8ed36ea0f3c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.budget.golden @@ -0,0 +1,3 @@ +cpu: 23678800 +mem: 97612 +size: 85 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden new file mode 100644 index 00000000000..3ee1061d2d0 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden @@ -0,0 +1 @@ +(con (list integer) [1,2,3,4,5,6,7,8,9,10,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden new file mode 100644 index 00000000000..653e769a48a --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden @@ -0,0 +1,51 @@ +let + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} +in +\(xs : list integer) -> + (letrec + !go : list (list integer) -> list integer + = caseList' + {list integer} + {list integer} + [] + (\(x : list integer) (xs : list (list integer)) -> + let + !r : list integer = go xs + in + (let + b = list integer + in + \(f : integer -> b -> b) (acc : b) -> + letrec + !go : list integer -> b + = caseList' + {integer} + {b} + acc + (\(x : integer) (xs : list integer) -> f x (go xs)) + in + go) + (mkCons {integer}) + r + x) + in + go) + (mkCons + {list integer} + xs + ((let + a = list integer + in + \(`$dMkNil` : (\arep -> list arep) a) (x : a) -> + mkCons {a} x `$dMkNil`) + [] + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden new file mode 100644 index 00000000000..3d0cdb2f9ed --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden @@ -0,0 +1,22 @@ +(program + 1.1.0 + (\xs -> + (\caseList' -> + (\s -> s s) + (\s -> + caseList' + [] + (\x xs -> + (\acc -> + (\s -> s s) + (\s -> + caseList' acc (\x xs -> force mkCons x (s s xs)))) + (s s xs) + x))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))) + (force mkCons xs (force mkCons xs [])))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.budget.golden index bf007a20f49..42417de0de0 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.budget.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.budget.golden @@ -1,2 +1,3 @@ -({cpu: 216462 -| mem: 1032}) \ No newline at end of file +cpu: 216462 +mem: 1032 +size: 9 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.budget.golden new file mode 100644 index 00000000000..a2606188654 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.budget.golden @@ -0,0 +1,3 @@ +cpu: 7834491 +mem: 32602 +size: 83 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden new file mode 100644 index 00000000000..e58cc9c2703 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden @@ -0,0 +1 @@ +(con (list integer) []) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.pir.golden new file mode 100644 index 00000000000..98ab693cfa1 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.pir.golden @@ -0,0 +1,32 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool +in +letrec + !drop : all a. (\arep -> list arep) a -> integer -> list a -> list a + = /\a -> + \(`$dMkNil` : (\arep -> list arep) a) (n : integer) (l : list a) -> + Bool_match + (ifThenElse {Bool} (lessThanEqualsInteger n 0) True False) + {all dead. list a} + (/\dead -> `$dMkNil`) + (/\dead -> + (let + r = list a + in + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r}) + `$dMkNil` + (\(ds : a) (xs : list a) -> + drop {a} `$dMkNil` (subtractInteger n 1) xs) + l) + {all dead. dead} +in +\(xs : list integer) -> drop {integer} [] 5 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden new file mode 100644 index 00000000000..c6573279a83 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden @@ -0,0 +1,25 @@ +(program + 1.1.0 + ((\drop xs -> force drop [] 5 xs) + ((\s -> s s) + (\s arg -> + delay + (\`$dMkNil` n l -> + force + (force ifThenElse + (lessThanEqualsInteger n 0) + (delay `$dMkNil`) + (delay + (force + (force (force chooseList) + l + (delay `$dMkNil`) + (delay + ((\ds xs -> + force (s s (delay (\x -> x))) + `$dMkNil` + (subtractInteger n 1) + xs) + (force headList l) + (force tailList l))))))))) + (delay (\x -> x))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.budget.golden new file mode 100644 index 00000000000..a0115dcd3f7 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.budget.golden @@ -0,0 +1,3 @@ +cpu: 5295830 +mem: 20590 +size: 54 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden new file mode 100644 index 00000000000..3a6e10d8766 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden @@ -0,0 +1 @@ +(con (list integer) [5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.pir.golden new file mode 100644 index 00000000000..221261db453 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.pir.golden @@ -0,0 +1,30 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool +in +letrec + !go : list integer -> list integer + = \(xs : list integer) -> + (let + r = list integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + [] + (\(x : integer) (xs' : list integer) -> + Bool_match + (ifThenElse {Bool} (lessThanInteger x 5) True False) + {all dead. list integer} + (/\dead -> go xs') + (/\dead -> xs) + {all dead. dead}) + xs +in +\(xs : list integer) -> go xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden new file mode 100644 index 00000000000..298568c5d68 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden @@ -0,0 +1,17 @@ +(program + 1.1.0 + ((\go xs -> go xs) + ((\s -> s s) + (\s xs -> + force + (force (force chooseList) + xs + (delay []) + (delay + ((\xs' -> + force + (force ifThenElse + (lessThanInteger (force headList xs) 5) + (delay (s s xs')) + (delay xs))) + (force tailList xs)))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.budget.golden new file mode 100644 index 00000000000..92d8c889f4c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.budget.golden @@ -0,0 +1,3 @@ +cpu: 11286024 +mem: 44712 +size: 57 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden new file mode 100644 index 00000000000..f217693e82c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden @@ -0,0 +1 @@ +(constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.pir.golden new file mode 100644 index 00000000000..de3fbfd9a10 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.pir.golden @@ -0,0 +1,27 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool +in +letrec + !go : list integer -> Bool + = \(xs : list integer) -> + chooseList + {integer} + {all dead. Bool} + xs + (/\dead -> False) + (/\dead -> + let + !x : integer = headList {integer} xs + !xs : list integer = tailList {integer} xs + in + Bool_match + (ifThenElse {Bool} (lessThanEqualsInteger x 0) True False) + {all dead. Bool} + (/\dead -> True) + (/\dead -> go xs) + {all dead. dead}) + {Bool} +in +\(xs : list integer) -> go xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.uplc.golden new file mode 100644 index 00000000000..8ecadadefad --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.uplc.golden @@ -0,0 +1,19 @@ +(program + 1.1.0 + ((\go xs -> go xs) + ((\s -> s s) + (\s xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + ((\x -> + (\xs -> + force + (force ifThenElse + (lessThanEqualsInteger x 0) + (delay (constr 0 [])) + (delay (s s xs)))) + (force tailList xs)) + (force headList xs)))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.budget.golden new file mode 100644 index 00000000000..5acec6cac96 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.budget.golden @@ -0,0 +1,3 @@ +cpu: 64100 +mem: 500 +size: 4 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden new file mode 100644 index 00000000000..e58cc9c2703 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden @@ -0,0 +1 @@ +(con (list integer) []) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.pir.golden new file mode 100644 index 00000000000..907987c8f2b --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.pir.golden @@ -0,0 +1 @@ +\(ds : list integer) -> [] \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.uplc.golden new file mode 100644 index 00000000000..c2725f32aa6 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.uplc.golden @@ -0,0 +1 @@ +(program 1.1.0 (\ds -> [])) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.budget.golden new file mode 100644 index 00000000000..d7ef144c6ce --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.budget.golden @@ -0,0 +1,3 @@ +cpu: 14524094 +mem: 54082 +size: 66 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden new file mode 100644 index 00000000000..41828d6c7f7 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden @@ -0,0 +1 @@ +(con (list integer) [2,4,6,8,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.pir.golden new file mode 100644 index 00000000000..992ee3c35f0 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.pir.golden @@ -0,0 +1,37 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool +in +\(xs : list integer) -> + (letrec + !go : list integer -> list integer + = (let + r = list integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + [] + (\(x : integer) (xs : list integer) -> + let + !xs : list integer = go xs + in + Bool_match + (ifThenElse + {Bool} + (equalsInteger 0 (modInteger x 2)) + True + False) + {all dead. list integer} + (/\dead -> mkCons {integer} x xs) + (/\dead -> xs) + {all dead. dead}) + in + go) + xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.uplc.golden new file mode 100644 index 00000000000..787246eefc0 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.uplc.golden @@ -0,0 +1,20 @@ +(program + 1.1.0 + (\xs -> + (\s -> s s) + (\s xs -> + force + (force (force chooseList) + xs + (delay []) + (delay + ((\x -> + (\xs -> + force + (force ifThenElse + (equalsInteger 0 (modInteger x 2)) + (delay (force mkCons x xs)) + (delay xs))) + ((\x -> s s x) (force tailList xs))) + (force headList xs))))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.budget.golden new file mode 100644 index 00000000000..085d5b78308 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.budget.golden @@ -0,0 +1,3 @@ +cpu: 5144480 +mem: 20098 +size: 67 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden new file mode 100644 index 00000000000..13675c87619 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden @@ -0,0 +1 @@ +(constr 0 (con integer 3)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.pir.golden new file mode 100644 index 00000000000..f958ac99c46 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.pir.golden @@ -0,0 +1,32 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool + data (Maybe :: * -> *) a | Maybe_match where + Just : a -> Maybe a + Nothing : Maybe a +in +letrec + !go : integer -> list integer -> Maybe integer + = \(i : integer) -> + (let + r = Maybe integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + (Nothing {integer}) + (\(x : integer) (xs : list integer) -> + Bool_match + (ifThenElse {Bool} (equalsInteger 4 x) True False) + {all dead. Maybe integer} + (/\dead -> Just {integer} i) + (/\dead -> go (addInteger 1 i) xs) + {all dead. dead}) +in +\(xs : list integer) -> go 0 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.uplc.golden new file mode 100644 index 00000000000..bcc1a4f3992 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.uplc.golden @@ -0,0 +1,17 @@ +(program + 1.1.0 + ((\go xs -> go 0 xs) + ((\s -> s s) + (\s i xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + ((\xs -> + force + (force ifThenElse + (equalsInteger 4 (force headList xs)) + (delay (constr 0 [i])) + (delay ((\x -> s s x) (addInteger 1 i) xs)))) + (force tailList xs)))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.budget.golden new file mode 100644 index 00000000000..43166bb930d --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.budget.golden @@ -0,0 +1,3 @@ +cpu: 13551064 +mem: 52032 +size: 67 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden new file mode 100644 index 00000000000..f217693e82c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden @@ -0,0 +1 @@ +(constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.pir.golden new file mode 100644 index 00000000000..25c92f13699 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.pir.golden @@ -0,0 +1,32 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool + data (Maybe :: * -> *) a | Maybe_match where + Just : a -> Maybe a + Nothing : Maybe a +in +letrec + !go : integer -> list integer -> Maybe integer + = \(i : integer) -> + (let + r = Maybe integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + (Nothing {integer}) + (\(x : integer) (xs : list integer) -> + Bool_match + (ifThenElse {Bool} (equalsInteger 99 x) True False) + {all dead. Maybe integer} + (/\dead -> Just {integer} i) + (/\dead -> go (addInteger 1 i) xs) + {all dead. dead}) +in +\(xs : list integer) -> go 0 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.uplc.golden new file mode 100644 index 00000000000..99ad4a6b8d8 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.uplc.golden @@ -0,0 +1,17 @@ +(program + 1.1.0 + ((\go xs -> go 0 xs) + ((\s -> s s) + (\s i xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + ((\xs -> + force + (force ifThenElse + (equalsInteger 99 (force headList xs)) + (delay (constr 0 [i])) + (delay ((\x -> s s x) (addInteger 1 i) xs)))) + (force tailList xs)))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.budget.golden new file mode 100644 index 00000000000..4501200a757 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.budget.golden @@ -0,0 +1,3 @@ +cpu: 17232174 +mem: 64702 +size: 81 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden new file mode 100644 index 00000000000..2f184a3b84b --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden @@ -0,0 +1 @@ +(con (list integer) [0,2,4,6,8]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.pir.golden new file mode 100644 index 00000000000..28c9d47971a --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.pir.golden @@ -0,0 +1,41 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool +in +letrec + !go : integer -> list integer -> list integer + = \(i : integer) -> + (let + r = list integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + [] + (\(x : integer) (xs : list integer) -> + let + !indices : list integer = go (addInteger 1 i) xs + in + Bool_match + (Bool_match + (ifThenElse + {Bool} + (equalsInteger 0 (modInteger x 2)) + True + False) + {all dead. Bool} + (/\dead -> False) + (/\dead -> True) + {all dead. dead}) + {all dead. list integer} + (/\dead -> mkCons {integer} i indices) + (/\dead -> indices) + {all dead. dead}) +in +\(xs : list integer) -> go 0 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.uplc.golden new file mode 100644 index 00000000000..9e292caca94 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.uplc.golden @@ -0,0 +1,20 @@ +(program + 1.1.0 + ((\go xs -> go 0 xs) + ((\s -> s s) + (\s i xs -> + force + (force (force chooseList) + xs + (delay []) + (delay + ((\x xs -> + (\indices -> + force + (force ifThenElse + (equalsInteger 0 (modInteger x 2)) + (delay indices) + (delay (force mkCons i indices)))) + ((\x -> s s x) (addInteger 1 i) xs)) + (force headList xs) + (force tailList xs)))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.budget.golden new file mode 100644 index 00000000000..f9bf03bd822 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.budget.golden @@ -0,0 +1,3 @@ +cpu: 10564694 +mem: 42012 +size: 55 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden new file mode 100644 index 00000000000..b23026d4762 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden @@ -0,0 +1 @@ +(con integer 0) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.pir.golden new file mode 100644 index 00000000000..7862d8270ca --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.pir.golden @@ -0,0 +1,17 @@ +letrec + !go : integer -> list integer -> integer + = \(acc : integer) (xs : list integer) -> + chooseList + {integer} + {all dead. integer} + xs + (/\dead -> acc) + (/\dead -> + let + !x : integer = headList {integer} xs + !xs : list integer = tailList {integer} xs + in + go (multiplyInteger acc x) xs) + {integer} +in +\(xs : list integer) -> go 0 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden new file mode 100644 index 00000000000..8322b8d50f8 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden @@ -0,0 +1,14 @@ +(program + 1.1.0 + ((\go xs -> go 0 xs) + ((\s -> s s) + (\s acc xs -> + force + (force (force chooseList) + xs + (delay acc) + (delay + ((\x -> + (\xs -> (\x -> s s x) (multiplyInteger acc x) xs) + (force tailList xs)) + (force headList xs)))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.budget.golden new file mode 100644 index 00000000000..5bc45bc907f --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.budget.golden @@ -0,0 +1,3 @@ +cpu: 9179244 +mem: 32712 +size: 44 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden new file mode 100644 index 00000000000..0dc9ac9d664 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden @@ -0,0 +1 @@ +(con integer 55) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.pir.golden new file mode 100644 index 00000000000..a12b587ff2a --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.pir.golden @@ -0,0 +1,13 @@ +letrec + !go : list integer -> integer + = \(xs : list integer) -> + chooseList + {integer} + {all dead. integer} + xs + (/\dead -> 0) + (/\dead -> + addInteger (headList {integer} xs) (go (tailList {integer} xs))) + {integer} +in +\(xs : list integer) -> go xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.uplc.golden new file mode 100644 index 00000000000..fe0abf441a2 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.uplc.golden @@ -0,0 +1,13 @@ +(program + 1.1.0 + ((\go xs -> go xs) + ((\s -> s s) + (\s xs -> + force + (force (force chooseList) + xs + (delay 0) + (delay + (addInteger + (force headList xs) + ((\x -> s s x) (force tailList xs))))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.budget.golden new file mode 100644 index 00000000000..4e7df0819aa --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.budget.golden @@ -0,0 +1,5 @@ +An error has occurred: +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. +Final budget: ({cpu: 192592 +| mem: 164}) +Logs: PT23 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.eval.golden new file mode 100644 index 00000000000..f2c04fe10eb --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.eval.golden @@ -0,0 +1,2 @@ +An error has occurred: +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.pir.golden new file mode 100644 index 00000000000..ba3a37864af --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.pir.golden @@ -0,0 +1,24 @@ +let + data Unit | Unit_match where + Unit : Unit +in +\(ds : list integer) -> + (let + r = Unit -> integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + (\(ds : Unit) -> + let + !x : Unit = trace {Unit} "PT23" Unit + in + error {integer}) + (\(x : integer) (xs : list integer) (ds : Unit) -> x) + [] + Unit \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.uplc.golden new file mode 100644 index 00000000000..793b96b43d4 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.uplc.golden @@ -0,0 +1,9 @@ +(program + 1.1.0 + (\ds -> + force + (force (force chooseList) + [] + (delay (\ds -> (\x -> error) (force trace "PT23" (constr 0 [])))) + (delay ((\x xs ds -> x) (force headList []) (force tailList [])))) + (constr 0 []))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.budget.golden new file mode 100644 index 00000000000..558d423b840 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.budget.golden @@ -0,0 +1,3 @@ +cpu: 761907 +mem: 3096 +size: 39 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden new file mode 100644 index 00000000000..132831f390c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden @@ -0,0 +1 @@ +(con integer 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.pir.golden new file mode 100644 index 00000000000..de4295e6e50 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.pir.golden @@ -0,0 +1,24 @@ +let + data Unit | Unit_match where + Unit : Unit +in +\(xs : list integer) -> + (let + r = Unit -> integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + (\(ds : Unit) -> + let + !x : Unit = trace {Unit} "PT23" Unit + in + error {integer}) + (\(x : integer) (xs : list integer) (ds : Unit) -> x) + xs + Unit \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.uplc.golden new file mode 100644 index 00000000000..8a8d6b52439 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.uplc.golden @@ -0,0 +1,9 @@ +(program + 1.1.0 + (\xs -> + force + (force (force chooseList) + xs + (delay (\ds -> (\x -> error) (force trace "PT23" (constr 0 [])))) + (delay ((\x xs ds -> x) (force headList xs) (force tailList xs)))) + (constr 0 []))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.budget.golden new file mode 100644 index 00000000000..18bc78eee2a --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.budget.golden @@ -0,0 +1,5 @@ +An error has occurred: +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. +Final budget: ({cpu: 192592 +| mem: 164}) +Logs: PT25 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.eval.golden new file mode 100644 index 00000000000..f2c04fe10eb --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.eval.golden @@ -0,0 +1,2 @@ +An error has occurred: +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.pir.golden new file mode 100644 index 00000000000..b7c27a9bfab --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.pir.golden @@ -0,0 +1,32 @@ +let + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + data Unit | Unit_match where + Unit : Unit +in +letrec + !last : all a. list a -> a + = /\a -> + \(l : list a) -> + caseList' + {a} + {Unit -> a} + (\(ds : Unit) -> + let + !x : Unit = trace {Unit} "PT25" Unit + in + error {a}) + (\(x : a) (xs : list a) (ds : Unit) -> + caseList' {a} {a} x (\(ds : a) -> last {a}) xs) + l + Unit +in +\(ds : list integer) -> last {integer} [] \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden new file mode 100644 index 00000000000..64812a5b424 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden @@ -0,0 +1,21 @@ +(program + 1.1.0 + ((\caseList' -> + (\last ds -> force last []) + ((\s -> s s) + (\s arg -> + delay + (\l -> + caseList' + (\ds -> (\x -> error) (force trace "PT25" (constr 0 []))) + (\x xs ds -> + caseList' x (\ds -> force (s s (delay (\x -> x)))) xs) + l + (constr 0 []))) + (delay (\x -> x)))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.budget.golden new file mode 100644 index 00000000000..eeb1a0d0604 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.budget.golden @@ -0,0 +1,5 @@ +An error has occurred: +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. +Final budget: ({cpu: 9570662 +| mem: 41124}) +Logs: PT25 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden new file mode 100644 index 00000000000..f2c04fe10eb --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden @@ -0,0 +1,2 @@ +An error has occurred: +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.pir.golden new file mode 100644 index 00000000000..ec52654da5d --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.pir.golden @@ -0,0 +1,32 @@ +let + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + data Unit | Unit_match where + Unit : Unit +in +letrec + !last : all a. list a -> a + = /\a -> + \(l : list a) -> + caseList' + {a} + {Unit -> a} + (\(ds : Unit) -> + let + !x : Unit = trace {Unit} "PT25" Unit + in + error {a}) + (\(x : a) (xs : list a) (ds : Unit) -> + caseList' {a} {a} x (\(ds : a) -> last {a}) xs) + l + Unit +in +\(xs : list integer) -> last {integer} xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden new file mode 100644 index 00000000000..c1ed70ae53a --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden @@ -0,0 +1,21 @@ +(program + 1.1.0 + ((\caseList' -> + (\last xs -> force last xs) + ((\s -> s s) + (\s arg -> + delay + (\l -> + caseList' + (\ds -> (\x -> error) (force trace "PT25" (constr 0 []))) + (\x xs ds -> + caseList' x (\ds -> force (s s (delay (\x -> x)))) xs) + l + (constr 0 []))) + (delay (\x -> x)))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.budget.golden new file mode 100644 index 00000000000..e4bd625c510 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.budget.golden @@ -0,0 +1,3 @@ +cpu: 9659244 +mem: 35712 +size: 47 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden new file mode 100644 index 00000000000..3df7275df82 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden @@ -0,0 +1 @@ +(con integer 10) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.pir.golden new file mode 100644 index 00000000000..d008c120106 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.pir.golden @@ -0,0 +1,16 @@ +letrec + !go : list integer -> integer + = \(xs : list integer) -> + chooseList + {integer} + {all dead. integer} + xs + (/\dead -> 0) + (/\dead -> + let + !x : integer = headList {integer} xs + in + addInteger 1 (go (tailList {integer} xs))) + {integer} +in +\(xs : list integer) -> go xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.uplc.golden new file mode 100644 index 00000000000..51889e0d1ec --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.uplc.golden @@ -0,0 +1,12 @@ +(program + 1.1.0 + ((\go xs -> go xs) + ((\s -> s s) + (\s xs -> + force + (force (force chooseList) + xs + (delay 0) + (delay + ((\x -> addInteger 1 ((\x -> s s x) (force tailList xs))) + (force headList xs)))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.budget.golden new file mode 100644 index 00000000000..8c448704111 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.budget.golden @@ -0,0 +1,3 @@ +cpu: 681907 +mem: 2596 +size: 25 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden new file mode 100644 index 00000000000..005b0a452f3 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden @@ -0,0 +1 @@ +(constr 0 (con integer 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.pir.golden new file mode 100644 index 00000000000..e3b39197e86 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.pir.golden @@ -0,0 +1,20 @@ +let + data (Maybe :: * -> *) a | Maybe_match where + Just : a -> Maybe a + Nothing : Maybe a +in +\(xs : list integer) -> + (let + r = Maybe integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + (Nothing {integer}) + (\(x : integer) (ds : list integer) -> Just {integer} x) + xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.uplc.golden new file mode 100644 index 00000000000..6e71d21bd03 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.uplc.golden @@ -0,0 +1,9 @@ +(program + 1.1.0 + (\xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + ((\ds -> constr 0 [(force headList xs)]) (force tailList xs)))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.budget.golden new file mode 100644 index 00000000000..cf66fde6a2c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.budget.golden @@ -0,0 +1,3 @@ +cpu: 357094 +mem: 1532 +size: 25 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden new file mode 100644 index 00000000000..f217693e82c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden @@ -0,0 +1 @@ +(constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.pir.golden new file mode 100644 index 00000000000..d5b9c329d17 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.pir.golden @@ -0,0 +1,20 @@ +let + data (Maybe :: * -> *) a | Maybe_match where + Just : a -> Maybe a + Nothing : Maybe a +in +\(ds : list integer) -> + (let + r = Maybe integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + (Nothing {integer}) + (\(x : integer) (ds : list integer) -> Just {integer} x) + [] \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.uplc.golden new file mode 100644 index 00000000000..65216008d85 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.uplc.golden @@ -0,0 +1,9 @@ +(program + 1.1.0 + (\ds -> + force + (force (force chooseList) + [] + (delay (constr 1 [])) + (delay + ((\ds -> constr 0 [(force headList [])]) (force tailList [])))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden index 5dd2d08364f..124103bfe9f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden @@ -1,18 +1,12 @@ (program 1.1.0 - (force - ((\s -> s s) - (\s arg -> - delay - (\xs -> - force - (force (force chooseList) - xs - (delay []) - (delay - ((\xs -> - force mkCons - (addInteger 1 (force headList xs)) - (force (s s (delay (\x -> x))) xs)) - (force tailList xs)))))) - (delay (\x -> x))))) + ((\s -> s s) + (\s xs -> + force + (force (force chooseList) + xs + (delay []) + (delay + ((\xs -> + force mkCons (addInteger 1 (force headList xs)) (s s xs)) + (force tailList xs))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.budget.golden new file mode 100644 index 00000000000..807ec259d6e --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.budget.golden @@ -0,0 +1,3 @@ +cpu: 14844094 +mem: 56082 +size: 75 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden new file mode 100644 index 00000000000..658d1c3fa5c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden @@ -0,0 +1 @@ +(con (list integer) [1,3,5,7,9]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.pir.golden new file mode 100644 index 00000000000..201fff9c3e9 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.pir.golden @@ -0,0 +1,48 @@ +let + data (Maybe :: * -> *) a | Maybe_match where + Just : a -> Maybe a + Nothing : Maybe a + data Bool | Bool_match where + True : Bool + False : Bool +in +\(xs : list integer) -> + (letrec + !go : list integer -> list integer + = (let + r = list integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + [] + (\(x : integer) (xs : list integer) -> + Maybe_match + {integer} + (Bool_match + (Bool_match + (ifThenElse + {Bool} + (equalsInteger 0 (modInteger x 2)) + True + False) + {all dead. Bool} + (/\dead -> False) + (/\dead -> True) + {all dead. dead}) + {all dead. Maybe integer} + (/\dead -> Just {integer} x) + (/\dead -> Nothing {integer}) + {all dead. dead}) + {all dead. list integer} + (\(y : integer) -> /\dead -> mkCons {integer} y (go xs)) + (/\dead -> go xs) + {all dead. dead}) + in + go) + xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.uplc.golden new file mode 100644 index 00000000000..dda4598cd03 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.uplc.golden @@ -0,0 +1,23 @@ +(program + 1.1.0 + (\xs -> + (\s -> s s) + (\s xs -> + force + (force (force chooseList) + xs + (delay []) + (delay + ((\x xs -> + force + (case + (force + (force ifThenElse + (equalsInteger 0 (modInteger x 2)) + (delay (constr 1 [])) + (delay (constr 0 [x])))) + [ (\y -> delay (force mkCons y (s s xs))) + , (delay (s s xs)) ])) + (force headList xs) + (force tailList xs))))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.budget.golden new file mode 100644 index 00000000000..eb294710d33 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.budget.golden @@ -0,0 +1,3 @@ +cpu: 11434984 +mem: 45112 +size: 63 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden new file mode 100644 index 00000000000..1dd2b8ed5d3 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden @@ -0,0 +1 @@ +(constr 0) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.pir.golden new file mode 100644 index 00000000000..3f9860f20b1 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.pir.golden @@ -0,0 +1,33 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool +in +letrec + !go : list integer -> Bool + = \(xs : list integer) -> + chooseList + {integer} + {all dead. Bool} + xs + (/\dead -> False) + (/\dead -> + let + !x : integer = headList {integer} xs + !xs : list integer = tailList {integer} xs + in + Bool_match + (ifThenElse {Bool} (equalsInteger 42 x) True False) + {all dead. Bool} + (/\dead -> True) + (/\dead -> go xs) + {all dead. dead}) + {Bool} +in +\(xs : list integer) -> + Bool_match + (go xs) + {all dead. Bool} + (/\dead -> False) + (/\dead -> True) + {all dead. dead} \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.uplc.golden new file mode 100644 index 00000000000..3e44f6c9204 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.uplc.golden @@ -0,0 +1,20 @@ +(program + 1.1.0 + ((\go xs -> + force (case (go xs) [(delay (constr 1 [])), (delay (constr 0 []))])) + ((\s -> s s) + (\s xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + ((\x -> + (\xs -> + force + (force ifThenElse + (equalsInteger 42 x) + (delay (constr 0 [])) + (delay (s s xs)))) + (force tailList xs)) + (force headList xs)))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden new file mode 100644 index 00000000000..86d1e402861 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden @@ -0,0 +1,50 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} +in +letrec + !go : list integer -> list integer -> list integer + = \(xs : list integer) -> + caseList' + {integer} + {list integer} + [] + (\(y : integer) (ys : list integer) -> + Bool_match + ((letrec + !go : list integer -> Bool + = caseList' + {integer} + {Bool} + False + (\(x : integer) (xs : list integer) -> + Bool_match + (ifThenElse + {Bool} + (equalsInteger x y) + True + False) + {all dead. Bool} + (/\dead -> True) + (/\dead -> go xs) + {all dead. dead}) + in + go) + xs) + {all dead. list integer} + (/\dead -> go ys xs) + (/\dead -> mkCons {integer} y (go ys (mkCons {integer} y xs))) + {all dead. dead}) +in +\(xs : list integer) -> go [] xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden new file mode 100644 index 00000000000..a4202fc1abe --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden @@ -0,0 +1,33 @@ +(program + 1.1.0 + ((\caseList' -> + (\go xs -> go [] xs) + ((\s -> s s) + (\s xs -> + caseList' + [] + (\y ys -> + force + (case + ((\s -> s s) + (\s -> + caseList' + (constr 1 []) + (\x xs -> + force + (force ifThenElse + (equalsInteger x y) + (delay (constr 0 [])) + (delay (s s xs))))) + xs) + [ (delay (s s ys xs)) + , (delay + (force mkCons + y + (s s ys (force mkCons y xs)))) ]))))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.budget.golden new file mode 100644 index 00000000000..6f831e88dc3 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.budget.golden @@ -0,0 +1,3 @@ +cpu: 4705572 +mem: 21018 +size: 111 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden new file mode 100644 index 00000000000..d7ab80beb57 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden @@ -0,0 +1 @@ +(con (list integer) [1]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden new file mode 100644 index 00000000000..764882df8e1 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden @@ -0,0 +1,50 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} +in +letrec + !go : list integer -> list integer -> list integer + = \(xs : list integer) -> + caseList' + {integer} + {list integer} + [] + (\(y : integer) (ys : list integer) -> + Bool_match + ((letrec + !go : list integer -> Bool + = caseList' + {integer} + {Bool} + False + (\(x : integer) (xs : list integer) -> + Bool_match + (ifThenElse + {Bool} + (lessThanInteger x y) + False + True) + {all dead. Bool} + (/\dead -> True) + (/\dead -> go xs) + {all dead. dead}) + in + go) + xs) + {all dead. list integer} + (/\dead -> go ys xs) + (/\dead -> mkCons {integer} y (go ys (mkCons {integer} y xs))) + {all dead. dead}) +in +\(xs : list integer) -> go [] xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden new file mode 100644 index 00000000000..c1e8c095e64 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden @@ -0,0 +1,33 @@ +(program + 1.1.0 + ((\caseList' -> + (\go xs -> go [] xs) + ((\s -> s s) + (\s xs -> + caseList' + [] + (\y ys -> + force + (case + ((\s -> s s) + (\s -> + caseList' + (constr 1 []) + (\x xs -> + force + (force ifThenElse + (lessThanInteger x y) + (delay (s s xs)) + (delay (constr 0 []))))) + xs) + [ (delay (s s ys xs)) + , (delay + (force mkCons + y + (s s ys (force mkCons y xs)))) ]))))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.budget.golden new file mode 100644 index 00000000000..44cc03385cb --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.budget.golden @@ -0,0 +1,3 @@ +cpu: 374582 +mem: 1533 +size: 14 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden new file mode 100644 index 00000000000..f217693e82c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden @@ -0,0 +1 @@ +(constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.pir.golden new file mode 100644 index 00000000000..34e911a928f --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.pir.golden @@ -0,0 +1,6 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool +in +\(xs : list integer) -> ifThenElse {Bool} (nullList {integer} xs) True False \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.uplc.golden new file mode 100644 index 00000000000..05a9d295460 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.uplc.golden @@ -0,0 +1,3 @@ +(program + 1.1.0 + (\xs -> force ifThenElse (force nullList xs) (constr 0 []) (constr 1 []))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.budget.golden new file mode 100644 index 00000000000..69d06c3c39b --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.budget.golden @@ -0,0 +1,3 @@ +cpu: 1125956 +mem: 4897 +size: 53 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden new file mode 100644 index 00000000000..1dd2b8ed5d3 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden @@ -0,0 +1 @@ +(constr 0) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.pir.golden new file mode 100644 index 00000000000..2a026ae4c03 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.pir.golden @@ -0,0 +1,27 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool +in +letrec + !go : list bool -> Bool + = \(xs : list bool) -> + chooseList + {bool} + {all dead. Bool} + xs + (/\dead -> False) + (/\dead -> + let + !x : bool = headList {bool} xs + !xs : list bool = tailList {bool} xs + in + Bool_match + (ifThenElse {Bool} x True False) + {all dead. Bool} + (/\dead -> True) + (/\dead -> go xs) + {all dead. dead}) + {Bool} +in +\(xs : list bool) -> go xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.uplc.golden new file mode 100644 index 00000000000..6899fdc8a6f --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.uplc.golden @@ -0,0 +1,19 @@ +(program + 1.1.0 + ((\go xs -> go xs) + ((\s -> s s) + (\s xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + ((\x -> + (\xs -> + force + (force ifThenElse + x + (delay (constr 0 [])) + (delay (s s xs)))) + (force tailList xs)) + (force headList xs)))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.budget.golden new file mode 100644 index 00000000000..75722453e18 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.budget.golden @@ -0,0 +1,3 @@ +cpu: 8478546 +mem: 34362 +size: 46 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden new file mode 100644 index 00000000000..7c7c2a59e12 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden @@ -0,0 +1 @@ +(con (list integer) [0,0,0,0,0,0,0,0,0,0]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.pir.golden new file mode 100644 index 00000000000..bfc7347272d --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.pir.golden @@ -0,0 +1,16 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool +in +letrec + !go : integer -> list integer + = \(n : integer) -> + Bool_match + (ifThenElse {Bool} (lessThanEqualsInteger n 0) True False) + {all dead. list integer} + (/\dead -> []) + (/\dead -> mkCons {integer} 0 (go (subtractInteger n 1))) + {all dead. dead} +in +\(ds : list integer) -> go 10 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.uplc.golden new file mode 100644 index 00000000000..79a2423792c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.uplc.golden @@ -0,0 +1,11 @@ +(program + 1.1.0 + ((\go ds -> go 10) + ((\s -> s s) + (\s n -> + force + (force ifThenElse + (lessThanEqualsInteger n 0) + (delay []) + (delay + (force mkCons 0 ((\x -> s s x) (subtractInteger n 1))))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.budget.golden new file mode 100644 index 00000000000..443cf79e380 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.budget.golden @@ -0,0 +1,3 @@ +cpu: 10938784 +mem: 45812 +size: 65 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden new file mode 100644 index 00000000000..be17fceb5b5 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden @@ -0,0 +1 @@ +(con (list integer) [10,9,8,7,6,5,4,3,2,1,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.pir.golden new file mode 100644 index 00000000000..947476915ae --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.pir.golden @@ -0,0 +1,20 @@ +letrec + !revAppend : all a. list a -> list a -> list a + = /\a -> + \(l : list a) (r : list a) -> + (let + r = list a + in + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r}) + r + (\(x : a) (xs : list a) -> revAppend {a} xs (mkCons {a} x r)) + l +in +\(xs : list integer) -> revAppend {integer} xs xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.uplc.golden new file mode 100644 index 00000000000..5d2e2ecdf08 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.uplc.golden @@ -0,0 +1,19 @@ +(program + 1.1.0 + ((\revAppend xs -> force revAppend xs xs) + ((\s -> s s) + (\s arg -> + delay + (\l r -> + force + (force (force chooseList) + l + (delay r) + (delay + ((\x xs -> + force (s s (delay (\x -> x))) + xs + (force mkCons x r)) + (force headList l) + (force tailList l)))))) + (delay (\x -> x))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.budget.golden new file mode 100644 index 00000000000..443cf79e380 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.budget.golden @@ -0,0 +1,3 @@ +cpu: 10938784 +mem: 45812 +size: 65 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden new file mode 100644 index 00000000000..e2799de9624 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden @@ -0,0 +1 @@ +(con (list integer) [10,9,8,7,6,5,4,3,2,1]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.pir.golden new file mode 100644 index 00000000000..3d1eee382e9 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.pir.golden @@ -0,0 +1,20 @@ +letrec + !revAppend : all a. list a -> list a -> list a + = /\a -> + \(l : list a) (r : list a) -> + (let + r = list a + in + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r}) + r + (\(x : a) (xs : list a) -> revAppend {a} xs (mkCons {a} x r)) + l +in +\(xs : list integer) -> revAppend {integer} xs [] \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.uplc.golden new file mode 100644 index 00000000000..8f3d26881e8 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.uplc.golden @@ -0,0 +1,19 @@ +(program + 1.1.0 + ((\revAppend xs -> force revAppend xs []) + ((\s -> s s) + (\s arg -> + delay + (\l r -> + force + (force (force chooseList) + l + (delay r) + (delay + ((\x xs -> + force (s s (delay (\x -> x))) + xs + (force mkCons x r)) + (force headList l) + (force tailList l)))))) + (delay (\x -> x))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.budget.golden new file mode 100644 index 00000000000..5acec6cac96 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.budget.golden @@ -0,0 +1,3 @@ +cpu: 64100 +mem: 500 +size: 4 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden new file mode 100644 index 00000000000..d7ab80beb57 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden @@ -0,0 +1 @@ +(con (list integer) [1]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.pir.golden new file mode 100644 index 00000000000..0f64ef8492e --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.pir.golden @@ -0,0 +1 @@ +\(ds : list integer) -> [1] \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden new file mode 100644 index 00000000000..d7c5977f73c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden @@ -0,0 +1 @@ +(program 1.1.0 (\ds -> [1])) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.budget.golden new file mode 100644 index 00000000000..18bc78eee2a --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.budget.golden @@ -0,0 +1,5 @@ +An error has occurred: +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. +Final budget: ({cpu: 192592 +| mem: 164}) +Logs: PT25 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.eval.golden new file mode 100644 index 00000000000..f2c04fe10eb --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.eval.golden @@ -0,0 +1,2 @@ +An error has occurred: +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.pir.golden new file mode 100644 index 00000000000..ba8b0f02986 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.pir.golden @@ -0,0 +1,33 @@ +let + data Unit | Unit_match where + Unit : Unit +in +\(ds : list integer) -> + (let + r = list integer + in + \(nilCase : Unit -> r) + (consCase : integer -> list integer -> r) + (l : list integer) -> + (let + r = Unit -> r + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + nilCase + (\(x : integer) (xs : list integer) (ds : Unit) -> consCase x xs) + l + Unit) + (\(ds : Unit) -> + let + !x : Unit = trace {Unit} "PT25" Unit + in + error {list integer}) + (\(ds : integer) (xs : list integer) -> xs) + [] \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.uplc.golden new file mode 100644 index 00000000000..bf34b9f1680 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.uplc.golden @@ -0,0 +1,9 @@ +(program + 1.1.0 + (\ds -> + force + (force (force chooseList) + [] + (delay (\ds -> (\x -> error) (force trace "PT25" (constr 0 [])))) + (delay ((\x xs ds -> xs) (force headList []) (force tailList [])))) + (constr 0 []))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.budget.golden new file mode 100644 index 00000000000..558d423b840 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.budget.golden @@ -0,0 +1,3 @@ +cpu: 761907 +mem: 3096 +size: 39 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden new file mode 100644 index 00000000000..af0310fec0b --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden @@ -0,0 +1 @@ +(con (list integer) [2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.pir.golden new file mode 100644 index 00000000000..f263763145a --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.pir.golden @@ -0,0 +1,33 @@ +let + data Unit | Unit_match where + Unit : Unit +in +\(xs : list integer) -> + (let + r = list integer + in + \(nilCase : Unit -> r) + (consCase : integer -> list integer -> r) + (l : list integer) -> + (let + r = Unit -> r + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + nilCase + (\(x : integer) (xs : list integer) (ds : Unit) -> consCase x xs) + l + Unit) + (\(ds : Unit) -> + let + !x : Unit = trace {Unit} "PT25" Unit + in + error {list integer}) + (\(ds : integer) (xs : list integer) -> xs) + xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.uplc.golden new file mode 100644 index 00000000000..266a36fc6ba --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.uplc.golden @@ -0,0 +1,9 @@ +(program + 1.1.0 + (\xs -> + force + (force (force chooseList) + xs + (delay (\ds -> (\x -> error) (force trace "PT25" (constr 0 [])))) + (delay ((\x xs ds -> xs) (force headList xs) (force tailList xs)))) + (constr 0 []))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.budget.golden new file mode 100644 index 00000000000..6842d2d00dd --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.budget.golden @@ -0,0 +1,3 @@ +cpu: 8356301 +mem: 33762 +size: 85 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden new file mode 100644 index 00000000000..5a97069a30a --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden @@ -0,0 +1 @@ +(con (list integer) [1,2,3,4,5]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.pir.golden new file mode 100644 index 00000000000..4b4566fc10f --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.pir.golden @@ -0,0 +1,32 @@ +let + data Bool | Bool_match where + True : Bool + False : Bool +in +letrec + !take : all a. (\arep -> list arep) a -> integer -> list a -> list a + = /\a -> + \(`$dMkNil` : (\arep -> list arep) a) (n : integer) (l : list a) -> + Bool_match + (ifThenElse {Bool} (lessThanEqualsInteger n 0) True False) + {all dead. list a} + (/\dead -> `$dMkNil`) + (/\dead -> + (let + r = list a + in + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r}) + `$dMkNil` + (\(x : a) (xs : list a) -> + mkCons {a} x (take {a} `$dMkNil` (subtractInteger n 1) xs)) + l) + {all dead. dead} +in +\(xs : list integer) -> take {integer} [] 5 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.uplc.golden new file mode 100644 index 00000000000..0b887c563e4 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.uplc.golden @@ -0,0 +1,26 @@ +(program + 1.1.0 + ((\take xs -> force take [] 5 xs) + ((\s -> s s) + (\s arg -> + delay + (\`$dMkNil` n l -> + force + (force ifThenElse + (lessThanEqualsInteger n 0) + (delay `$dMkNil`) + (delay + (force + (force (force chooseList) + l + (delay `$dMkNil`) + (delay + ((\xs -> + force mkCons + (force headList l) + (force (s s (delay (\x -> x))) + `$dMkNil` + (subtractInteger n 1) + xs)) + (force tailList l))))))))) + (delay (\x -> x))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.budget.golden index 59608b99532..f397d477904 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.budget.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.budget.golden @@ -1,2 +1,3 @@ -({cpu: 665907 -| mem: 2496}) \ No newline at end of file +cpu: 665907 +mem: 2496 +size: 24 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.budget.golden index 8f2c634b339..8bcd39377af 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.budget.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.budget.golden @@ -1,2 +1,3 @@ -({cpu: 357094 -| mem: 1532}) \ No newline at end of file +cpu: 357094 +mem: 1532 +size: 24 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.budget.golden new file mode 100644 index 00000000000..d57cd589ec3 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.budget.golden @@ -0,0 +1,3 @@ +cpu: 1667714 +mem: 6992 +size: 45 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden new file mode 100644 index 00000000000..f217693e82c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden @@ -0,0 +1 @@ +(constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.pir.golden new file mode 100644 index 00000000000..fa07c55ff0f --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.pir.golden @@ -0,0 +1,27 @@ +let + data (Maybe :: * -> *) a | Maybe_match where + Just : a -> Maybe a + Nothing : Maybe a + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} +in +\(xs : list integer) -> + caseList' + {integer} + {Maybe integer} + (Nothing {integer}) + (\(x : integer) -> + caseList' + {integer} + {Maybe integer} + (Just {integer} x) + (\(ds : integer) (ds : list integer) -> Nothing {integer})) + xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden new file mode 100644 index 00000000000..3d6b3af2588 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden @@ -0,0 +1,14 @@ +(program + 1.1.0 + (\xs -> + (\caseList' -> + caseList' + (constr 1 []) + (\x -> caseList' (constr 0 [x]) (\ds ds -> constr 1 []))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.budget.golden new file mode 100644 index 00000000000..61d87258cfd --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.budget.golden @@ -0,0 +1,3 @@ +cpu: 549094 +mem: 2732 +size: 45 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden new file mode 100644 index 00000000000..f217693e82c --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden @@ -0,0 +1 @@ +(constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.pir.golden new file mode 100644 index 00000000000..efb969694c4 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.pir.golden @@ -0,0 +1,27 @@ +let + data (Maybe :: * -> *) a | Maybe_match where + Just : a -> Maybe a + Nothing : Maybe a + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} +in +\(ds : list integer) -> + caseList' + {integer} + {Maybe integer} + (Nothing {integer}) + (\(x : integer) -> + caseList' + {integer} + {Maybe integer} + (Just {integer} x) + (\(ds : integer) (ds : list integer) -> Nothing {integer})) + [] \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.uplc.golden new file mode 100644 index 00000000000..61a01732fec --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.uplc.golden @@ -0,0 +1,14 @@ +(program + 1.1.0 + (\ds -> + (\caseList' -> + caseList' + (constr 1 []) + (\x -> caseList' (constr 0 [x]) (\ds ds -> constr 1 []))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))) + [])) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index f3f50fe9b42..57a2096b34f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -19,7 +19,8 @@ tests :: TestNested tests = testNested ("BuiltinList" "Budget") . pure $ testNestedGhc - [ goldenBundle "map" map (map `unsafeApplyCode` l1) + [ + goldenBundle "map" map (map `unsafeApplyCode` l1) , goldenBundle "elem" elem (elem `unsafeApplyCode` l1) , goldenBundle "find" find (find `unsafeApplyCode` l1) , goldenBundle "any" any (any `unsafeApplyCode` l1) @@ -45,8 +46,8 @@ tests = , goldenBundle "notElem" notElem (notElem `unsafeApplyCode` l1) , goldenBundle "foldr" foldr (foldr `unsafeApplyCode` l1) , goldenBundle "foldl" foldl (foldl `unsafeApplyCode` l1) - , goldenBundle "concat" concat (concat `unsafeApplyCode` l1) - , goldenBundle "concatMap" concatMap (concatMap `unsafeApplyCode` l1) + -- , goldenBundle "concat" concat (concat `unsafeApplyCode` l1) + -- , goldenBundle "concatMap" concatMap (concatMap `unsafeApplyCode` l1) , goldenBundle "listToMaybeJust" listToMaybeJust (listToMaybeJust `unsafeApplyCode` l1) , goldenBundle "listToMaybeNothing" listToMaybeNothing (listToMaybeNothing `unsafeApplyCode` l1) @@ -58,9 +59,9 @@ tests = , goldenBundle "replicate" replicate (replicate `unsafeApplyCode` l1) , goldenBundle "findIndexJust" findIndexJust (findIndexJust `unsafeApplyCode` l1) , goldenBundle "findIndexNothing" findIndexNothing (findIndexNothing `unsafeApplyCode` l1) - , goldenBundle "unzip" unzip (unzip `unsafeApplyCode` l3) - , goldenBundle "zip" zip (zip `unsafeApplyCode` l1) - , goldenBundle "zipWith" zipWith (zipWith `unsafeApplyCode` l1) + -- , goldenBundle "unzip" unzip (unzip `unsafeApplyCode` l3) + -- , goldenBundle "zip" zip (zip `unsafeApplyCode` l1) + -- , goldenBundle "zipWith" zipWith (zipWith `unsafeApplyCode` l1) , goldenBundle "headOk" headOk (headOk `unsafeApplyCode` l1) , goldenBundle "headEmpty" headEmpty (headEmpty `unsafeApplyCode` l1) , goldenBundle "lastOk" lastOk (lastOk `unsafeApplyCode` l1) @@ -70,11 +71,11 @@ tests = , goldenBundle "take" take (take `unsafeApplyCode` l1) , goldenBundle "drop" drop (drop `unsafeApplyCode` l1) , goldenBundle "dropWhile" dropWhile (dropWhile `unsafeApplyCode` l1) - , goldenBundle "splitAt" splitAt (splitAt `unsafeApplyCode` l1) + -- , goldenBundle "splitAt" splitAt (splitAt `unsafeApplyCode` l1) , goldenBundle "elemBy" elemBy (elemBy `unsafeApplyCode` l1) - , goldenBundle "partition" partition (partition `unsafeApplyCode` l1) - , goldenBundle "sort" sort (sort `unsafeApplyCode` l1) - , goldenBundle "sortBy" sortBy (sortBy `unsafeApplyCode` l1) + -- , goldenBundle "partition" partition (partition `unsafeApplyCode` l1) + -- , goldenBundle "sort" sort (sort `unsafeApplyCode` l1) + -- , goldenBundle "sortBy" sortBy (sortBy `unsafeApplyCode` l1) , goldenBundle "nub" nub (nub `unsafeApplyCode` l1) , goldenBundle "nubBy" nubBy (nubBy `unsafeApplyCode` l1) ] @@ -158,10 +159,10 @@ foldl :: CompiledCode (L.BuiltinList Integer -> Integer) foldl = $$(compile [|| \xs -> L.foldl (P.*) 0 xs ||]) concat :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -concat = $$(compile [|| \xs -> L.concat (xs L.<| (L.singleton (L.singleton 1))) ||]) +concat = undefined -- $$(compile [|| \xs -> L.concat (xs L.<| L.singleton xs) ||]) concatMap :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -concatMap = undefined -- $$(compile [|| L.concatMap ||]) +concatMap = undefined -- $$(compile [|| \xs -> L.concatMap ( \x -> L.singleton (1 P.+ x) ) xs ||]) listToMaybeJust :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) listToMaybeJust = $$(compile [|| \xs -> L.listToMaybe xs ||]) @@ -197,7 +198,7 @@ zip :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList (P.BuiltinPair Integ zip = undefined -- $$(compile [|| \xs -> L.zip xs xs ||]) zipWith :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -zipWith = undefined -- $$(compile [|| L.zipWith ||]) +zipWith = $$(compile [|| \xs -> L.zipWith (P.+) xs xs ||]) headOk :: CompiledCode (L.BuiltinList Integer -> Integer) headOk = $$(compile [|| \xs -> L.head xs ||]) @@ -226,8 +227,10 @@ drop = $$(compile [|| \xs -> L.drop 5 xs ||]) dropWhile :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) dropWhile = $$(compile [|| \xs -> L.dropWhile (P.< 5) xs ||]) -splitAt :: CompiledCode (L.BuiltinList Integer -> - P.BuiltinPair (L.BuiltinList Integer) (L.BuiltinList Integer)) +splitAt + :: CompiledCode ( + L.BuiltinList Integer -> P.BuiltinPair (L.BuiltinList Integer) (L.BuiltinList Integer) + ) splitAt = undefined -- $$(compile [|| \xs -> L.splitAt 2 xs ||]) elemBy :: CompiledCode (L.BuiltinList Integer -> Bool) @@ -237,16 +240,16 @@ partition :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) partition = undefined -- $$(compile [|| L.partition ||]) sort :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -sort = undefined -- $$(compile [|| L.sort ||]) +sort = undefined -- $$(compile [|| \xs -> L.sort xs ||]) sortBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -sortBy = undefined -- $$(compile [|| L.sortBy ||]) +sortBy = undefined -- $$(compile [|| \xs -> L.sortBy (P.<=) xs ||]) nub :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -nub = undefined -- $$(compile [|| L.nub ||]) +nub = $$(compile [|| \xs -> L.nub xs ||]) nubBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -nubBy = undefined -- $$(compile [|| L.nubBy ||]) +nubBy = $$(compile [|| \xs -> L.nubBy (P.>=) xs ||]) l1 :: CompiledCode (L.BuiltinList Integer) l1 = liftCodeDef $ toBuiltin ([1 .. 10] :: [Integer]) diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index 93243ff9bc3..9ca0ad773a6 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -54,8 +54,6 @@ module PlutusTx.BuiltinList ( nubBy ) where -import Prelude (undefined) - import PlutusTx.Builtins qualified as B import PlutusTx.Builtins.HasOpaque import PlutusTx.Builtins.Internal qualified as BI @@ -382,7 +380,7 @@ nubBy eq = go empty go xs = caseList' empty ( \y ys -> if elemBy eq y xs - then go xs ys + then go ys xs else y <| go ys (y <| xs) ) {-# INLINABLE nubBy #-} @@ -437,11 +435,59 @@ partition p = BI.BuiltinPair . foldr select (empty, empty) {-# INLINABLE partition #-} -- | Plutus Tx version of 'Data.List.sort' for 'BuiltinList'. -sort :: Ord a => BuiltinList a -> BuiltinList a +sort :: (MkNil a, Ord a) => BuiltinList a -> BuiltinList a sort = sortBy compare {-# INLINABLE sort #-} -- | Plutus Tx version of 'Data.List.sortBy' for 'BuiltinList'. -sortBy :: (a -> a -> Ordering) -> BuiltinList a -> BuiltinList a -sortBy cmp l = undefined +sortBy :: MkNil a => (a -> a -> Ordering) -> BuiltinList a -> BuiltinList a +sortBy cmp = mergeAll . sequences + where + sequences = caseList'' empty (singleton . singleton) f + where + f a b xs + | a `cmp` b == GT = descending b (singleton a) xs + | otherwise = ascending b (cons a) xs + + descending a as l = caseList' d f l + where + d = (a <| as) <| sequences l + f b bs + | a `cmp` b == GT = descending b (a <| as) bs + | otherwise = d + + ascending a as l = caseList' d f l + where + d = as (singleton a) <| sequences l + f b bs + | a `cmp` b /= GT = ascending b (as . cons a) bs + | otherwise = d + + mergeAll l = + case uniqueElement l of + Nothing -> + mergeAll (mergePairs l) + Just x -> + x + + mergePairs = caseList'' empty singleton f + where + f a b xs = merge a b <| mergePairs xs + + merge as bs + | null as = bs + | null bs = as + | otherwise = do + let a = head as + let b = head bs + let as' = tail as + let bs' = tail bs + if a `cmp` b == GT then + b <| merge as bs' + else + a <| merge as' bs + + caseList'' :: forall a r. r -> (a -> r) -> (a -> a -> BuiltinList a -> r) -> BuiltinList a -> r + caseList'' f0 f1 f2 = caseList' f0 ( \x xs -> caseList' (f1 x) ( \y ys -> f2 x y ys ) xs ) + {-# INLINABLE sortBy #-} From bf89cd90814d7f9a2875543cdcb20bb2801bebff Mon Sep 17 00:00:00 2001 From: zeme Date: Tue, 20 May 2025 14:42:13 +0200 Subject: [PATCH 05/30] wip --- out.html | 563 ------------------------------------------------------- 1 file changed, 563 deletions(-) delete mode 100644 out.html diff --git a/out.html b/out.html deleted file mode 100644 index d40f8b832bc..00000000000 --- a/out.html +++ /dev/null @@ -1,563 +0,0 @@ - - -{-# INLINEABLE sortBy #-} -sortBy :: forall a. (a -> a -> Ordering) -> [a] -> [a] -sortBy a -> a -> Ordering -cmp = (a -> a -> Bool) -> [a] -> [a] -forall a. (a -> a -> Bool) -> [a] -> [a] -actualSort (\a -x a -y -> a -> a -> Ordering -cmp a -x a -y Ordering -> Ordering -> Bool -forall a. Eq a => a -> a -> Bool -== Ordering -GT) - -actualSort :: (a -> a -> Bool) -> [a] -> [a] -actualSort :: forall a. (a -> a -> Bool) -> [a] -> [a] -actualSort a -> a -> Bool -gt [a] -ns - | [] <- [a] -ns = [] - | [a -a] <- [a] -ns = [a -a] - | [a -a,a -b] <- [a] -ns = [a] -> [a] -> [a] -merge [a -a] [a -b] - | [a -a,a -b,a -c] <- [a] -ns = [a] -> [a] -> [a] -> [a] -merge3 [a -a] [a -b] [a -c] - | [a -a,a -b,a -c,a -d] <- [a] -ns = [a] -> [a] -> [a] -> [a] -> [a] -merge4 [a -a] [a -b] [a -c] [a -d] - | Bool -otherwise = [[a]] -> [a] -merge_all ([a] -> [[a]] -sequences [a] -ns) - where - sequences :: [a] -> [[a]] -sequences (a -a:a -b:[a] -xs) - | a -a a -> a -> Bool -`gt` a -b = a -> [a] -> [a] -> [[a]] -descending a -b [a -a] [a] -xs - | Bool -otherwise = a -> ([a] -> [a]) -> [a] -> [[a]] -ascending a -b (a -aa -> [a] -> [a] -forall a. a -> [a] -> [a] -:) [a] -xs - sequences [a] -xs = [[a] -xs] - - descending :: a -> [a] -> [a] -> [[a]] -descending a -a [a] -as (a -b:[a] -bs) - | a -a a -> a -> Bool -`gt` a -b = a -> [a] -> [a] -> [[a]] -descending a -b (a -aa -> [a] -> [a] -forall a. a -> [a] -> [a] -:[a] -as) [a] -bs - descending a -a [a] -as [a] -bs = (a -aa -> [a] -> [a] -forall a. a -> [a] -> [a] -:[a] -as)[a] -> [[a]] -> [[a]] -forall a. a -> [a] -> [a] -: [a] -> [[a]] -sequences [a] -bs - - ascending :: a -> ([a] -> [a]) -> [a] -> [[a]] -ascending a -a [a] -> [a] -as (a -b:[a] -bs) - | Bool -> Bool -not (a -a a -> a -> Bool -`gt` a -b) = a -> ([a] -> [a]) -> [a] -> [[a]] -ascending a -b (\[a] -ys -> [a] -> [a] -as (a -aa -> [a] -> [a] -forall a. a -> [a] -> [a] -:[a] -ys)) [a] -bs - ascending a -a [a] -> [a] -as [a] -bs = let !x :: [a] -x = [a] -> [a] -as [a -a] - in [a] -x [a] -> [[a]] -> [[a]] -forall a. a -> [a] -> [a] -: [a] -> [[a]] -sequences [a] -bs - - merge_all :: [[a]] -> [a] -merge_all [[a] -x] = [a] -x - merge_all [[a]] -xs = [[a]] -> [a] -merge_all ([[a]] -> [[a]] -reduce_once [[a]] -xs) - - reduce_once :: [[a]] -> [[a]] -reduce_once [] = [] - reduce_once [[a] -a] = [[a] -a] - reduce_once [[a] -a,[a] -b] = [[a] -> [a] -> [a] -merge [a] -a [a] -b] - reduce_once [[a] -a,[a] -b,[a] -c] = [[a] -> [a] -> [a] -> [a] -merge3 [a] -a [a] -b [a] -c] - reduce_once [[a] -a,[a] -b,[a] -c,[a] -d,[a] -e] = [[a] -> [a] -> [a] -merge [a] -a [a] -b, [a] -> [a] -> [a] -> [a] -merge3 [a] -c [a] -d [a] -e] - reduce_once [[a] -a,[a] -b,[a] -c,[a] -d,[a] -e,[a] -f] = [[a] -> [a] -> [a] -> [a] -merge3 [a] -a [a] -b [a] -c, [a] -> [a] -> [a] -> [a] -merge3 [a] -d [a] -e [a] -f] - reduce_once ([a] -a:[a] -b:[a] -c:[a] -d:[[a]] -xs) = let !x :: [a] -x = [a] -> [a] -> [a] -> [a] -> [a] -merge4 [a] -a [a] -b [a] -c [a] -d - in [a] -x [a] -> [[a]] -> [[a]] -forall a. a -> [a] -> [a] -: [[a]] -> [[a]] -reduce_once [[a]] -xs - - merge :: [a] -> [a] -> [a] -merge as :: [a] -as@(a -a:[a] -as') bs :: [a] -bs@(a -b:[a] -bs') - | a -a a -> a -> Bool -`gt` a -b = a -b a -> [a] -> [a] -forall a. a -> [a] -> [a] -: [a] -> [a] -> [a] -merge [a] -as [a] -bs' - | Bool -otherwise = a -a a -> [a] -> [a] -forall a. a -> [a] -> [a] -: [a] -> [a] -> [a] -merge [a] -as' [a] -bs - merge [] [a] -bs = [a] -bs - merge [a] -as [] = [a] -as - - -- `merge3` is a manually fused version of `merge (merge as bs) cs` - merge3 :: [a] -> [a] -> [a] -> [a] -merge3 as :: [a] -as@(a -a:[a] -as') bs :: [a] -bs@(a -b:[a] -bs') [a] -cs - | a -a a -> a -> Bool -`gt` a -b = a -> [a] -> [a] -> [a] -> [a] -merge3X a -b [a] -as [a] -bs' [a] -cs - | Bool -otherwise = a -> [a] -> [a] -> [a] -> [a] -merge3X a -a [a] -as' [a] -bs [a] -cs - merge3 [] [a] -bs [a] -cs = [a] -> [a] -> [a] -merge [a] -bs [a] -cs - merge3 [a] -as [] [a] -cs = [a] -> [a] -> [a] -merge [a] -as [a] -cs - - merge3X :: a -> [a] -> [a] -> [a] -> [a] -merge3X a -x [a] -as [a] -bs cs :: [a] -cs@(a -c:[a] -cs') - | a -x a -> a -> Bool -`gt` a -c = a -c a -> [a] -> [a] -forall a. a -> [a] -> [a] -: a -> [a] -> [a] -> [a] -> [a] -merge3X a -x [a] -as [a] -bs [a] -cs' - | Bool -otherwise = a -x a -> [a] -> [a] -forall a. a -> [a] -> [a] -: [a] -> [a] -> [a] -> [a] -merge3 [a] -as [a] -bs [a] -cs - merge3X a -x [a] -as [a] -bs [] = a -x a -> [a] -> [a] -forall a. a -> [a] -> [a] -: [a] -> [a] -> [a] -merge [a] -as [a] -bs - - merge3Y :: [a] -> a -> [a] -> [a] -> [a] -merge3Y as :: [a] -as@(a -a:[a] -as') a -y [a] -bs [a] -cs - | a -a a -> a -> Bool -`gt` a -y = a -y a -> [a] -> [a] -forall a. a -> [a] -> [a] -: [a] -> [a] -> [a] -> [a] -merge3 [a] -as [a] -bs [a] -cs - | Bool -otherwise = a -a a -> [a] -> [a] -forall a. a -> [a] -> [a] -: [a] -> a -> [a] -> [a] -> [a] -merge3Y [a] -as' a -y [a] -bs [a] -cs - merge3Y [] a -x [a] -bs [a] -cs = a -x a -> [a] -> [a] -forall a. a -> [a] -> [a] -: [a] -> [a] -> [a] -merge [a] -bs [a] -cs - - -- `merge4 as bs cs ds` is (essentially) a manually fused version of - -- `merge (merge as bs) (merge cs ds)` - merge4 :: [a] -> [a] -> [a] -> [a] -> [a] -merge4 as :: [a] -as@(a -a:[a] -as') bs :: [a] -bs@(a -b:[a] -bs') [a] -cs [a] -ds - | a -a a -> a -> Bool -`gt` a -b = a -> [a] -> [a] -> [a] -> [a] -> [a] -merge4X a -b [a] -as [a] -bs' [a] -cs [a] -ds - | Bool -otherwise = a -> [a] -> [a] -> [a] -> [a] -> [a] -merge4X a -a [a] -as' [a] -bs [a] -cs [a] -ds - merge4 [] [a] -bs [a] -cs [a] -ds = [a] -> [a] -> [a] -> [a] -merge3 [a] -bs [a] -cs [a] -ds - merge4 [a] -as [] [a] -cs [a] -ds = [a] -> [a] -> [a] -> [a] -merge3 [a] -as [a] -cs [a] -ds - - merge4X :: a -> [a] -> [a] -> [a] -> [a] -> [a] -merge4X a -x [a] -as [a] -bs cs :: [a] -cs@(a -c:[a] -cs') ds :: [a] -ds@(a -d:[a] -ds') - | a -c a -> a -> Bool -`gt` a -d = a -> [a] -> [a] -> a -> [a] -> [a] -> [a] -merge4XY a -x [a] -as [a] -bs a -d [a] -cs [a] -ds' - | Bool -otherwise = a -> [a] -> [a] -> a -> [a] -> [a] -> [a] -merge4XY a -x [a] -as [a] -bs a -c [a] -cs' [a] -ds - merge4X a -x [a] -as [a] -bs [] [a] -ds = a -> [a] -> [a] -> [a] -> [a] -merge3X a -x [a] -as [a] -bs [a] -ds - merge4X a -x [a] -as [a] -bs [a] -cs [] = a -> [a] -> [a] -> [a] -> [a] -merge3X a -x [a] -as [a] -bs [a] -cs - - merge4Y :: [a] -> [a] -> a -> [a] -> [a] -> [a] -merge4Y as :: [a] -as@(a -a:[a] -as') bs :: [a] -bs@(a -b:[a] -bs') a -y [a] -cs [a] -ds - | a -a a -> a -> Bool -`gt` a -b = a -> [a] -> [a] -> a -> [a] -> [a] -> [a] -merge4XY a -b [a] -as [a] -bs' a -y [a] -cs [a] -ds - | Bool -otherwise = a -> [a] -> [a] -> a -> [a] -> [a] -> [a] -merge4XY a -a [a] -as' [a] -bs a -y [a] -cs [a] -ds - merge4Y [a] -as [] a -y [a] -cs [a] -ds = [a] -> a -> [a] -> [a] -> [a] -merge3Y [a] -as a -y [a] -cs [a] -ds - merge4Y [] [a] -bs a -y [a] -cs [a] -ds = [a] -> a -> [a] -> [a] -> [a] -merge3Y [a] -bs a -y [a] -cs [a] -ds - - merge4XY :: a -> [a] -> [a] -> a -> [a] -> [a] -> [a] -merge4XY a -x [a] -as [a] -bs a -y [a] -cs [a] -ds - | a -x a -> a -> Bool -`gt` a -y = a -y a -> [a] -> [a] -forall a. a -> [a] -> [a] -: a -> [a] -> [a] -> [a] -> [a] -> [a] -merge4X a -x [a] -as [a] -bs [a] -cs [a] -ds - | Bool -otherwise = a -x a -> [a] -> [a] -forall a. a -> [a] -> [a] -: [a] -> [a] -> a -> [a] -> [a] -> [a] -merge4Y [a] -as [a] -bs a -y [a] -cs [a] -ds - - \ No newline at end of file From 7cc06cba0fac50fdbf1b565c5177d06dd7711a68 Mon Sep 17 00:00:00 2001 From: zeme Date: Wed, 21 May 2025 12:03:14 +0200 Subject: [PATCH 06/30] wip --- .../BuiltinList/Budget/9.6/(++).budget.golden | 3 -- .../BuiltinList/Budget/9.6/(++).eval.golden | 4 ++ .../BuiltinList/Budget/9.6/(<|).budget.golden | 3 -- .../BuiltinList/Budget/9.6/(<|).eval.golden | 4 ++ .../BuiltinList/Budget/9.6/and.budget.golden | 3 -- .../BuiltinList/Budget/9.6/and.eval.golden | 4 ++ .../Budget/9.6/append.budget.golden | 3 -- .../BuiltinList/Budget/9.6/append.eval.golden | 4 ++ .../Budget/9.6/concat.budget.golden | 3 -- .../BuiltinList/Budget/9.6/concat.eval.golden | 1 - .../BuiltinList/Budget/9.6/concat.pir.golden | 51 ------------------- .../BuiltinList/Budget/9.6/concat.uplc.golden | 22 -------- .../BuiltinList/Budget/9.6/cons.budget.golden | 3 -- .../BuiltinList/Budget/9.6/cons.eval.golden | 4 ++ .../BuiltinList/Budget/9.6/drop.budget.golden | 3 -- .../BuiltinList/Budget/9.6/drop.eval.golden | 6 ++- .../BuiltinList/Budget/9.6/drop.pir.golden | 2 +- .../BuiltinList/Budget/9.6/drop.uplc.golden | 2 +- .../Budget/9.6/dropWhile.budget.golden | 3 -- .../Budget/9.6/dropWhile.eval.golden | 4 ++ .../Budget/9.6/elemBy.budget.golden | 3 -- .../BuiltinList/Budget/9.6/elemBy.eval.golden | 4 ++ .../Budget/9.6/empty.budget.golden | 3 -- .../BuiltinList/Budget/9.6/empty.eval.golden | 4 ++ .../Budget/9.6/filter.budget.golden | 3 -- .../BuiltinList/Budget/9.6/filter.eval.golden | 4 ++ .../Budget/9.6/findIndexJust.budget.golden | 3 -- .../Budget/9.6/findIndexJust.eval.golden | 4 ++ .../Budget/9.6/findIndexNothing.budget.golden | 3 -- .../Budget/9.6/findIndexNothing.eval.golden | 4 ++ .../Budget/9.6/findIndices.budget.golden | 3 -- .../Budget/9.6/findIndices.eval.golden | 4 ++ .../Budget/9.6/foldl.budget.golden | 3 -- .../BuiltinList/Budget/9.6/foldl.eval.golden | 4 ++ .../Budget/9.6/foldr.budget.golden | 3 -- .../BuiltinList/Budget/9.6/foldr.eval.golden | 4 ++ .../Budget/9.6/headEmpty.budget.golden | 5 -- .../Budget/9.6/headOk.budget.golden | 3 -- .../BuiltinList/Budget/9.6/headOk.eval.golden | 4 ++ .../Budget/9.6/indexNegative.budget.golden | 5 -- .../Budget/9.6/indexTooLarge.budget.golden | 5 -- .../Budget/9.6/lastEmpty.budget.golden | 5 -- .../Budget/9.6/lastOk.budget.golden | 5 -- .../Budget/9.6/length.budget.golden | 3 -- .../BuiltinList/Budget/9.6/length.eval.golden | 4 ++ .../Budget/9.6/listToMaybeJust.budget.golden | 3 -- .../Budget/9.6/listToMaybeJust.eval.golden | 4 ++ .../9.6/listToMaybeNothing.budget.golden | 3 -- .../Budget/9.6/listToMaybeNothing.eval.golden | 4 ++ .../Budget/9.6/mapMaybe.budget.golden | 3 -- .../Budget/9.6/mapMaybe.eval.golden | 4 ++ .../Budget/9.6/notElem.budget.golden | 3 -- .../Budget/9.6/notElem.eval.golden | 4 ++ .../Budget/9.6/nubBy.budget.golden | 3 -- .../BuiltinList/Budget/9.6/nubBy.eval.golden | 1 - .../BuiltinList/Budget/9.6/null.budget.golden | 3 -- .../BuiltinList/Budget/9.6/null.eval.golden | 4 ++ .../BuiltinList/Budget/9.6/or.budget.golden | 3 -- .../BuiltinList/Budget/9.6/or.eval.golden | 4 ++ .../Budget/9.6/replicate.budget.golden | 3 -- .../Budget/9.6/replicate.eval.golden | 4 ++ .../Budget/9.6/revAppend.budget.golden | 3 -- .../Budget/9.6/revAppend.eval.golden | 4 ++ .../Budget/9.6/reverse.budget.golden | 3 -- .../Budget/9.6/reverse.eval.golden | 4 ++ .../Budget/9.6/singleton.budget.golden | 3 -- .../Budget/9.6/singleton.eval.golden | 4 ++ .../Budget/9.6/tailEmpty.budget.golden | 5 -- .../Budget/9.6/tailOk.budget.golden | 3 -- .../BuiltinList/Budget/9.6/tailOk.eval.golden | 4 ++ .../BuiltinList/Budget/9.6/take.budget.golden | 3 -- .../BuiltinList/Budget/9.6/take.eval.golden | 4 ++ .../Budget/9.6/unconsJust.budget.golden | 3 -- .../Budget/9.6/unconsJust.eval.golden | 4 ++ .../Budget/9.6/unconsNothing.budget.golden | 3 -- .../Budget/9.6/unconsNothing.eval.golden | 4 ++ .../9.6/uniqueElementJust.budget.golden | 3 -- .../Budget/9.6/uniqueElementJust.eval.golden | 4 ++ .../9.6/uniqueElementNothing.budget.golden | 3 -- .../9.6/uniqueElementNothing.eval.golden | 4 ++ plutus-tx/src/PlutusTx/BuiltinList.hs | 2 +- 81 files changed, 136 insertions(+), 214 deletions(-) delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.budget.golden delete mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.budget.golden diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).budget.golden deleted file mode 100644 index 3f0532d9475..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 9002784 -mem: 33712 -size: 42 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden index 3ee1061d2d0..9d0530c2037 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden @@ -1 +1,5 @@ +cpu: 9002784 +mem: 33712 +size: 42 + (con (list integer) [1,2,3,4,5,6,7,8,9,10,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).budget.golden deleted file mode 100644 index 42417de0de0..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 216462 -mem: 1032 -size: 9 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden index 6c5264d56a4..ba51fd9d80e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden @@ -1 +1,5 @@ +cpu: 216462 +mem: 1032 +size: 9 + (con (list integer) [42,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.budget.golden deleted file mode 100644 index aebcc3f4057..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 2091812 -mem: 8694 -size: 53 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden index f217693e82c..752d9c11fea 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden @@ -1 +1,5 @@ +cpu: 2091812 +mem: 8694 +size: 53 + (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.budget.golden deleted file mode 100644 index 3f0532d9475..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 9002784 -mem: 33712 -size: 42 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden index 3ee1061d2d0..9d0530c2037 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden @@ -1 +1,5 @@ +cpu: 9002784 +mem: 33712 +size: 42 + (con (list integer) [1,2,3,4,5,6,7,8,9,10,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.budget.golden deleted file mode 100644 index 8ed36ea0f3c..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 23678800 -mem: 97612 -size: 85 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden deleted file mode 100644 index 3ee1061d2d0..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden +++ /dev/null @@ -1 +0,0 @@ -(con (list integer) [1,2,3,4,5,6,7,8,9,10,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden deleted file mode 100644 index 653e769a48a..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden +++ /dev/null @@ -1,51 +0,0 @@ -let - !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r - = /\a r -> - \(z : r) (f : a -> list a -> r) (xs : list a) -> - chooseList - {a} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {a} xs) (tailList {a} xs)) - {r} -in -\(xs : list integer) -> - (letrec - !go : list (list integer) -> list integer - = caseList' - {list integer} - {list integer} - [] - (\(x : list integer) (xs : list (list integer)) -> - let - !r : list integer = go xs - in - (let - b = list integer - in - \(f : integer -> b -> b) (acc : b) -> - letrec - !go : list integer -> b - = caseList' - {integer} - {b} - acc - (\(x : integer) (xs : list integer) -> f x (go xs)) - in - go) - (mkCons {integer}) - r - x) - in - go) - (mkCons - {list integer} - xs - ((let - a = list integer - in - \(`$dMkNil` : (\arep -> list arep) a) (x : a) -> - mkCons {a} x `$dMkNil`) - [] - xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden deleted file mode 100644 index 3d0cdb2f9ed..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden +++ /dev/null @@ -1,22 +0,0 @@ -(program - 1.1.0 - (\xs -> - (\caseList' -> - (\s -> s s) - (\s -> - caseList' - [] - (\x xs -> - (\acc -> - (\s -> s s) - (\s -> - caseList' acc (\x xs -> force mkCons x (s s xs)))) - (s s xs) - x))) - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay (f (force headList xs) (force tailList xs))))) - (force mkCons xs (force mkCons xs [])))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.budget.golden deleted file mode 100644 index 42417de0de0..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 216462 -mem: 1032 -size: 9 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden index d2d86960ed6..4eec5a3badc 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden @@ -1 +1,5 @@ +cpu: 216462 +mem: 1032 +size: 9 + (con (list integer) [0,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.budget.golden deleted file mode 100644 index a2606188654..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 7834491 -mem: 32602 -size: 83 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden index e58cc9c2703..084b26d837c 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden @@ -1 +1,5 @@ -(con (list integer) []) \ No newline at end of file +cpu: 7834491 +mem: 32602 +size: 83 + +(con (list integer) [6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.pir.golden index 98ab693cfa1..c0bbd86e804 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.pir.golden @@ -10,7 +10,7 @@ letrec Bool_match (ifThenElse {Bool} (lessThanEqualsInteger n 0) True False) {all dead. list a} - (/\dead -> `$dMkNil`) + (/\dead -> l) (/\dead -> (let r = list a diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden index c6573279a83..5e05913f523 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden @@ -8,7 +8,7 @@ force (force ifThenElse (lessThanEqualsInteger n 0) - (delay `$dMkNil`) + (delay l) (delay (force (force (force chooseList) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.budget.golden deleted file mode 100644 index a0115dcd3f7..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 5295830 -mem: 20590 -size: 54 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden index 3a6e10d8766..208e37b12cc 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden @@ -1 +1,5 @@ +cpu: 5295830 +mem: 20590 +size: 54 + (con (list integer) [5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.budget.golden deleted file mode 100644 index 92d8c889f4c..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 11286024 -mem: 44712 -size: 57 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden index f217693e82c..f90d707746f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden @@ -1 +1,5 @@ +cpu: 11286024 +mem: 44712 +size: 57 + (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.budget.golden deleted file mode 100644 index 5acec6cac96..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 64100 -mem: 500 -size: 4 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden index e58cc9c2703..906f70b6c08 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden @@ -1 +1,5 @@ +cpu: 64100 +mem: 500 +size: 4 + (con (list integer) []) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.budget.golden deleted file mode 100644 index d7ef144c6ce..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 14524094 -mem: 54082 -size: 66 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden index 41828d6c7f7..e0deb5d9e5a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden @@ -1 +1,5 @@ +cpu: 14524094 +mem: 54082 +size: 66 + (con (list integer) [2,4,6,8,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.budget.golden deleted file mode 100644 index 085d5b78308..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 5144480 -mem: 20098 -size: 67 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden index 13675c87619..369f791ff5a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden @@ -1 +1,5 @@ +cpu: 5144480 +mem: 20098 +size: 67 + (constr 0 (con integer 3)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.budget.golden deleted file mode 100644 index 43166bb930d..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 13551064 -mem: 52032 -size: 67 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden index f217693e82c..11f4c84d736 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden @@ -1 +1,5 @@ +cpu: 13551064 +mem: 52032 +size: 67 + (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.budget.golden deleted file mode 100644 index 4501200a757..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 17232174 -mem: 64702 -size: 81 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden index 2f184a3b84b..59d0960ad98 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden @@ -1 +1,5 @@ +cpu: 17232174 +mem: 64702 +size: 81 + (con (list integer) [0,2,4,6,8]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.budget.golden deleted file mode 100644 index f9bf03bd822..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 10564694 -mem: 42012 -size: 55 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden index b23026d4762..f0184f44abc 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden @@ -1 +1,5 @@ +cpu: 10564694 +mem: 42012 +size: 55 + (con integer 0) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.budget.golden deleted file mode 100644 index 5bc45bc907f..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 9179244 -mem: 32712 -size: 44 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden index 0dc9ac9d664..c4e8898d563 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden @@ -1 +1,5 @@ +cpu: 9179244 +mem: 32712 +size: 44 + (con integer 55) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.budget.golden deleted file mode 100644 index 4e7df0819aa..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.budget.golden +++ /dev/null @@ -1,5 +0,0 @@ -An error has occurred: -The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. -Final budget: ({cpu: 192592 -| mem: 164}) -Logs: PT23 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.budget.golden deleted file mode 100644 index 558d423b840..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 761907 -mem: 3096 -size: 39 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden index 132831f390c..80fd21ad390 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden @@ -1 +1,5 @@ +cpu: 761907 +mem: 3096 +size: 39 + (con integer 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.budget.golden deleted file mode 100644 index 6fd7da844c9..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.budget.golden +++ /dev/null @@ -1,5 +0,0 @@ -An error has occurred: -The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. -Final budget: ({cpu: 59598 -| mem: 132}) -Logs: PT21 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.budget.golden deleted file mode 100644 index 04ff5940af6..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.budget.golden +++ /dev/null @@ -1,5 +0,0 @@ -An error has occurred: -The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. -Final budget: ({cpu: 11866562 -| mem: 41164}) -Logs: PT22 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.budget.golden deleted file mode 100644 index 18bc78eee2a..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.budget.golden +++ /dev/null @@ -1,5 +0,0 @@ -An error has occurred: -The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. -Final budget: ({cpu: 192592 -| mem: 164}) -Logs: PT25 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.budget.golden deleted file mode 100644 index eeb1a0d0604..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.budget.golden +++ /dev/null @@ -1,5 +0,0 @@ -An error has occurred: -The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. -Final budget: ({cpu: 9570662 -| mem: 41124}) -Logs: PT25 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.budget.golden deleted file mode 100644 index e4bd625c510..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 9659244 -mem: 35712 -size: 47 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden index 3df7275df82..0ff2611645b 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden @@ -1 +1,5 @@ +cpu: 9659244 +mem: 35712 +size: 47 + (con integer 10) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.budget.golden deleted file mode 100644 index 8c448704111..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 681907 -mem: 2596 -size: 25 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden index 005b0a452f3..c51ab8f5ceb 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden @@ -1 +1,5 @@ +cpu: 681907 +mem: 2596 +size: 25 + (constr 0 (con integer 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.budget.golden deleted file mode 100644 index cf66fde6a2c..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 357094 -mem: 1532 -size: 25 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden index f217693e82c..6eec30a642f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden @@ -1 +1,5 @@ +cpu: 357094 +mem: 1532 +size: 25 + (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.budget.golden deleted file mode 100644 index 807ec259d6e..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 14844094 -mem: 56082 -size: 75 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden index 658d1c3fa5c..9a10cb7525d 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden @@ -1 +1,5 @@ +cpu: 14844094 +mem: 56082 +size: 75 + (con (list integer) [1,3,5,7,9]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.budget.golden deleted file mode 100644 index eb294710d33..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 11434984 -mem: 45112 -size: 63 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden index 1dd2b8ed5d3..6e7ed93cb18 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden @@ -1 +1,5 @@ +cpu: 11434984 +mem: 45112 +size: 63 + (constr 0) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.budget.golden deleted file mode 100644 index 6f831e88dc3..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 4705572 -mem: 21018 -size: 111 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden deleted file mode 100644 index d7ab80beb57..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden +++ /dev/null @@ -1 +0,0 @@ -(con (list integer) [1]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.budget.golden deleted file mode 100644 index 44cc03385cb..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 374582 -mem: 1533 -size: 14 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden index f217693e82c..01e48473efb 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden @@ -1 +1,5 @@ +cpu: 374582 +mem: 1533 +size: 14 + (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.budget.golden deleted file mode 100644 index 69d06c3c39b..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 1125956 -mem: 4897 -size: 53 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden index 1dd2b8ed5d3..dac90627f55 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden @@ -1 +1,5 @@ +cpu: 1125956 +mem: 4897 +size: 53 + (constr 0) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.budget.golden deleted file mode 100644 index 75722453e18..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 8478546 -mem: 34362 -size: 46 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden index 7c7c2a59e12..b95204f057d 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden @@ -1 +1,5 @@ +cpu: 8478546 +mem: 34362 +size: 46 + (con (list integer) [0,0,0,0,0,0,0,0,0,0]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.budget.golden deleted file mode 100644 index 443cf79e380..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 10938784 -mem: 45812 -size: 65 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden index be17fceb5b5..c7c5e70c6f5 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden @@ -1 +1,5 @@ +cpu: 10938784 +mem: 45812 +size: 65 + (con (list integer) [10,9,8,7,6,5,4,3,2,1,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.budget.golden deleted file mode 100644 index 443cf79e380..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 10938784 -mem: 45812 -size: 65 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden index e2799de9624..4a0b1fee052 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden @@ -1 +1,5 @@ +cpu: 10938784 +mem: 45812 +size: 65 + (con (list integer) [10,9,8,7,6,5,4,3,2,1]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.budget.golden deleted file mode 100644 index 5acec6cac96..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 64100 -mem: 500 -size: 4 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden index d7ab80beb57..2c86e256dd2 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden @@ -1 +1,5 @@ +cpu: 64100 +mem: 500 +size: 4 + (con (list integer) [1]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.budget.golden deleted file mode 100644 index 18bc78eee2a..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.budget.golden +++ /dev/null @@ -1,5 +0,0 @@ -An error has occurred: -The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. -Final budget: ({cpu: 192592 -| mem: 164}) -Logs: PT25 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.budget.golden deleted file mode 100644 index 558d423b840..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 761907 -mem: 3096 -size: 39 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden index af0310fec0b..86aa7f56508 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden @@ -1 +1,5 @@ +cpu: 761907 +mem: 3096 +size: 39 + (con (list integer) [2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.budget.golden deleted file mode 100644 index 6842d2d00dd..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 8356301 -mem: 33762 -size: 85 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden index 5a97069a30a..0b6fb76a1c7 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden @@ -1 +1,5 @@ +cpu: 8356301 +mem: 33762 +size: 85 + (con (list integer) [1,2,3,4,5]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.budget.golden deleted file mode 100644 index f397d477904..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 665907 -mem: 2496 -size: 24 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden index ceae63c9d5a..710ffb00b0f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden @@ -1 +1,5 @@ +cpu: 665907 +mem: 2496 +size: 24 + (constr 0 (constr 0 (con integer 1) (con (list integer) [2,3,4,5,6,7,8,9,10]))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.budget.golden deleted file mode 100644 index 8bcd39377af..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 357094 -mem: 1532 -size: 24 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden index f217693e82c..6597dd039a7 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden @@ -1 +1,5 @@ +cpu: 357094 +mem: 1532 +size: 24 + (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.budget.golden deleted file mode 100644 index d57cd589ec3..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 1667714 -mem: 6992 -size: 45 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden index f217693e82c..2fd26f9041f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden @@ -1 +1,5 @@ +cpu: 1667714 +mem: 6992 +size: 45 + (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.budget.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.budget.golden deleted file mode 100644 index 61d87258cfd..00000000000 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.budget.golden +++ /dev/null @@ -1,3 +0,0 @@ -cpu: 549094 -mem: 2732 -size: 45 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden index f217693e82c..01ce14fd5fd 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden @@ -1 +1,5 @@ +cpu: 549094 +mem: 2732 +size: 45 + (constr 1) \ No newline at end of file diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index 9ca0ad773a6..9c087c5525d 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -338,7 +338,7 @@ take n l -- | Plutus Tx version of 'Data.List.drop' for 'BuiltinList'. drop :: forall a. (MkNil a) => Integer -> BuiltinList a -> BuiltinList a drop n l - | n `B.lessThanEqualsInteger` 0 = empty + | n `B.lessThanEqualsInteger` 0 = l | otherwise = caseList' empty ( \_ xs -> drop (B.subtractInteger n 1) xs ) l From eb452fd4c533cbfcd1e72f5a706002c6c2128b27 Mon Sep 17 00:00:00 2001 From: zeme Date: Wed, 21 May 2025 12:27:30 +0200 Subject: [PATCH 07/30] wip --- .../Budget/9.6/uniqueElementJust.eval.golden | 8 ++-- .../Budget/9.6/uniqueElementJust.pir.golden | 31 +++++++++++-- .../Budget/9.6/uniqueElementJust.uplc.golden | 44 ++++++++++++++----- .../test/BuiltinList/Budget/Spec.hs | 24 +++++----- 4 files changed, 75 insertions(+), 32 deletions(-) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden index 2fd26f9041f..2c99798921c 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden @@ -1,5 +1,5 @@ -cpu: 1667714 -mem: 6992 -size: 45 +cpu: 3718050 +mem: 16462 +size: 114 -(constr 1) \ No newline at end of file +(constr 0 (con integer 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.pir.golden index fa07c55ff0f..8c9c2507c56 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.pir.golden @@ -1,7 +1,7 @@ let - data (Maybe :: * -> *) a | Maybe_match where - Just : a -> Maybe a - Nothing : Maybe a + data Bool | Bool_match where + True : Bool + False : Bool !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r = /\a r -> \(z : r) (f : a -> list a -> r) (xs : list a) -> @@ -13,6 +13,29 @@ let (/\dead -> f (headList {a} xs) (tailList {a} xs)) {r} in +letrec + !take : all a. (\arep -> list arep) a -> integer -> list a -> list a + = /\a -> + \(`$dMkNil` : (\arep -> list arep) a) (n : integer) (l : list a) -> + Bool_match + (ifThenElse {Bool} (lessThanEqualsInteger n 0) True False) + {all dead. list a} + (/\dead -> `$dMkNil`) + (/\dead -> + caseList' + {a} + {list a} + `$dMkNil` + (\(x : a) (xs : list a) -> + mkCons {a} x (take {a} `$dMkNil` (subtractInteger n 1) xs)) + l) + {all dead. dead} +in +let + data (Maybe :: * -> *) a | Maybe_match where + Just : a -> Maybe a + Nothing : Maybe a +in \(xs : list integer) -> caseList' {integer} @@ -24,4 +47,4 @@ in {Maybe integer} (Just {integer} x) (\(ds : integer) (ds : list integer) -> Nothing {integer})) - xs \ No newline at end of file + (take {integer} [] 1 xs) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden index 3d6b3af2588..cd265454aa9 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden @@ -1,14 +1,34 @@ (program 1.1.0 - (\xs -> - (\caseList' -> - caseList' - (constr 1 []) - (\x -> caseList' (constr 0 [x]) (\ds ds -> constr 1 []))) - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay (f (force headList xs) (force tailList xs))))) - xs)) \ No newline at end of file + ((\caseList' -> + (\take xs -> + caseList' + (constr 1 []) + (\x -> caseList' (constr 0 [x]) (\ds ds -> constr 1 [])) + (force take [] 1 xs)) + ((\s -> s s) + (\s arg -> + delay + (\`$dMkNil` n l -> + force + (force ifThenElse + (lessThanEqualsInteger n 0) + (delay `$dMkNil`) + (delay + (caseList' + `$dMkNil` + (\x xs -> + force mkCons + x + (force (s s (delay (\x -> x))) + `$dMkNil` + (subtractInteger n 1) + xs)) + l))))) + (delay (\x -> x)))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index 57a2096b34f..287b662ee27 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -76,8 +76,8 @@ tests = -- , goldenBundle "partition" partition (partition `unsafeApplyCode` l1) -- , goldenBundle "sort" sort (sort `unsafeApplyCode` l1) -- , goldenBundle "sortBy" sortBy (sortBy `unsafeApplyCode` l1) - , goldenBundle "nub" nub (nub `unsafeApplyCode` l1) - , goldenBundle "nubBy" nubBy (nubBy `unsafeApplyCode` l1) + -- , goldenBundle "nub" nub (nub `unsafeApplyCode` l1) + -- , goldenBundle "nubBy" nubBy (nubBy `unsafeApplyCode` l1) ] map :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) @@ -90,13 +90,13 @@ find :: CompiledCode (L.BuiltinList Integer -> (Maybe Integer, Maybe Integer)) find = $$(compile [||\xs -> (L.find (P.>= 8) xs, L.find (P.>= 12) xs)||]) any :: CompiledCode (L.BuiltinList Integer -> (Bool, Bool)) -any = $$(compile [||\xs -> (L.any (P.>= 8) xs, L.any (P.>= 12) xs)||]) +any = $$(compile [|| \xs -> (L.any (P.>= 8) xs, L.any (P.>= 12) xs) ||]) all :: CompiledCode (L.BuiltinList Integer -> (Bool, Bool)) -all = $$(compile [||\xs -> (L.all (P.>= 8) xs, L.all (P.>= 0) xs)||]) +all = $$(compile [|| \xs -> (L.all (P.>= 8) xs, L.all (P.>= 0) xs) ||]) index :: CompiledCode (L.BuiltinList Integer -> Integer) -index = $$(compile [||\xs -> xs L.!! 5 ||]) +index = $$(compile [|| \xs -> xs L.!! 5 ||]) indexNegative :: CompiledCode (L.BuiltinList Integer -> Integer) indexNegative = $$(compile [||\xs -> xs L.!! (-1) ||]) @@ -171,7 +171,7 @@ listToMaybeNothing :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) listToMaybeNothing = $$(compile [|| \_ -> L.listToMaybe L.empty ||]) uniqueElementJust :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) -uniqueElementJust = $$(compile [|| \xs -> L.uniqueElement xs ||]) +uniqueElementJust = $$(compile [|| \xs -> L.uniqueElement (L.take 1 xs) ||]) uniqueElementNothing :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) uniqueElementNothing = $$(compile [|| \_ -> L.uniqueElement L.empty ||]) @@ -245,11 +245,11 @@ sort = undefined -- $$(compile [|| \xs -> L.sort xs ||]) sortBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) sortBy = undefined -- $$(compile [|| \xs -> L.sortBy (P.<=) xs ||]) -nub :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -nub = $$(compile [|| \xs -> L.nub xs ||]) +-- nub :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +-- nub = $$(compile [|| \xs -> L.nub xs ||]) -nubBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -nubBy = $$(compile [|| \xs -> L.nubBy (P.>=) xs ||]) +-- nubBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +-- nubBy = $$(compile [|| \xs -> L.nubBy (P.>=) xs ||]) l1 :: CompiledCode (L.BuiltinList Integer) l1 = liftCodeDef $ toBuiltin ([1 .. 10] :: [Integer]) @@ -257,5 +257,5 @@ l1 = liftCodeDef $ toBuiltin ([1 .. 10] :: [Integer]) l2 :: CompiledCode (L.BuiltinList P.BuiltinBool) l2 = liftCodeDef $ toBuiltin ([True, False] :: [Bool]) -l3 :: CompiledCode (L.BuiltinList (P.BuiltinPair Integer Integer)) -l3 = liftCodeDef $ toBuiltin ([ (1, 2), (3, 4), (5, 6) ] :: [(Integer, Integer)]) +-- l3 :: CompiledCode (L.BuiltinList (P.BuiltinPair Integer Integer)) +-- l3 = liftCodeDef $ toBuiltin ([ (1, 2), (3, 4), (5, 6) ] :: [(Integer, Integer)]) From 4e938f48d793c3dfc97a5dbd9297debd362f4584 Mon Sep 17 00:00:00 2001 From: zeme Date: Wed, 21 May 2025 15:05:37 +0200 Subject: [PATCH 08/30] wip --- SECURITY.md | 3 +- .../src/PlutusTx/Compiler/Expr.hs | 8 -- .../BuiltinList/Budget/9.6/nub.eval.golden | 5 ++ .../BuiltinList/Budget/9.6/nub.pir.golden | 5 +- .../BuiltinList/Budget/9.6/nub.uplc.golden | 9 +-- .../BuiltinList/Budget/9.6/nubBy.eval.golden | 5 ++ .../BuiltinList/Budget/9.6/nubBy.pir.golden | 5 +- .../BuiltinList/Budget/9.6/nubBy.uplc.golden | 9 +-- .../test/BuiltinList/Budget/Spec.hs | 73 ++++++++++--------- plutus-tx/src/PlutusTx/BuiltinList.hs | 6 +- plutus-tx/src/PlutusTx/Builtins.hs | 3 + plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs | 2 + plutus-tx/src/PlutusTx/List.hs | 3 +- 13 files changed, 75 insertions(+), 61 deletions(-) create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden diff --git a/SECURITY.md b/SECURITY.md index 3de629817d2..5c70e7743d2 100644 --- a/SECURITY.md +++ b/SECURITY.md @@ -15,4 +15,5 @@ Please provide a clear and concise description of the vulnerability, including: If you have developed any code or utilities that can help demonstrate the suspected vulnerability, please mention them in your email but ***DO NOT*** attempt to include them as attachments as this may cause your Email to be blocked by spam filters. -See the security file in the [Cardano engineering handbook](https://github.com/input-output-hk/cardano-engineering-handbook/blob/main/SECURITY.md). \ No newline at end of file +See the security file in the [Cardano engineering handbook](https://github.com/input-output-hk/cardano-engineering-handbook/blob/main/SECURITY.md). + diff --git a/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs b/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs index f48ef912318..e2491c42e78 100644 --- a/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs +++ b/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs @@ -843,7 +843,6 @@ compileExpr e = traceCompilation 2 ("Compiling expr:" GHC.<+> GHC.ppr e) $ do builtinBoolTyCon <- lookupGhcTyCon ''BI.BuiltinBool builtinDataTyCon <- lookupGhcTyCon ''Builtins.BuiltinData builtinPairTyCon <- lookupGhcTyCon ''BI.BuiltinPair - builtinListTyCon <- lookupGhcTyCon ''BI.BuiltinList stringTyName <- lookupGhcName ''Builtins.BuiltinString stringToBuiltinStringName <- lookupGhcName 'Builtins.stringToBuiltinString builtinByteStringTyName <- lookupGhcName ''Builtins.BuiltinByteString @@ -1019,13 +1018,6 @@ compileExpr e = traceCompilation 2 ("Compiling expr:" GHC.<+> GHC.ppr e) $ do | (tyCon, tyArg1, tyArg2) == (builtinPairTyCon, builtinDataTyCon, builtinDataTyCon) -> pure $ PLC.mkConstant annMayInline ([] @(PLC.Data, PLC.Data)) - GHC.TyConApp tyCon [GHC.TyConApp tyArg1 []] - | (tyCon, tyArg1) == (builtinListTyCon, builtinIntegerTyCon) -> - pure $ PLC.mkConstant annMayInline ([] @[Integer]) - | (tyCon, tyArg1) == (builtinListTyCon, builtinBoolTyCon) -> - pure $ PLC.mkConstant annMayInline ([] @[Bool]) - | (tyCon, tyArg1) == (builtinListTyCon, builtinDataTyCon) -> - pure $ PLC.mkConstant annMayInline ([] @[PLC.Data]) _ -> throwPlain $ CompilationError "'mkNil' applied to an unknown type" diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden new file mode 100644 index 00000000000..ed4d9be1c6e --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden @@ -0,0 +1,5 @@ +cpu: 72202849 +mem: 301062 +size: 114 + +(con (list integer) [1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden index 86d1e402861..36153711de8 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden @@ -15,7 +15,7 @@ let in letrec !go : list integer -> list integer -> list integer - = \(xs : list integer) -> + = \(l : list integer) (xs : list integer) -> caseList' {integer} {list integer} @@ -46,5 +46,6 @@ letrec (/\dead -> go ys xs) (/\dead -> mkCons {integer} y (go ys (mkCons {integer} y xs))) {all dead. dead}) + l in -\(xs : list integer) -> go [] xs \ No newline at end of file +\(xs : list integer) -> go xs [] \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden index a4202fc1abe..a1c1daffffb 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden @@ -1,9 +1,9 @@ (program 1.1.0 ((\caseList' -> - (\go xs -> go [] xs) + (\go xs -> go xs []) ((\s -> s s) - (\s xs -> + (\s l xs -> caseList' [] (\y ys -> @@ -22,9 +22,8 @@ xs) [ (delay (s s ys xs)) , (delay - (force mkCons - y - (s s ys (force mkCons y xs)))) ]))))) + (force mkCons y (s s ys (force mkCons y xs)))) ])) + l))) (\z f xs -> force (force (force chooseList) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden new file mode 100644 index 00000000000..d68444d7713 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden @@ -0,0 +1,5 @@ +cpu: 71885914 +mem: 301062 +size: 114 + +(con (list integer) [1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden index 764882df8e1..2ab6b4b8160 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden @@ -15,7 +15,7 @@ let in letrec !go : list integer -> list integer -> list integer - = \(xs : list integer) -> + = \(l : list integer) (xs : list integer) -> caseList' {integer} {list integer} @@ -46,5 +46,6 @@ letrec (/\dead -> go ys xs) (/\dead -> mkCons {integer} y (go ys (mkCons {integer} y xs))) {all dead. dead}) + l in -\(xs : list integer) -> go [] xs \ No newline at end of file +\(xs : list integer) -> go xs [] \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden index c1e8c095e64..447aeb9216f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden @@ -1,9 +1,9 @@ (program 1.1.0 ((\caseList' -> - (\go xs -> go [] xs) + (\go xs -> go xs []) ((\s -> s s) - (\s xs -> + (\s l xs -> caseList' [] (\y ys -> @@ -22,9 +22,8 @@ xs) [ (delay (s s ys xs)) , (delay - (force mkCons - y - (s s ys (force mkCons y xs)))) ]))))) + (force mkCons y (s s ys (force mkCons y xs)))) ])) + l))) (\z f xs -> force (force (force chooseList) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index 287b662ee27..40b9b0d8c5f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -46,8 +46,6 @@ tests = , goldenBundle "notElem" notElem (notElem `unsafeApplyCode` l1) , goldenBundle "foldr" foldr (foldr `unsafeApplyCode` l1) , goldenBundle "foldl" foldl (foldl `unsafeApplyCode` l1) - -- , goldenBundle "concat" concat (concat `unsafeApplyCode` l1) - -- , goldenBundle "concatMap" concatMap (concatMap `unsafeApplyCode` l1) , goldenBundle "listToMaybeJust" listToMaybeJust (listToMaybeJust `unsafeApplyCode` l1) , goldenBundle "listToMaybeNothing" listToMaybeNothing (listToMaybeNothing `unsafeApplyCode` l1) @@ -59,9 +57,6 @@ tests = , goldenBundle "replicate" replicate (replicate `unsafeApplyCode` l1) , goldenBundle "findIndexJust" findIndexJust (findIndexJust `unsafeApplyCode` l1) , goldenBundle "findIndexNothing" findIndexNothing (findIndexNothing `unsafeApplyCode` l1) - -- , goldenBundle "unzip" unzip (unzip `unsafeApplyCode` l3) - -- , goldenBundle "zip" zip (zip `unsafeApplyCode` l1) - -- , goldenBundle "zipWith" zipWith (zipWith `unsafeApplyCode` l1) , goldenBundle "headOk" headOk (headOk `unsafeApplyCode` l1) , goldenBundle "headEmpty" headEmpty (headEmpty `unsafeApplyCode` l1) , goldenBundle "lastOk" lastOk (lastOk `unsafeApplyCode` l1) @@ -71,13 +66,21 @@ tests = , goldenBundle "take" take (take `unsafeApplyCode` l1) , goldenBundle "drop" drop (drop `unsafeApplyCode` l1) , goldenBundle "dropWhile" dropWhile (dropWhile `unsafeApplyCode` l1) - -- , goldenBundle "splitAt" splitAt (splitAt `unsafeApplyCode` l1) , goldenBundle "elemBy" elemBy (elemBy `unsafeApplyCode` l1) + , goldenBundle "nub" nub (nub `unsafeApplyCode` l1) + , goldenBundle "nubBy" nubBy (nubBy `unsafeApplyCode` l1) + -- TODO The following tests are ignored because they require implementation of + -- arbitrarily nested BuiltinList types. + -- See `class MkNil` in PlutusTx.Builtins.HasOpaque. + -- , goldenBundle "concat" concat (concat `unsafeApplyCode` l1) + -- , goldenBundle "concatMap" concatMap (concatMap `unsafeApplyCode` l1) + -- , goldenBundle "unzip" unzip (unzip `unsafeApplyCode` l3) + -- , goldenBundle "zip" zip (zip `unsafeApplyCode` l1) + -- , goldenBundle "zipWith" zipWith (zipWith `unsafeApplyCode` l1) + -- , goldenBundle "splitAt" splitAt (splitAt `unsafeApplyCode` l1) -- , goldenBundle "partition" partition (partition `unsafeApplyCode` l1) -- , goldenBundle "sort" sort (sort `unsafeApplyCode` l1) -- , goldenBundle "sortBy" sortBy (sortBy `unsafeApplyCode` l1) - -- , goldenBundle "nub" nub (nub `unsafeApplyCode` l1) - -- , goldenBundle "nubBy" nubBy (nubBy `unsafeApplyCode` l1) ] map :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) @@ -158,12 +161,6 @@ foldr = $$(compile [|| \xs -> L.foldr (P.+) 0 xs ||]) foldl :: CompiledCode (L.BuiltinList Integer -> Integer) foldl = $$(compile [|| \xs -> L.foldl (P.*) 0 xs ||]) -concat :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -concat = undefined -- $$(compile [|| \xs -> L.concat (xs L.<| L.singleton xs) ||]) - -concatMap :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -concatMap = undefined -- $$(compile [|| \xs -> L.concatMap ( \x -> L.singleton (1 P.+ x) ) xs ||]) - listToMaybeJust :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) listToMaybeJust = $$(compile [|| \xs -> L.listToMaybe xs ||]) @@ -191,12 +188,6 @@ findIndexJust = $$(compile [|| \xs -> L.findIndex (P.== 4) xs ||]) findIndexNothing :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) findIndexNothing = $$(compile [|| \xs -> L.findIndex (P.== 99) xs ||]) -unzip :: CompiledCode (L.BuiltinList (P.BuiltinPair a b) -> L.BuiltinList Integer) -unzip = undefined -- $$(compile [|| \xs -> L.unzip xs ||]) - -zip :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList (P.BuiltinPair Integer Integer)) -zip = undefined -- $$(compile [|| \xs -> L.zip xs xs ||]) - zipWith :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) zipWith = $$(compile [|| \xs -> L.zipWith (P.+) xs xs ||]) @@ -227,15 +218,37 @@ drop = $$(compile [|| \xs -> L.drop 5 xs ||]) dropWhile :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) dropWhile = $$(compile [|| \xs -> L.dropWhile (P.< 5) xs ||]) +elemBy :: CompiledCode (L.BuiltinList Integer -> Bool) +elemBy = $$(compile [|| \xs -> L.elemBy (P.<=) 0 xs ||]) + +nub :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +nub = $$(compile [|| \xs -> L.nub xs ||]) + +nubBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +nubBy = $$(compile [|| \xs -> L.nubBy (P.>=) xs ||]) + +l1 :: CompiledCode (L.BuiltinList Integer) +l1 = liftCodeDef $ toBuiltin ([1 .. 10] :: [Integer]) + +l2 :: CompiledCode (L.BuiltinList P.BuiltinBool) +l2 = liftCodeDef $ toBuiltin ([True, False] :: [Bool]) + +-- TODO The following functions cannot compile because they require implementation of +-- arbitrarily nested BuiltinList types. +-- See `class MkNil` in PlutusTx.Builtins.HasOpaque. + +concat :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +concat = undefined -- $$(compile [|| \xs -> L.concat (xs L.<| L.singleton xs) ||]) + +concatMap :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) +concatMap = undefined -- $$(compile [|| \xs -> L.concatMap ( \x -> L.singleton (1 P.+ x) ) xs ||]) + splitAt :: CompiledCode ( L.BuiltinList Integer -> P.BuiltinPair (L.BuiltinList Integer) (L.BuiltinList Integer) ) splitAt = undefined -- $$(compile [|| \xs -> L.splitAt 2 xs ||]) -elemBy :: CompiledCode (L.BuiltinList Integer -> Bool) -elemBy = $$(compile [|| \xs -> L.elemBy (P.<=) 0 xs ||]) - partition :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) partition = undefined -- $$(compile [|| L.partition ||]) @@ -245,17 +258,11 @@ sort = undefined -- $$(compile [|| \xs -> L.sort xs ||]) sortBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) sortBy = undefined -- $$(compile [|| \xs -> L.sortBy (P.<=) xs ||]) --- nub :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) --- nub = $$(compile [|| \xs -> L.nub xs ||]) - --- nubBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) --- nubBy = $$(compile [|| \xs -> L.nubBy (P.>=) xs ||]) - -l1 :: CompiledCode (L.BuiltinList Integer) -l1 = liftCodeDef $ toBuiltin ([1 .. 10] :: [Integer]) +unzip :: CompiledCode (L.BuiltinList (P.BuiltinPair a b) -> L.BuiltinList Integer) +unzip = undefined -- $$(compile [|| \xs -> L.unzip xs ||]) -l2 :: CompiledCode (L.BuiltinList P.BuiltinBool) -l2 = liftCodeDef $ toBuiltin ([True, False] :: [Bool]) +zip :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList (P.BuiltinPair Integer Integer)) +zip = undefined -- $$(compile [|| \xs -> L.zip xs xs ||]) -- l3 :: CompiledCode (L.BuiltinList (P.BuiltinPair Integer Integer)) -- l3 = liftCodeDef $ toBuiltin ([ (1, 2), (3, 4), (5, 6) ] :: [(Integer, Integer)]) diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index 9c087c5525d..032f1a8e08b 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -374,15 +374,15 @@ elemBy eq y = go -- | Plutus Tx version of 'Data.List.nubBy' for 'BuiltinList'. nubBy :: forall a. (MkNil a) => (a -> a -> Bool) -> BuiltinList a -> BuiltinList a -nubBy eq = go empty +nubBy eq = flip go empty where go :: BuiltinList a -> BuiltinList a -> BuiltinList a - go xs = caseList' empty + go l xs = caseList' empty ( \y ys -> if elemBy eq y xs then go ys xs else y <| go ys (y <| xs) - ) + ) l {-# INLINABLE nubBy #-} -- | Plutus Tx version of 'Data.List.zipWith' for 'BuiltinList'. diff --git a/plutus-tx/src/PlutusTx/Builtins.hs b/plutus-tx/src/PlutusTx/Builtins.hs index a97ca15c185..77c9bd26430 100644 --- a/plutus-tx/src/PlutusTx/Builtins.hs +++ b/plutus-tx/src/PlutusTx/Builtins.hs @@ -485,6 +485,7 @@ pairToPair :: BI.BuiltinPair a b -> (a, b) pairToPair tup = (BI.fst tup, BI.snd tup) {-# INLINE pairToPair #-} +<<<<<<< HEAD <<<<<<< HEAD sopListToArray :: (HasToOpaque a arep, MkNil arep) => [a] -> BI.BuiltinArray arep ======= @@ -493,6 +494,8 @@ pairFromPair :: (a, b) -> BI.BuiltinPair a b pairFromPair = BI.BuiltinPair {-# INLINE pairFromPair #-} +======= +>>>>>>> c6f4afe5d3 (wip) sopListToArray :: (HasToOpaque a arep, MkNil arep) => [a] -> BI.BuiltinArray arep >>>>>>> 14e3427f6c (PlutusTx.Data.List & PlutusTx.BuiltinList - Feature Parity) sopListToArray l = BI.listToArray (toOpaque l) diff --git a/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs b/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs index 73249224495..0ac1fe377fb 100644 --- a/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs +++ b/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs @@ -274,6 +274,8 @@ class MkNil arep where instance MkNil BuiltinInteger instance MkNil BuiltinBool instance MkNil BuiltinData +-- TODO: the following two instances are not implemented in the plugin. +-- They require changes to PlutusTx.Compiler.Expr.compileExpr instance (MkNil a) => MkNil (BuiltinList a) instance (MkNil a, MkNil b) => MkNil (BuiltinPair a b) diff --git a/plutus-tx/src/PlutusTx/List.hs b/plutus-tx/src/PlutusTx/List.hs index e0f1ade12e7..7f59fe60675 100644 --- a/plutus-tx/src/PlutusTx/List.hs +++ b/plutus-tx/src/PlutusTx/List.hs @@ -263,7 +263,7 @@ findIndex f = go 0 -} infixl 9 !! (!!) :: forall a. [a] -> Integer -> a -_ !! n0 | n0 < 0 = traceError negativeIndexError -- Builtin . lessThan +_ !! n0 | n0 < 0 = traceError negativeIndexError xs0 !! n0 = go n0 xs0 where go :: Integer -> [a] -> a @@ -404,7 +404,6 @@ nubBy eq l = nubBy' l [] {-# INLINEABLE nubBy #-} -- | Plutus Tx version of 'Data.List.zipWith'. --- TODO loses elements if the lists are of different lengths zipWith :: forall a b c. (a -> b -> c) -> [a] -> [b] -> [c] zipWith f = go where From 51d349d602f0b4d5faa2015533f296c2238703a3 Mon Sep 17 00:00:00 2001 From: zeme Date: Thu, 22 May 2025 14:51:02 +0200 Subject: [PATCH 09/30] wip --- plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs | 17 +++++------------ .../test/BuiltinList/Budget/Spec.hs | 10 +++++----- plutus-tx/src/PlutusTx/BuiltinList.hs | 2 +- 3 files changed, 11 insertions(+), 18 deletions(-) diff --git a/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs b/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs index e2491c42e78..c6462c4d3dc 100644 --- a/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs +++ b/plutus-tx-plugin/src/PlutusTx/Compiler/Expr.hs @@ -1003,24 +1003,17 @@ compileExpr e = traceCompilation 2 ("Compiling expr:" GHC.<+> GHC.ppr e) $ do -- GHC.Var (isErrorId -> True) `GHC.App` GHC.Type t `GHC.App` _ -> PIR.TyInst annMayInline <$> errorFunc <*> compileTypeNorm t - - (strip -> GHC.Var n) `GHC.App` GHC.Type ty | GHC.getName n == mkNilOpaqueName -> - case ty of + (strip -> GHC.Var n) `GHC.App` GHC.Type ty + | GHC.getName n == mkNilOpaqueName -> case ty of GHC.TyConApp tyCon [] | tyCon == GHC.integerTyCon || tyCon == builtinIntegerTyCon -> pure $ PLC.mkConstant annMayInline ([] @Integer) - | tyCon == builtinBoolTyCon -> - pure $ PLC.mkConstant annMayInline ([] @Bool) - | tyCon == builtinDataTyCon -> - pure $ PLC.mkConstant annMayInline ([] @PLC.Data) - + | tyCon == builtinBoolTyCon -> pure $ PLC.mkConstant annMayInline ([] @Bool) + | tyCon == builtinDataTyCon -> pure $ PLC.mkConstant annMayInline ([] @PLC.Data) GHC.TyConApp tyCon [GHC.TyConApp tyArg1 [], GHC.TyConApp tyArg2 []] | (tyCon, tyArg1, tyArg2) == (builtinPairTyCon, builtinDataTyCon, builtinDataTyCon) -> pure $ PLC.mkConstant annMayInline ([] @(PLC.Data, PLC.Data)) - - _ -> - throwPlain $ CompilationError "'mkNil' applied to an unknown type" - + _ -> throwPlain $ CompilationError "'mkNil' applied to an unknown type" GHC.Var n | GHC.getName n == useToOpaqueName -> throwPlain $ diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index 40b9b0d8c5f..ec8817885ea 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -120,7 +120,7 @@ empty :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) empty = $$(compile [|| \_ -> L.empty ||]) singleton :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -singleton = $$(compile [|| \_ -> L.singleton 1 ||]) +singleton = $$(compile [|| \_ -> L.singleton 42 ||]) null :: CompiledCode (L.BuiltinList Integer -> Bool) null = $$(compile [|| \xs -> L.null xs ||]) @@ -159,7 +159,7 @@ foldr :: CompiledCode (L.BuiltinList Integer -> Integer) foldr = $$(compile [|| \xs -> L.foldr (P.+) 0 xs ||]) foldl :: CompiledCode (L.BuiltinList Integer -> Integer) -foldl = $$(compile [|| \xs -> L.foldl (P.*) 0 xs ||]) +foldl = $$(compile [|| \xs -> L.foldl (P.*) 1 xs ||]) listToMaybeJust :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) listToMaybeJust = $$(compile [|| \xs -> L.listToMaybe xs ||]) @@ -222,16 +222,16 @@ elemBy :: CompiledCode (L.BuiltinList Integer -> Bool) elemBy = $$(compile [|| \xs -> L.elemBy (P.<=) 0 xs ||]) nub :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -nub = $$(compile [|| \xs -> L.nub xs ||]) +nub = $$(compile [|| \xs -> L.nub (L.concat xs xs xs) ||]) nubBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -nubBy = $$(compile [|| \xs -> L.nubBy (P.>=) xs ||]) +nubBy = $$(compile [|| \xs -> L.nubBy (P.<=) xs ||]) l1 :: CompiledCode (L.BuiltinList Integer) l1 = liftCodeDef $ toBuiltin ([1 .. 10] :: [Integer]) l2 :: CompiledCode (L.BuiltinList P.BuiltinBool) -l2 = liftCodeDef $ toBuiltin ([True, False] :: [Bool]) +l2 = liftCodeDef $ toBuiltin ([True, False, True, False] :: [Bool]) -- TODO The following functions cannot compile because they require implementation of -- arbitrarily nested BuiltinList types. diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index 032f1a8e08b..937658f3783 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -317,7 +317,7 @@ head = caseList last :: forall a. BuiltinList a -> a last = caseList ( \_ -> traceError lastEmptyBuiltinListError ) - ( \x -> caseList' x ( \_ -> last ) + ( \x xs -> caseList' x ( \_ _ -> last xs ) xs ) {-# INLINABLE last #-} From 33617a982715e166f0a40b0d0f7fbcb18d96184a Mon Sep 17 00:00:00 2001 From: zeme Date: Thu, 22 May 2025 14:58:36 +0200 Subject: [PATCH 10/30] wip --- .../BuiltinList/Budget/9.6/foldl.eval.golden | 2 +- .../BuiltinList/Budget/9.6/foldl.pir.golden | 2 +- .../BuiltinList/Budget/9.6/foldl.uplc.golden | 2 +- .../Budget/9.6/headEmpty.eval.golden | 3 ++- .../Budget/9.6/indexNegative.eval.golden | 3 ++- .../Budget/9.6/indexTooLarge.eval.golden | 3 ++- .../Budget/9.6/lastEmpty.eval.golden | 3 ++- .../Budget/9.6/lastEmpty.pir.golden | 2 +- .../Budget/9.6/lastEmpty.uplc.golden | 5 ++++- .../BuiltinList/Budget/9.6/lastOk.eval.golden | 7 ++++-- .../BuiltinList/Budget/9.6/lastOk.pir.golden | 2 +- .../BuiltinList/Budget/9.6/lastOk.uplc.golden | 5 ++++- .../BuiltinList/Budget/9.6/nub.eval.golden | 6 ++--- .../BuiltinList/Budget/9.6/nub.pir.golden | 22 ++++++++++++++++++- .../BuiltinList/Budget/9.6/nub.uplc.golden | 7 +++++- .../BuiltinList/Budget/9.6/nubBy.eval.golden | 6 ++--- .../BuiltinList/Budget/9.6/nubBy.pir.golden | 6 ++--- .../BuiltinList/Budget/9.6/nubBy.uplc.golden | 6 ++--- .../Budget/9.6/singleton.eval.golden | 2 +- .../Budget/9.6/singleton.pir.golden | 2 +- .../Budget/9.6/singleton.uplc.golden | 2 +- .../Budget/9.6/tailEmpty.eval.golden | 3 ++- .../test/BuiltinList/Budget/Spec.hs | 2 +- 23 files changed, 71 insertions(+), 32 deletions(-) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden index f0184f44abc..c1ae4ce26a0 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden @@ -2,4 +2,4 @@ cpu: 10564694 mem: 42012 size: 55 -(con integer 0) \ No newline at end of file +(con integer 3628800) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.pir.golden index 7862d8270ca..8c537ad0d3e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.pir.golden @@ -14,4 +14,4 @@ letrec go (multiplyInteger acc x) xs) {integer} in -\(xs : list integer) -> go 0 xs \ No newline at end of file +\(xs : list integer) -> go 1 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden index 8322b8d50f8..4cb7ba65d72 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden @@ -1,6 +1,6 @@ (program 1.1.0 - ((\go xs -> go 0 xs) + ((\go xs -> go 1 xs) ((\s -> s s) (\s acc xs -> force diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.eval.golden index f2c04fe10eb..1c1ef919814 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.eval.golden @@ -1,2 +1,3 @@ An error has occurred: -The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. \ No newline at end of file +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. +Caused by: error \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.eval.golden index f2c04fe10eb..1c1ef919814 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.eval.golden @@ -1,2 +1,3 @@ An error has occurred: -The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. \ No newline at end of file +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. +Caused by: error \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.eval.golden index f2c04fe10eb..1c1ef919814 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.eval.golden @@ -1,2 +1,3 @@ An error has occurred: -The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. \ No newline at end of file +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. +Caused by: error \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.eval.golden index f2c04fe10eb..1c1ef919814 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.eval.golden @@ -1,2 +1,3 @@ An error has occurred: -The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. \ No newline at end of file +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. +Caused by: error \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.pir.golden index b7c27a9bfab..9033db2f166 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.pir.golden @@ -25,7 +25,7 @@ letrec in error {a}) (\(x : a) (xs : list a) (ds : Unit) -> - caseList' {a} {a} x (\(ds : a) -> last {a}) xs) + caseList' {a} {a} x (\(ds : a) (ds : list a) -> last {a} xs) xs) l Unit in diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden index 64812a5b424..e9503910195 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden @@ -9,7 +9,10 @@ caseList' (\ds -> (\x -> error) (force trace "PT25" (constr 0 []))) (\x xs ds -> - caseList' x (\ds -> force (s s (delay (\x -> x)))) xs) + caseList' + x + (\ds ds -> force (s s (delay (\x -> x))) xs) + xs) l (constr 0 []))) (delay (\x -> x)))) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden index f2c04fe10eb..9303a55d91e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden @@ -1,2 +1,5 @@ -An error has occurred: -The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. \ No newline at end of file +cpu: 17967427 +mem: 78056 +size: 87 + +(con integer 10) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.pir.golden index ec52654da5d..22c3a114a04 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.pir.golden @@ -25,7 +25,7 @@ letrec in error {a}) (\(x : a) (xs : list a) (ds : Unit) -> - caseList' {a} {a} x (\(ds : a) -> last {a}) xs) + caseList' {a} {a} x (\(ds : a) (ds : list a) -> last {a} xs) xs) l Unit in diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden index c1ed70ae53a..a2aff3024b6 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden @@ -9,7 +9,10 @@ caseList' (\ds -> (\x -> error) (force trace "PT25" (constr 0 []))) (\x xs ds -> - caseList' x (\ds -> force (s s (delay (\x -> x)))) xs) + caseList' + x + (\ds ds -> force (s s (delay (\x -> x))) xs) + xs) l (constr 0 []))) (delay (\x -> x)))) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden index ed4d9be1c6e..da937161e5e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden @@ -1,5 +1,5 @@ -cpu: 72202849 -mem: 301062 -size: 114 +cpu: 157975998 +mem: 655724 +size: 137 (con (list integer) [1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden index 36153711de8..cf54189252c 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden @@ -48,4 +48,24 @@ letrec {all dead. dead}) l in -\(xs : list integer) -> go xs [] \ No newline at end of file +\(xs : list integer) -> + let + !eta : list integer + = (let + b = list integer + in + \(f : integer -> b -> b) (acc : b) -> + letrec + !go : list integer -> b + = caseList' + {integer} + {b} + acc + (\(x : integer) (xs : list integer) -> f x (go xs)) + in + go) + (mkCons {integer}) + xs + xs + in + go eta [] \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden index a1c1daffffb..68bf6347fa7 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden @@ -1,7 +1,12 @@ (program 1.1.0 ((\caseList' -> - (\go xs -> go xs []) + (\go xs -> + go + ((\s -> s s) + (\s -> caseList' xs (\x xs -> force mkCons x (s s xs))) + xs) + []) ((\s -> s s) (\s l xs -> caseList' diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden index d68444d7713..bae47f5774e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden @@ -1,5 +1,5 @@ -cpu: 71885914 -mem: 301062 +cpu: 22604119 +mem: 98670 size: 114 -(con (list integer) [1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file +(con (list integer) [1]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden index 2ab6b4b8160..0cccfdb4edb 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden @@ -32,9 +32,9 @@ letrec Bool_match (ifThenElse {Bool} - (lessThanInteger x y) - False - True) + (lessThanEqualsInteger x y) + True + False) {all dead. Bool} (/\dead -> True) (/\dead -> go xs) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden index 447aeb9216f..92444bc80a1 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden @@ -16,9 +16,9 @@ (\x xs -> force (force ifThenElse - (lessThanInteger x y) - (delay (s s xs)) - (delay (constr 0 []))))) + (lessThanEqualsInteger x y) + (delay (constr 0 [])) + (delay (s s xs))))) xs) [ (delay (s s ys xs)) , (delay diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden index 2c86e256dd2..34304684821 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden @@ -2,4 +2,4 @@ cpu: 64100 mem: 500 size: 4 -(con (list integer) [1]) \ No newline at end of file +(con (list integer) [42]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.pir.golden index 0f64ef8492e..32193031548 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.pir.golden @@ -1 +1 @@ -\(ds : list integer) -> [1] \ No newline at end of file +\(ds : list integer) -> [42] \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden index d7c5977f73c..26d8c4ac9b7 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden @@ -1 +1 @@ -(program 1.1.0 (\ds -> [1])) \ No newline at end of file +(program 1.1.0 (\ds -> [42])) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.eval.golden index f2c04fe10eb..1c1ef919814 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.eval.golden @@ -1,2 +1,3 @@ An error has occurred: -The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. \ No newline at end of file +The machine terminated because of an error, either from a built-in function or from an explicit use of 'error'. +Caused by: error \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index ec8817885ea..ae776639824 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -222,7 +222,7 @@ elemBy :: CompiledCode (L.BuiltinList Integer -> Bool) elemBy = $$(compile [|| \xs -> L.elemBy (P.<=) 0 xs ||]) nub :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -nub = $$(compile [|| \xs -> L.nub (L.concat xs xs xs) ||]) +nub = $$(compile [|| \xs -> L.nub (L.append xs xs) ||]) nubBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) nubBy = $$(compile [|| \xs -> L.nubBy (P.<=) xs ||]) From 5a2b3422c990bb3bcaa5c9ce9df24e219ba23cd0 Mon Sep 17 00:00:00 2001 From: zeme Date: Mon, 26 May 2025 16:51:08 +0200 Subject: [PATCH 11/30] wip --- .../BuiltinList/Budget/9.6/concat.eval.golden | 5 ++ .../BuiltinList/Budget/9.6/concat.pir.golden | 42 +++++++++++++ .../BuiltinList/Budget/9.6/concat.uplc.golden | 22 +++++++ .../Budget/9.6/concatMap.eval.golden | 5 ++ .../Budget/9.6/concatMap.pir.golden | 62 +++++++++++++++++++ .../Budget/9.6/concatMap.uplc.golden | 38 ++++++++++++ .../test/BuiltinList/Budget/Spec.hs | 18 +++--- 7 files changed, 185 insertions(+), 7 deletions(-) create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.uplc.golden diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden new file mode 100644 index 00000000000..7b47bf3084d --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden @@ -0,0 +1,5 @@ +cpu: 7467372 +mem: 32100 +size: 75 + +(con (list integer) [1,2,3,4]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden new file mode 100644 index 00000000000..e6f0d202d3d --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden @@ -0,0 +1,42 @@ +let + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} +in +\(xss : list (list integer)) -> + (letrec + !go : list (list integer) -> list integer + = caseList' + {list integer} + {list integer} + [] + (\(x : list integer) (xs : list (list integer)) -> + let + !r : list integer = go xs + in + (let + b = list integer + in + \(f : integer -> b -> b) (acc : b) -> + letrec + !go : list integer -> b + = caseList' + {integer} + {b} + acc + (\(x : integer) (xs : list integer) -> f x (go xs)) + in + go) + (mkCons {integer}) + r + x) + in + go) + xss \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden new file mode 100644 index 00000000000..c79e107e23b --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden @@ -0,0 +1,22 @@ +(program + 1.1.0 + (\xss -> + (\caseList' -> + (\s -> s s) + (\s -> + caseList' + [] + (\x xs -> + (\acc -> + (\s -> s s) + (\s -> + caseList' acc (\x xs -> force mkCons x (s s xs)))) + (s s xs) + x))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))) + xss)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden new file mode 100644 index 00000000000..8b602509874 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden @@ -0,0 +1,5 @@ +cpu: 56224464 +mem: 237912 +size: 120 + +(con (list integer) [1,1,2,2,3,3,4,4,5,5,6,6,7,7,8,8,9,9,10,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.pir.golden new file mode 100644 index 00000000000..ed94210abf4 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.pir.golden @@ -0,0 +1,62 @@ +let + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + data Bool | Bool_match where + True : Bool + False : Bool +in +\(xss : list integer) -> + (letrec + !go : list integer -> list integer + = caseList' + {integer} + {list integer} + [] + (\(x : integer) -> + letrec + !go : integer -> list integer + = \(n : integer) -> + Bool_match + (ifThenElse + {Bool} + (lessThanEqualsInteger n 0) + True + False) + {all dead. list integer} + (/\dead -> []) + (/\dead -> + mkCons {integer} x (go (subtractInteger n 1))) + {all dead. dead} + in + \(xs : list integer) -> + let + !ys : list integer = go xs + !l : list integer = go 2 + in + (let + b = list integer + in + \(f : integer -> b -> b) (acc : b) -> + letrec + !go : list integer -> b + = caseList' + {integer} + {b} + acc + (\(x : integer) (xs : list integer) -> f x (go xs)) + in + go) + (mkCons {integer}) + ys + l) + in + go) + xss \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.uplc.golden new file mode 100644 index 00000000000..1d8408b64ed --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.uplc.golden @@ -0,0 +1,38 @@ +(program + 1.1.0 + (\xss -> + (\caseList' -> + (\s -> s s) + (\s -> + caseList' + [] + (\x -> + (\go xs -> + (\ys -> + (\l -> + (\s -> s s) + (\s -> + caseList' + ys + (\x xs -> force mkCons x (s s xs))) + l) + (go 2)) + (s s xs)) + ((\s -> s s) + (\s n -> + force + (force ifThenElse + (lessThanEqualsInteger n 0) + (delay []) + (delay + (force mkCons + x + ((\x -> s s x) + (subtractInteger n 1)))))))))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))) + xss)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index ae776639824..5e2766140ce 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -72,8 +72,8 @@ tests = -- TODO The following tests are ignored because they require implementation of -- arbitrarily nested BuiltinList types. -- See `class MkNil` in PlutusTx.Builtins.HasOpaque. - -- , goldenBundle "concat" concat (concat `unsafeApplyCode` l1) - -- , goldenBundle "concatMap" concatMap (concatMap `unsafeApplyCode` l1) + , goldenBundle "concat" concat (concat `unsafeApplyCode` l4) + , goldenBundle "concatMap" concatMap (concatMap `unsafeApplyCode` l1) -- , goldenBundle "unzip" unzip (unzip `unsafeApplyCode` l3) -- , goldenBundle "zip" zip (zip `unsafeApplyCode` l1) -- , goldenBundle "zipWith" zipWith (zipWith `unsafeApplyCode` l1) @@ -233,15 +233,21 @@ l1 = liftCodeDef $ toBuiltin ([1 .. 10] :: [Integer]) l2 :: CompiledCode (L.BuiltinList P.BuiltinBool) l2 = liftCodeDef $ toBuiltin ([True, False, True, False] :: [Bool]) +l3 :: CompiledCode (L.BuiltinList (P.BuiltinPair Integer Integer)) +l3 = liftCodeDef $ toBuiltin ([ (1, 2), (3, 4), (5, 6) ] :: [(Integer, Integer)]) + +l4 :: CompiledCode (L.BuiltinList (L.BuiltinList Integer)) +l4 = liftCodeDef $ toBuiltin ([[1, 2], [3, 4]] :: [[Integer]]) + -- TODO The following functions cannot compile because they require implementation of -- arbitrarily nested BuiltinList types. -- See `class MkNil` in PlutusTx.Builtins.HasOpaque. -concat :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -concat = undefined -- $$(compile [|| \xs -> L.concat (xs L.<| L.singleton xs) ||]) +concat :: CompiledCode (L.BuiltinList (L.BuiltinList Integer) -> L.BuiltinList Integer) +concat = $$(compile [|| \xss -> L.concat xss ||]) concatMap :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -concatMap = undefined -- $$(compile [|| \xs -> L.concatMap ( \x -> L.singleton (1 P.+ x) ) xs ||]) +concatMap = $$(compile [|| \xss -> L.concatMap (L.replicate 2) xss ||]) splitAt :: CompiledCode ( @@ -264,5 +270,3 @@ unzip = undefined -- $$(compile [|| \xs -> L.unzip xs ||]) zip :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList (P.BuiltinPair Integer Integer)) zip = undefined -- $$(compile [|| \xs -> L.zip xs xs ||]) --- l3 :: CompiledCode (L.BuiltinList (P.BuiltinPair Integer Integer)) --- l3 = liftCodeDef $ toBuiltin ([ (1, 2), (3, 4), (5, 6) ] :: [(Integer, Integer)]) From 8b12c98c3159fffad9317277d4613eb280bb2c1c Mon Sep 17 00:00:00 2001 From: zeme Date: Mon, 26 May 2025 16:56:04 +0200 Subject: [PATCH 12/30] donw --- plutus-tx/src/PlutusTx/Builtins.hs | 12 ------------ plutus-tx/src/PlutusTx/List.hs | 12 ------------ 2 files changed, 24 deletions(-) diff --git a/plutus-tx/src/PlutusTx/Builtins.hs b/plutus-tx/src/PlutusTx/Builtins.hs index 77c9bd26430..3914701f173 100644 --- a/plutus-tx/src/PlutusTx/Builtins.hs +++ b/plutus-tx/src/PlutusTx/Builtins.hs @@ -485,19 +485,7 @@ pairToPair :: BI.BuiltinPair a b -> (a, b) pairToPair tup = (BI.fst tup, BI.snd tup) {-# INLINE pairToPair #-} -<<<<<<< HEAD -<<<<<<< HEAD sopListToArray :: (HasToOpaque a arep, MkNil arep) => [a] -> BI.BuiltinArray arep -======= --- | Turn a normal pair into a builtin pair, useful in patterns. -pairFromPair :: (a, b) -> BI.BuiltinPair a b -pairFromPair = BI.BuiltinPair -{-# INLINE pairFromPair #-} - -======= ->>>>>>> c6f4afe5d3 (wip) -sopListToArray :: (HasToOpaque a arep, MkNil arep) => [a] -> BI.BuiltinArray arep ->>>>>>> 14e3427f6c (PlutusTx.Data.List & PlutusTx.BuiltinList - Feature Parity) sopListToArray l = BI.listToArray (toOpaque l) {-# INLINEABLE sopListToArray #-} diff --git a/plutus-tx/src/PlutusTx/List.hs b/plutus-tx/src/PlutusTx/List.hs index 7f59fe60675..c883bde02a8 100644 --- a/plutus-tx/src/PlutusTx/List.hs +++ b/plutus-tx/src/PlutusTx/List.hs @@ -274,18 +274,6 @@ xs0 !! n0 = go n0 xs0 else go (Builtins.subtractInteger n 1) xs {-# INLINABLE (!!) #-} -(!!) :: forall a. [a] -> Integer -> a -_ !! n0 | n0 < 0 = traceError negativeIndexError -xs0 !! n0 = go n0 xs0 - where - go :: Integer -> [a] -> a - go _ [] = traceError indexTooLargeError - go n (x : xs) = - if Builtins.equalsInteger n 0 - then x - else go (Builtins.subtractInteger n 1) xs -{-# INLINEABLE (!!) #-} - {-| Cons each element of the first list to the second one in reverse order (i.e. the last element of the first list is the head of the result). From 25a5c917138c990d26138a0abb2817733eac54e0 Mon Sep 17 00:00:00 2001 From: zeme Date: Tue, 27 May 2025 10:07:47 +0200 Subject: [PATCH 13/30] wip --- .../test/BuiltinList/Budget/Spec.hs | 6 +- ...250527_092743_lorenzo.calegari_list_api.md | 10 ++++ plutus-tx/src/PlutusTx/BuiltinList.hs | 59 ++++++++++--------- 3 files changed, 43 insertions(+), 32 deletions(-) create mode 100644 plutus-tx/changelog.d/20250527_092743_lorenzo.calegari_list_api.md diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index 5e2766140ce..3e2f7f5b830 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -69,14 +69,14 @@ tests = , goldenBundle "elemBy" elemBy (elemBy `unsafeApplyCode` l1) , goldenBundle "nub" nub (nub `unsafeApplyCode` l1) , goldenBundle "nubBy" nubBy (nubBy `unsafeApplyCode` l1) + , goldenBundle "concat" concat (concat `unsafeApplyCode` l4) + , goldenBundle "concatMap" concatMap (concatMap `unsafeApplyCode` l1) + , goldenBundle "zipWith" zipWith (zipWith `unsafeApplyCode` l1) -- TODO The following tests are ignored because they require implementation of -- arbitrarily nested BuiltinList types. -- See `class MkNil` in PlutusTx.Builtins.HasOpaque. - , goldenBundle "concat" concat (concat `unsafeApplyCode` l4) - , goldenBundle "concatMap" concatMap (concatMap `unsafeApplyCode` l1) -- , goldenBundle "unzip" unzip (unzip `unsafeApplyCode` l3) -- , goldenBundle "zip" zip (zip `unsafeApplyCode` l1) - -- , goldenBundle "zipWith" zipWith (zipWith `unsafeApplyCode` l1) -- , goldenBundle "splitAt" splitAt (splitAt `unsafeApplyCode` l1) -- , goldenBundle "partition" partition (partition `unsafeApplyCode` l1) -- , goldenBundle "sort" sort (sort `unsafeApplyCode` l1) diff --git a/plutus-tx/changelog.d/20250527_092743_lorenzo.calegari_list_api.md b/plutus-tx/changelog.d/20250527_092743_lorenzo.calegari_list_api.md new file mode 100644 index 00000000000..59689c596a0 --- /dev/null +++ b/plutus-tx/changelog.d/20250527_092743_lorenzo.calegari_list_api.md @@ -0,0 +1,10 @@ +### Added + +- Added over 30 new functions to `PlutusTx.BuiltinList` + +- Added new function `mapMaybe` to `PlutusTx.List` + +- Added new errors codes: + - `PT23` -> `PlutusTx.BuiltinList.head: empty list` + - `PT24` -> `PlutusTx.BuiltinList.tail: empty list` + - `PT25` -> `PlutusTx.BuiltinList.last: empty list` diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index 937658f3783..817ebe161d0 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -1,4 +1,5 @@ {-# LANGUAGE LambdaCase #-} +{-# OPTIONS_GHC -Wno-unused-top-binds #-} -- | Functions operating on `BuiltinList`. module PlutusTx.BuiltinList ( @@ -36,22 +37,23 @@ module PlutusTx.BuiltinList ( reverse, replicate, findIndex, - unzip, - zip, - zipWith, head, last, tail, take, drop, dropWhile, - splitAt, elemBy, - partition, - sort, - sortBy, nub, - nubBy + nubBy, + zipWith + -- TODO export these when we have fixed the MkNil issue (see HasOpaque.hs) + -- unzip, + -- zip, + -- splitAt, + -- partition, + -- sort, + -- sortBy, ) where import PlutusTx.Builtins qualified as B @@ -282,29 +284,29 @@ reverse xs = revAppend xs empty {-# INLINABLE reverse #-} -- | Plutus Tx version of 'Data.List.zip' for 'BuiltinList'. -zip +_zip :: forall a b. (MkNil a, MkNil b) => BuiltinList a -> BuiltinList b -> BuiltinList (BuiltinPair a b) -zip = zipWith (curry BI.BuiltinPair) -{-# INLINABLE zip #-} +_zip = zipWith (curry BI.BuiltinPair) +{-# INLINABLE _zip #-} -- | Plutus Tx version of 'Data.List.unzip' for 'BuiltinList'. -unzip +_unzip :: forall a b. (MkNil a, MkNil b) => BuiltinList (BuiltinPair a b) -> BuiltinPair (BuiltinList a) (BuiltinList b) -unzip = caseList' emptyPair +_unzip = caseList' emptyPair ( \p l -> do let BI.BuiltinPair (x, y) = p - let BI.BuiltinPair (xs', ys') = unzip l + let BI.BuiltinPair (xs', ys') = _unzip l BI.BuiltinPair (x <| xs', y <| ys') ) where emptyPair :: BuiltinPair (BuiltinList a) (BuiltinList b) emptyPair = BI.BuiltinPair (empty, empty) -{-# INLINABLE unzip #-} +{-# INLINABLE _unzip #-} -- | Plutus Tx version of 'Data.List.head' for 'BuiltinList'. head :: forall a. BuiltinList a -> a @@ -345,19 +347,19 @@ drop n l {-# INLINABLE drop #-} -- | Plutus Tx version of 'Data.List.splitAt' for 'BuiltinList'. -splitAt +_splitAt :: forall a. (MkNil a) => Integer -> BuiltinList a -> BuiltinPair (BuiltinList a) (BuiltinList a) -splitAt n xs +_splitAt n xs | n `B.lessThanEqualsInteger` 0 = BI.BuiltinPair (empty, xs) | B.null xs = BI.BuiltinPair (empty, empty) | otherwise = do let (x, xs') = B.unsafeUncons xs - let BI.BuiltinPair (xs'', xs''') = splitAt (n `B.subtractInteger` 1) xs' + let BI.BuiltinPair (xs'', xs''') = _splitAt (n `B.subtractInteger` 1) xs' BI.BuiltinPair (x <| xs'', xs''') -{-# INLINABLE splitAt #-} +{-# INLINABLE _splitAt #-} -- | Plutus Tx version of 'Data.List.nub' for 'BuiltinList'. nub :: forall a. (Eq a, MkNil a) => BuiltinList a -> BuiltinList a @@ -423,25 +425,25 @@ replicate n0 x = go n0 {-# INLINABLE replicate #-} -- | Plutus Tx version of 'Data.List.partition' for 'BuiltinList'. -partition +_partition :: forall a. (MkNil a) => (a -> Bool) -> BuiltinList a -> BuiltinPair (BuiltinList a) (BuiltinList a) -partition p = BI.BuiltinPair . foldr select (empty, empty) +_partition p = BI.BuiltinPair . foldr select (empty, empty) where select :: a -> (BuiltinList a, BuiltinList a) -> (BuiltinList a, BuiltinList a) select x ~(ts, fs) = if p x then (x <| ts, fs) else (ts, x <| fs) -{-# INLINABLE partition #-} +{-# INLINABLE _partition #-} -- | Plutus Tx version of 'Data.List.sort' for 'BuiltinList'. -sort :: (MkNil a, Ord a) => BuiltinList a -> BuiltinList a -sort = sortBy compare -{-# INLINABLE sort #-} +_sort :: (MkNil a, Ord a) => BuiltinList a -> BuiltinList a +_sort = _sortBy compare +{-# INLINABLE _sort #-} -- | Plutus Tx version of 'Data.List.sortBy' for 'BuiltinList'. -sortBy :: MkNil a => (a -> a -> Ordering) -> BuiltinList a -> BuiltinList a -sortBy cmp = mergeAll . sequences +_sortBy :: MkNil a => (a -> a -> Ordering) -> BuiltinList a -> BuiltinList a +_sortBy cmp = mergeAll . sequences where sequences = caseList'' empty (singleton . singleton) f where @@ -489,5 +491,4 @@ sortBy cmp = mergeAll . sequences caseList'' :: forall a r. r -> (a -> r) -> (a -> a -> BuiltinList a -> r) -> BuiltinList a -> r caseList'' f0 f1 f2 = caseList' f0 ( \x xs -> caseList' (f1 x) ( \y ys -> f2 x y ys ) xs ) - -{-# INLINABLE sortBy #-} +{-# INLINABLE _sortBy #-} From 826e41f2fff82a086018a893d31f037259603a8b Mon Sep 17 00:00:00 2001 From: zeme Date: Tue, 27 May 2025 13:11:39 +0200 Subject: [PATCH 14/30] wip --- plutus-tx/src/PlutusTx/BuiltinList.hs | 3 +-- plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs | 1 + plutus-tx/src/PlutusTx/List.hs | 4 ++-- 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index 817ebe161d0..86bbf08454e 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -1,5 +1,4 @@ {-# LANGUAGE LambdaCase #-} -{-# OPTIONS_GHC -Wno-unused-top-binds #-} -- | Functions operating on `BuiltinList`. module PlutusTx.BuiltinList ( @@ -47,7 +46,7 @@ module PlutusTx.BuiltinList ( nub, nubBy, zipWith - -- TODO export these when we have fixed the MkNil issue (see HasOpaque.hs) + -- TODO uncomment when done https://github.com/IntersectMBO/plutus-private/issues/1604 -- unzip, -- zip, -- splitAt, diff --git a/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs b/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs index 0ac1fe377fb..fc7f8f5bbf6 100644 --- a/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs +++ b/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs @@ -276,6 +276,7 @@ instance MkNil BuiltinBool instance MkNil BuiltinData -- TODO: the following two instances are not implemented in the plugin. -- They require changes to PlutusTx.Compiler.Expr.compileExpr +-- See https://github.com/IntersectMBO/plutus-private/issues/1604 instance (MkNil a) => MkNil (BuiltinList a) instance (MkNil a, MkNil b) => MkNil (BuiltinPair a b) diff --git a/plutus-tx/src/PlutusTx/List.hs b/plutus-tx/src/PlutusTx/List.hs index c883bde02a8..7f49932b544 100644 --- a/plutus-tx/src/PlutusTx/List.hs +++ b/plutus-tx/src/PlutusTx/List.hs @@ -105,8 +105,8 @@ mapMaybe f = go where go :: [a] -> [b] go = \case - [] -> [] - x:xs -> maybe (go xs) (\y -> y:go xs) (f x) + [] -> [] + x : xs -> maybe (go xs) (\y -> y : go xs) (f x) {-# INLINABLE mapMaybe #-} -- | Returns the conjunction of a list of Bools. From a73d18f0842a962753c9a371f1b7ef46e7fcf6b4 Mon Sep 17 00:00:00 2001 From: zeme Date: Tue, 27 May 2025 13:25:50 +0200 Subject: [PATCH 15/30] wip --- .../BuiltinList/Budget/9.6/index.eval.golden | 6 +- .../BuiltinList/Budget/9.6/index.pir.golden | 55 ++++++++----------- .../BuiltinList/Budget/9.6/index.uplc.golden | 31 ++++------- .../test/BuiltinList/Budget/Spec.hs | 9 +++ ...iy.Lazaryev_lookup_builtin_list_cheaper.md | 3 + plutus-tx/src/PlutusTx/BuiltinList.hs | 30 +++++----- 6 files changed, 66 insertions(+), 68 deletions(-) create mode 100644 plutus-tx/changelog.d/20250526_182207_Yuriy.Lazaryev_lookup_builtin_list_cheaper.md diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden index f6a19567956..4c3ae70e13c 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden @@ -1,5 +1,5 @@ -cpu: 8343274 -mem: 33698 -size: 81 +cpu: 1064403 +mem: 4200 +size: 50 (con integer 6) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden index 301600984c1..e6b8fa84d8e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden @@ -5,34 +5,27 @@ let data Unit | Unit_match where Unit : Unit in -letrec - !go : list integer -> integer -> integer - = \(xs : list integer) (i : integer) -> - (let - r = Unit -> Unit -> integer - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - (\(ds : Unit) -> - let - !x : Unit = trace {Unit} "PT22" Unit - in - error {Unit -> integer}) - (\(x : integer) (xs : list integer) (ds : Unit) (ds : Unit) -> - Bool_match - (ifThenElse {Bool} (equalsInteger 0 i) True False) - {all dead. integer} - (/\dead -> x) - (/\dead -> go xs (subtractInteger i 1)) - {all dead. dead}) - xs - Unit - Unit -in -\(xs : list integer) -> go xs 5 \ No newline at end of file +\(v : list integer) -> + let + !l : list integer = dropList {integer} 5 v + in + (let + r = Unit -> Unit -> integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + (\(_ann : Unit) -> + let + !x : Unit = trace {Unit} "PT22" Unit + in + error {Unit -> integer}) + (\(x : integer) (xs : list integer) (ds : Unit) (eta : Unit) -> x) + l + Unit + Unit \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden index cb885ad5218..f3f8a849b92 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden @@ -1,21 +1,14 @@ (program 1.1.0 - ((\go xs -> go xs 5) - ((\s -> s s) - (\s xs i -> - force - (force (force chooseList) - xs - (delay - (\ds -> (\x -> error) (force trace "PT22" (constr 0 [])))) - (delay - ((\x xs ds ds -> - force - (force ifThenElse - (equalsInteger 0 i) - (delay x) - (delay (s s xs (subtractInteger i 1))))) - (force headList xs) - (force tailList xs)))) - (constr 0 []) - (constr 0 []))))) \ No newline at end of file + (\v -> + (\l -> + force + (force (force chooseList) + l + (delay + (\_ann -> (\x -> error) (force trace "PT22" (constr 0 [])))) + (delay + ((\x xs ds eta -> x) (force headList l) (force tailList l)))) + (constr 0 []) + (constr 0 [])) + (force dropList 5 v))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index 3e2f7f5b830..85cd958a6b2 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -83,6 +83,15 @@ tests = -- , goldenBundle "sortBy" sortBy (sortBy `unsafeApplyCode` l1) ] +goldenBundleBuiltinList + :: TestName + -> CompiledCode (BuiltinList Integer -> a) + -> TestNested + goldenBundleBuiltinList label code = + let ints :: [Integer] = [1 .. 10] + applied = unsafeApplyCode code (liftCodeDef (toBuiltin ints)) + in goldenBundle label code applied + map :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) map = $$(compile [||L.map (P.+ 1)||]) diff --git a/plutus-tx/changelog.d/20250526_182207_Yuriy.Lazaryev_lookup_builtin_list_cheaper.md b/plutus-tx/changelog.d/20250526_182207_Yuriy.Lazaryev_lookup_builtin_list_cheaper.md new file mode 100644 index 00000000000..ce12c169983 --- /dev/null +++ b/plutus-tx/changelog.d/20250526_182207_Yuriy.Lazaryev_lookup_builtin_list_cheaper.md @@ -0,0 +1,3 @@ +### Changed + +- `BuiltinList` lookup is made cheaper by using the `DropList` builtin function. diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index 86bbf08454e..0c22abaac6d 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -1,4 +1,6 @@ -{-# LANGUAGE LambdaCase #-} +{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} + +{-# HLINT ignore "Redundant if" #-} -- | Functions operating on `BuiltinList`. module PlutusTx.BuiltinList ( @@ -154,22 +156,20 @@ all p = go go = caseList' True ( \x xs -> if p x then go xs else False ) {-# INLINEABLE all #-} --- | Plutus Tx version of '(GHC.List.!!)' for 'BuiltinList'. --- This function is partial and takes linear time. + +{-| Get the element at a given index. +This function throws an error if the index is negative or larger than the length +of the list. -} infixl 9 !! (!!) :: forall a. BuiltinList a -> Integer -> a -(!!) xs0 i0 - | i0 `B.lessThanInteger` 0 = traceError builtinListNegativeIndexError - | otherwise = go xs0 i0 - where - go :: BuiltinList a -> Integer -> a - go xs i = caseList - ( \_ -> traceError builtinListIndexTooLargeError ) - ( \y ys _ -> - if i `B.equalsInteger` 0 - then y - else go ys (B.subtractInteger i 1) - ) xs () +(!!) xs i + | i `B.lessThanInteger` 0 = traceError builtinListNegativeIndexError + | otherwise = + B.caseList + (\_ann -> traceError builtinListIndexTooLargeError) + (\y _rest _ann -> y) + (BI.drop i xs) + () {-# INLINEABLE (!!) #-} -- TODO add tests and changelog for Data.List From 3e3e2fce1631ff78bf4540f1579d47561c0645f7 Mon Sep 17 00:00:00 2001 From: zeme Date: Tue, 27 May 2025 14:34:37 +0200 Subject: [PATCH 16/30] wip --- .../test/BuiltinList/Budget/Spec.hs | 21 ++++++++----------- 1 file changed, 9 insertions(+), 12 deletions(-) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index ffd49d8f1ea..d59237c113b 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -4,18 +4,15 @@ module BuiltinList.Budget.Spec where -import Prelude (Bool (..), Integer, Maybe (..), pure, undefined, ($), (.)) -import System.FilePath -import Test.Tasty.Extras -import PlutusTx.BuiltinList ((!!)) -import PlutusTx.BuiltinList qualified as List +import PlutusTx.BuiltinList qualified as L import PlutusTx.Code (CompiledCode, unsafeApplyCode) import PlutusTx.Lift (liftCodeDef) +import PlutusTx.Prelude qualified as P import PlutusTx.Test (goldenBundle) import PlutusTx.TH (compile) -import System.FilePath (()) -import Test.Tasty (TestName) -import Test.Tasty.Extras (TestNested, testNested, testNestedGhc) +import Prelude (Bool (..), Integer, Maybe (..), pure, undefined, ($), (.)) +import System.FilePath +import Test.Tasty.Extras tests :: TestNested tests = @@ -230,16 +227,16 @@ nubBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) nubBy = $$(compile [|| \xs -> L.nubBy (P.<=) xs ||]) l1 :: CompiledCode (L.BuiltinList Integer) -l1 = liftCodeDef $ toBuiltin ([1 .. 10] :: [Integer]) +l1 = liftCodeDef $ P.toBuiltin ([1 .. 10] :: [Integer]) l2 :: CompiledCode (L.BuiltinList P.BuiltinBool) -l2 = liftCodeDef $ toBuiltin ([True, False, True, False] :: [Bool]) +l2 = liftCodeDef $ P.toBuiltin ([True, False, True, False] :: [Bool]) l3 :: CompiledCode (L.BuiltinList (P.BuiltinPair Integer Integer)) -l3 = liftCodeDef $ toBuiltin ([ (1, 2), (3, 4), (5, 6) ] :: [(Integer, Integer)]) +l3 = liftCodeDef $ P.toBuiltin ([ (1, 2), (3, 4), (5, 6) ] :: [(Integer, Integer)]) l4 :: CompiledCode (L.BuiltinList (L.BuiltinList Integer)) -l4 = liftCodeDef $ toBuiltin ([[1, 2], [3, 4]] :: [[Integer]]) +l4 = liftCodeDef $ P.toBuiltin ([[1, 2], [3, 4]] :: [[Integer]]) -- TODO The following functions cannot compile because they require implementation of -- arbitrarily nested BuiltinList types. From 4809d1b93d6d1ec9d9520d4d69041daa68fba5a9 Mon Sep 17 00:00:00 2001 From: zeme-wana <15709674+zeme-wana@users.noreply.github.com> Date: Wed, 28 May 2025 12:15:04 +0200 Subject: [PATCH 17/30] Update plutus-tx/src/PlutusTx/BuiltinList.hs Co-authored-by: effectfully --- plutus-tx/src/PlutusTx/BuiltinList.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index d287febda2b..5d2ce1f0fdb 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -409,7 +409,7 @@ dropWhile :: forall a. (MkNil a) => (a -> Bool) -> BuiltinList a -> BuiltinList dropWhile p = go where go :: BuiltinList a -> BuiltinList a - go xs = caseList' empty ( \x xs' -> if p x then go xs' else xs ) xs + go xs = caseList' xs ( \x xs' -> if p x then go xs' else xs ) xs {-# INLINABLE dropWhile #-} -- | Plutus Tx version of 'Data.List.replicate' for 'BuiltinList'. From 3e7502410c571ea8cd7533ee7fd9c3e15391aa14 Mon Sep 17 00:00:00 2001 From: zeme Date: Wed, 28 May 2025 12:55:53 +0200 Subject: [PATCH 18/30] done --- .../test/BuiltinList/Budget/Spec.hs | 63 ++++++++++--------- plutus-tx/src/PlutusTx/BuiltinList.hs | 9 ++- plutus-tx/src/PlutusTx/List.hs | 17 +---- 3 files changed, 39 insertions(+), 50 deletions(-) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index d59237c113b..4106bff5e16 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -4,15 +4,16 @@ module BuiltinList.Budget.Spec where +import PlutusTx.Prelude hiding (mapMaybe) + import PlutusTx.BuiltinList qualified as L import PlutusTx.Code (CompiledCode, unsafeApplyCode) import PlutusTx.Lift (liftCodeDef) -import PlutusTx.Prelude qualified as P import PlutusTx.Test (goldenBundle) import PlutusTx.TH (compile) -import Prelude (Bool (..), Integer, Maybe (..), pure, undefined, ($), (.)) -import System.FilePath -import Test.Tasty.Extras +import Prelude (undefined) +import System.FilePath (()) +import Test.Tasty.Extras (TestNested, testNested, testNestedGhc) tests :: TestNested tests = @@ -83,19 +84,19 @@ tests = ] map :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -map = $$(compile [||L.map (P.+ 1)||]) +map = $$(compile [||L.map (+ 1)||]) elem :: CompiledCode (L.BuiltinList Integer -> (Bool, Bool)) elem = $$(compile [||\xs -> (L.elem 8 xs, L.elem 12 xs)||]) find :: CompiledCode (L.BuiltinList Integer -> (Maybe Integer, Maybe Integer)) -find = $$(compile [||\xs -> (L.find (P.>= 8) xs, L.find (P.>= 12) xs)||]) +find = $$(compile [||\xs -> (L.find (>= 8) xs, L.find (>= 12) xs)||]) any :: CompiledCode (L.BuiltinList Integer -> (Bool, Bool)) -any = $$(compile [|| \xs -> (L.any (P.>= 8) xs, L.any (P.>= 12) xs) ||]) +any = $$(compile [|| \xs -> (L.any (>= 8) xs, L.any (>= 12) xs) ||]) all :: CompiledCode (L.BuiltinList Integer -> (Bool, Bool)) -all = $$(compile [|| \xs -> (L.all (P.>= 8) xs, L.all (P.>= 0) xs) ||]) +all = $$(compile [|| \xs -> (L.all (>= 8) xs, L.all (>= 0) xs) ||]) index :: CompiledCode (L.BuiltinList Integer -> Integer) index = $$(compile [|| \xs -> xs L.!! 5 ||]) @@ -134,31 +135,31 @@ append :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) append = $$(compile [|| \xs -> L.append xs xs ||]) findIndices :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -findIndices = $$(compile [|| \xs -> L.findIndices P.odd xs ||]) +findIndices = $$(compile [|| \xs -> L.findIndices odd xs ||]) filter :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -filter = $$(compile [|| \xs -> L.filter P.even xs ||]) +filter = $$(compile [|| \xs -> L.filter even xs ||]) mapMaybe :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -mapMaybe = $$(compile [|| \xs -> L.mapMaybe (\x -> if P.odd x then Just x else Nothing) xs ||]) +mapMaybe = $$(compile [|| \xs -> L.mapMaybe (\x -> if odd x then Just x else Nothing) xs ||]) length :: CompiledCode (L.BuiltinList Integer -> Integer) length = $$(compile [|| \xs -> L.length xs ||]) -and :: CompiledCode (L.BuiltinList P.BuiltinBool -> Bool) +and :: CompiledCode (L.BuiltinList BuiltinBool -> Bool) and = $$(compile [|| \xs -> L.and xs ||]) -or :: CompiledCode (L.BuiltinList P.BuiltinBool -> Bool) +or :: CompiledCode (L.BuiltinList BuiltinBool -> Bool) or = $$(compile [|| \xs -> L.or xs ||]) notElem :: CompiledCode (L.BuiltinList Integer -> Bool) notElem = $$(compile [|| \xs -> L.notElem 42 xs||]) foldr :: CompiledCode (L.BuiltinList Integer -> Integer) -foldr = $$(compile [|| \xs -> L.foldr (P.+) 0 xs ||]) +foldr = $$(compile [|| \xs -> L.foldr (+) 0 xs ||]) foldl :: CompiledCode (L.BuiltinList Integer -> Integer) -foldl = $$(compile [|| \xs -> L.foldl (P.*) 1 xs ||]) +foldl = $$(compile [|| \xs -> L.foldl (*) 1 xs ||]) listToMaybeJust :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) listToMaybeJust = $$(compile [|| \xs -> L.listToMaybe xs ||]) @@ -182,13 +183,13 @@ replicate :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) replicate = $$(compile [|| \_ -> L.replicate 10 0 ||]) findIndexJust :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) -findIndexJust = $$(compile [|| \xs -> L.findIndex (P.== 4) xs ||]) +findIndexJust = $$(compile [|| \xs -> L.findIndex (== 4) xs ||]) findIndexNothing :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) -findIndexNothing = $$(compile [|| \xs -> L.findIndex (P.== 99) xs ||]) +findIndexNothing = $$(compile [|| \xs -> L.findIndex (== 99) xs ||]) zipWith :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -zipWith = $$(compile [|| \xs -> L.zipWith (P.+) xs xs ||]) +zipWith = $$(compile [|| \xs -> L.zipWith (+) xs xs ||]) headOk :: CompiledCode (L.BuiltinList Integer -> Integer) headOk = $$(compile [|| \xs -> L.head xs ||]) @@ -215,28 +216,28 @@ drop :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) drop = $$(compile [|| \xs -> L.drop 5 xs ||]) dropWhile :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -dropWhile = $$(compile [|| \xs -> L.dropWhile (P.< 5) xs ||]) +dropWhile = $$(compile [|| \xs -> L.dropWhile (< 5) xs ||]) elemBy :: CompiledCode (L.BuiltinList Integer -> Bool) -elemBy = $$(compile [|| \xs -> L.elemBy (P.<=) 0 xs ||]) +elemBy = $$(compile [|| \xs -> L.elemBy (<=) 0 xs ||]) nub :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) nub = $$(compile [|| \xs -> L.nub (L.append xs xs) ||]) nubBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -nubBy = $$(compile [|| \xs -> L.nubBy (P.<=) xs ||]) +nubBy = $$(compile [|| \xs -> L.nubBy (<=) xs ||]) l1 :: CompiledCode (L.BuiltinList Integer) -l1 = liftCodeDef $ P.toBuiltin ([1 .. 10] :: [Integer]) +l1 = liftCodeDef $ toBuiltin ([1 .. 10] :: [Integer]) -l2 :: CompiledCode (L.BuiltinList P.BuiltinBool) -l2 = liftCodeDef $ P.toBuiltin ([True, False, True, False] :: [Bool]) +l2 :: CompiledCode (L.BuiltinList BuiltinBool) +l2 = liftCodeDef $ toBuiltin ([True, False, True, False] :: [Bool]) -l3 :: CompiledCode (L.BuiltinList (P.BuiltinPair Integer Integer)) -l3 = liftCodeDef $ P.toBuiltin ([ (1, 2), (3, 4), (5, 6) ] :: [(Integer, Integer)]) +l3 :: CompiledCode (L.BuiltinList (BuiltinPair Integer Integer)) +l3 = liftCodeDef $ toBuiltin ([ (1, 2), (3, 4), (5, 6) ] :: [(Integer, Integer)]) l4 :: CompiledCode (L.BuiltinList (L.BuiltinList Integer)) -l4 = liftCodeDef $ P.toBuiltin ([[1, 2], [3, 4]] :: [[Integer]]) +l4 = liftCodeDef $ toBuiltin ([[1, 2], [3, 4]] :: [[Integer]]) -- TODO The following functions cannot compile because they require implementation of -- arbitrarily nested BuiltinList types. @@ -250,7 +251,7 @@ concatMap = $$(compile [|| \xss -> L.concatMap (L.replicate 2) xss ||]) splitAt :: CompiledCode ( - L.BuiltinList Integer -> P.BuiltinPair (L.BuiltinList Integer) (L.BuiltinList Integer) + L.BuiltinList Integer -> BuiltinPair (L.BuiltinList Integer) (L.BuiltinList Integer) ) splitAt = undefined -- $$(compile [|| \xs -> L.splitAt 2 xs ||]) @@ -261,11 +262,11 @@ sort :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) sort = undefined -- $$(compile [|| \xs -> L.sort xs ||]) sortBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -sortBy = undefined -- $$(compile [|| \xs -> L.sortBy (P.<=) xs ||]) +sortBy = undefined -- $$(compile [|| \xs -> L.sortBy (<=) xs ||]) -unzip :: CompiledCode (L.BuiltinList (P.BuiltinPair a b) -> L.BuiltinList Integer) +unzip :: CompiledCode (L.BuiltinList (BuiltinPair a b) -> L.BuiltinList Integer) unzip = undefined -- $$(compile [|| \xs -> L.unzip xs ||]) -zip :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList (P.BuiltinPair Integer Integer)) +zip :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList (BuiltinPair Integer Integer)) zip = undefined -- $$(compile [|| \xs -> L.zip xs xs ||]) diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index 5d2ce1f0fdb..7e50d9fc238 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -297,8 +297,11 @@ _unzip -> BuiltinPair (BuiltinList a) (BuiltinList b) _unzip = caseList' emptyPair ( \p l -> do - let BI.BuiltinPair (x, y) = p - let BI.BuiltinPair (xs', ys') = _unzip l + let x = BI.fst p + let y = BI.snd p + let l' = _unzip l + let xs' = BI.fst l' + let ys' = BI.snd l' BI.BuiltinPair (x <| xs', y <| ys') ) where @@ -405,7 +408,7 @@ zipWith f = go {-# INLINABLE zipWith #-} -- | Plutus Tx version of 'Data.List.dropWhile' for 'BuiltinList'. -dropWhile :: forall a. (MkNil a) => (a -> Bool) -> BuiltinList a -> BuiltinList a +dropWhile :: forall a. (a -> Bool) -> BuiltinList a -> BuiltinList a dropWhile p = go where go :: BuiltinList a -> BuiltinList a diff --git a/plutus-tx/src/PlutusTx/List.hs b/plutus-tx/src/PlutusTx/List.hs index 7f49932b544..d034bcf037e 100644 --- a/plutus-tx/src/PlutusTx/List.hs +++ b/plutus-tx/src/PlutusTx/List.hs @@ -8,7 +8,6 @@ module PlutusTx.List ( null, length, map, - mapMaybe, and, or, any, @@ -55,7 +54,7 @@ import PlutusTx.Eq (Eq, (/=), (==)) import PlutusTx.ErrorCodes import PlutusTx.Ord (Ord, Ordering (..), compare, (<), (<=)) import PlutusTx.Trace (traceError) -import Prelude (Maybe (..), maybe, (.)) +import Prelude (Maybe (..), (.)) {- HLINT ignore -} @@ -95,20 +94,6 @@ map f = go x : xs -> f x : go xs {-# INLINEABLE map #-} --- | Plutus Tx version of 'Data.List.mapMaybe'. --- --- >>> mapMaybe (\i -> if odd i then Just i else Nothing) [1, 2, 3, 4] --- [1,3] --- -mapMaybe :: forall a b. (a -> Maybe b) -> [a] -> [b] -mapMaybe f = go - where - go :: [a] -> [b] - go = \case - [] -> [] - x : xs -> maybe (go xs) (\y -> y : go xs) (f x) -{-# INLINABLE mapMaybe #-} - -- | Returns the conjunction of a list of Bools. and :: [Bool] -> Bool and = \case From 72c30ee0687e4333ff59a741a3de3d81ee9e0db7 Mon Sep 17 00:00:00 2001 From: zeme Date: Wed, 28 May 2025 15:28:46 +0200 Subject: [PATCH 19/30] wip --- plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs | 2 +- plutus-ledger-api/src/PlutusLedgerApi/V2/Contexts.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs b/plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs index dc963b958a3..9b1394edd4d 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs @@ -42,7 +42,7 @@ module PlutusLedgerApi.V1.Contexts import PlutusTx import PlutusTx.Foldable qualified as F -import PlutusTx.List hiding (mapMaybe) +import PlutusTx.List import PlutusTx.Prelude import GHC.Generics (Generic) diff --git a/plutus-ledger-api/src/PlutusLedgerApi/V2/Contexts.hs b/plutus-ledger-api/src/PlutusLedgerApi/V2/Contexts.hs index 56730b57baa..e1387212652 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/V2/Contexts.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/V2/Contexts.hs @@ -60,7 +60,7 @@ import PlutusTx.Blueprint.Definition.Derive (definitionRef) import PlutusTx.Blueprint.TH (makeIsDataSchemaIndexed) import PlutusTx.Foldable qualified as F import PlutusTx.Lift (makeLift) -import PlutusTx.List hiding (mapMaybe) +import PlutusTx.List import Prettyprinter (Pretty (..), nest, vsep, (<+>)) -- | An input of a pending transaction. From b686a0540fbadba070f4c540804cb7f5ef7c1a91 Mon Sep 17 00:00:00 2001 From: zeme-wana <15709674+zeme-wana@users.noreply.github.com> Date: Wed, 28 May 2025 16:03:26 +0200 Subject: [PATCH 20/30] Update plutus-tx/src/PlutusTx/BuiltinList.hs Co-authored-by: Yura <1009751+Unisay@users.noreply.github.com> --- plutus-tx/src/PlutusTx/BuiltinList.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index 7e50d9fc238..d17b841fe88 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -214,7 +214,7 @@ infixr 5 ++ (++) l r = foldr (<|) r l {-# INLINABLE (++) #-} --- | Plutus Tx version of '(Data.List.append)' for 'BuiltinList'. +-- | Plutus Tx version of 'Data.List.append' for 'BuiltinList'. append :: forall a. BuiltinList a -> BuiltinList a -> BuiltinList a append = (++) {-# INLINABLE append #-} From eff07e60dc3a8f105e6d3c813e78fefecb15c7fc Mon Sep 17 00:00:00 2001 From: zeme Date: Wed, 28 May 2025 16:55:07 +0200 Subject: [PATCH 21/30] Removed dead code and appiled fourmolu --- .../test/BuiltinList/Budget/Spec.hs | 138 +++--- plutus-tx/src/PlutusTx/BuiltinList.hs | 428 +++++++++--------- plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs | 3 - 3 files changed, 300 insertions(+), 269 deletions(-) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index 4106bff5e16..da93151d3aa 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -17,10 +17,10 @@ import Test.Tasty.Extras (TestNested, testNested, testNestedGhc) tests :: TestNested tests = - testNested ("BuiltinList" "Budget") . pure $ - testNestedGhc - [ - goldenBundle "map" map (map `unsafeApplyCode` l1) + testNested ("BuiltinList" "Budget") + . pure + $ testNestedGhc + [ goldenBundle "map" map (map `unsafeApplyCode` l1) , goldenBundle "elem" elem (elem `unsafeApplyCode` l1) , goldenBundle "find" find (find `unsafeApplyCode` l1) , goldenBundle "any" any (any `unsafeApplyCode` l1) @@ -47,11 +47,15 @@ tests = , goldenBundle "foldr" foldr (foldr `unsafeApplyCode` l1) , goldenBundle "foldl" foldl (foldl `unsafeApplyCode` l1) , goldenBundle "listToMaybeJust" listToMaybeJust (listToMaybeJust `unsafeApplyCode` l1) - , goldenBundle "listToMaybeNothing" - listToMaybeNothing (listToMaybeNothing `unsafeApplyCode` l1) + , goldenBundle + "listToMaybeNothing" + listToMaybeNothing + (listToMaybeNothing `unsafeApplyCode` l1) , goldenBundle "uniqueElementJust" uniqueElementJust (uniqueElementJust `unsafeApplyCode` l1) - , goldenBundle "uniqueElementNothing" - uniqueElementNothing (uniqueElementNothing `unsafeApplyCode` l1) + , goldenBundle + "uniqueElementNothing" + uniqueElementNothing + (uniqueElementNothing `unsafeApplyCode` l1) , goldenBundle "revAppend" revAppend (revAppend `unsafeApplyCode` l1) , goldenBundle "reverse" reverse (reverse `unsafeApplyCode` l1) , goldenBundle "replicate" replicate (replicate `unsafeApplyCode` l1) @@ -93,19 +97,19 @@ find :: CompiledCode (L.BuiltinList Integer -> (Maybe Integer, Maybe Integer)) find = $$(compile [||\xs -> (L.find (>= 8) xs, L.find (>= 12) xs)||]) any :: CompiledCode (L.BuiltinList Integer -> (Bool, Bool)) -any = $$(compile [|| \xs -> (L.any (>= 8) xs, L.any (>= 12) xs) ||]) +any = $$(compile [||\xs -> (L.any (>= 8) xs, L.any (>= 12) xs)||]) all :: CompiledCode (L.BuiltinList Integer -> (Bool, Bool)) -all = $$(compile [|| \xs -> (L.all (>= 8) xs, L.all (>= 0) xs) ||]) +all = $$(compile [||\xs -> (L.all (>= 8) xs, L.all (>= 0) xs)||]) index :: CompiledCode (L.BuiltinList Integer -> Integer) -index = $$(compile [|| \xs -> xs L.!! 5 ||]) +index = $$(compile [||\xs -> xs L.!! 5||]) indexNegative :: CompiledCode (L.BuiltinList Integer -> Integer) -indexNegative = $$(compile [||\xs -> xs L.!! (-1) ||]) +indexNegative = $$(compile [||\xs -> xs L.!! (-1)||]) indexTooLarge :: CompiledCode (L.BuiltinList Integer -> Integer) -indexTooLarge = $$(compile [||\xs -> xs L.!! 10 ||]) +indexTooLarge = $$(compile [||\xs -> xs L.!! 10||]) cons :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) cons = $$(compile [||\xs -> L.cons 0 xs||]) @@ -117,115 +121,115 @@ unconsNothing :: CompiledCode (L.BuiltinList Integer -> Maybe (Integer, L.Builti unconsNothing = $$(compile [||\_ -> L.uncons L.empty||]) empty :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -empty = $$(compile [|| \_ -> L.empty ||]) +empty = $$(compile [||\_ -> L.empty||]) singleton :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -singleton = $$(compile [|| \_ -> L.singleton 42 ||]) +singleton = $$(compile [||\_ -> L.singleton 42||]) null :: CompiledCode (L.BuiltinList Integer -> Bool) -null = $$(compile [|| \xs -> L.null xs ||]) +null = $$(compile [||\xs -> L.null xs||]) (++) :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -(++) = $$(compile [|| \xs -> xs L.++ xs ||]) +(++) = $$(compile [||\xs -> xs L.++ xs||]) (<|) :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -(<|) = $$(compile [|| \xs -> 42 L.<| xs ||]) +(<|) = $$(compile [||\xs -> 42 L.<| xs||]) append :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -append = $$(compile [|| \xs -> L.append xs xs ||]) +append = $$(compile [||\xs -> L.append xs xs||]) findIndices :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -findIndices = $$(compile [|| \xs -> L.findIndices odd xs ||]) +findIndices = $$(compile [||\xs -> L.findIndices odd xs||]) filter :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -filter = $$(compile [|| \xs -> L.filter even xs ||]) +filter = $$(compile [||\xs -> L.filter even xs||]) mapMaybe :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -mapMaybe = $$(compile [|| \xs -> L.mapMaybe (\x -> if odd x then Just x else Nothing) xs ||]) +mapMaybe = $$(compile [||\xs -> L.mapMaybe (\x -> if odd x then Just x else Nothing) xs||]) length :: CompiledCode (L.BuiltinList Integer -> Integer) -length = $$(compile [|| \xs -> L.length xs ||]) +length = $$(compile [||\xs -> L.length xs||]) and :: CompiledCode (L.BuiltinList BuiltinBool -> Bool) -and = $$(compile [|| \xs -> L.and xs ||]) +and = $$(compile [||\xs -> L.and xs||]) or :: CompiledCode (L.BuiltinList BuiltinBool -> Bool) -or = $$(compile [|| \xs -> L.or xs ||]) +or = $$(compile [||\xs -> L.or xs||]) notElem :: CompiledCode (L.BuiltinList Integer -> Bool) -notElem = $$(compile [|| \xs -> L.notElem 42 xs||]) +notElem = $$(compile [||\xs -> L.notElem 42 xs||]) foldr :: CompiledCode (L.BuiltinList Integer -> Integer) -foldr = $$(compile [|| \xs -> L.foldr (+) 0 xs ||]) +foldr = $$(compile [||\xs -> L.foldr (+) 0 xs||]) foldl :: CompiledCode (L.BuiltinList Integer -> Integer) -foldl = $$(compile [|| \xs -> L.foldl (*) 1 xs ||]) +foldl = $$(compile [||\xs -> L.foldl (*) 1 xs||]) listToMaybeJust :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) -listToMaybeJust = $$(compile [|| \xs -> L.listToMaybe xs ||]) +listToMaybeJust = $$(compile [||\xs -> L.listToMaybe xs||]) listToMaybeNothing :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) -listToMaybeNothing = $$(compile [|| \_ -> L.listToMaybe L.empty ||]) +listToMaybeNothing = $$(compile [||\_ -> L.listToMaybe L.empty||]) uniqueElementJust :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) -uniqueElementJust = $$(compile [|| \xs -> L.uniqueElement (L.take 1 xs) ||]) +uniqueElementJust = $$(compile [||\xs -> L.uniqueElement (L.take 1 xs)||]) uniqueElementNothing :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) -uniqueElementNothing = $$(compile [|| \_ -> L.uniqueElement L.empty ||]) +uniqueElementNothing = $$(compile [||\_ -> L.uniqueElement L.empty||]) revAppend :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -revAppend = $$(compile [|| \xs -> L.revAppend xs xs ||]) +revAppend = $$(compile [||\xs -> L.revAppend xs xs||]) reverse :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -reverse = $$(compile [|| \xs -> L.reverse xs ||]) +reverse = $$(compile [||\xs -> L.reverse xs||]) replicate :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -replicate = $$(compile [|| \_ -> L.replicate 10 0 ||]) +replicate = $$(compile [||\_ -> L.replicate 10 0||]) findIndexJust :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) -findIndexJust = $$(compile [|| \xs -> L.findIndex (== 4) xs ||]) +findIndexJust = $$(compile [||\xs -> L.findIndex (== 4) xs||]) findIndexNothing :: CompiledCode (L.BuiltinList Integer -> Maybe Integer) -findIndexNothing = $$(compile [|| \xs -> L.findIndex (== 99) xs ||]) +findIndexNothing = $$(compile [||\xs -> L.findIndex (== 99) xs||]) zipWith :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -zipWith = $$(compile [|| \xs -> L.zipWith (+) xs xs ||]) +zipWith = $$(compile [||\xs -> L.zipWith (+) xs xs||]) headOk :: CompiledCode (L.BuiltinList Integer -> Integer) -headOk = $$(compile [|| \xs -> L.head xs ||]) +headOk = $$(compile [||\xs -> L.head xs||]) headEmpty :: CompiledCode (L.BuiltinList Integer -> Integer) -headEmpty = $$(compile [|| \_ -> L.head L.empty ||]) +headEmpty = $$(compile [||\_ -> L.head L.empty||]) lastOk :: CompiledCode (L.BuiltinList Integer -> Integer) -lastOk = $$(compile [|| \xs -> L.last xs ||]) +lastOk = $$(compile [||\xs -> L.last xs||]) lastEmpty :: CompiledCode (L.BuiltinList Integer -> Integer) -lastEmpty = $$(compile [|| \_ -> L.last L.empty ||]) +lastEmpty = $$(compile [||\_ -> L.last L.empty||]) tailOk :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -tailOk = $$(compile [|| \xs -> L.tail xs ||]) +tailOk = $$(compile [||\xs -> L.tail xs||]) tailEmpty :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -tailEmpty = $$(compile [|| \_ -> L.tail L.empty ||]) +tailEmpty = $$(compile [||\_ -> L.tail L.empty||]) take :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -take = $$(compile [|| \xs -> L.take 5 xs ||]) +take = $$(compile [||\xs -> L.take 5 xs||]) drop :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -drop = $$(compile [|| \xs -> L.drop 5 xs ||]) +drop = $$(compile [||\xs -> L.drop 5 xs||]) dropWhile :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -dropWhile = $$(compile [|| \xs -> L.dropWhile (< 5) xs ||]) +dropWhile = $$(compile [||\xs -> L.dropWhile (< 5) xs||]) elemBy :: CompiledCode (L.BuiltinList Integer -> Bool) -elemBy = $$(compile [|| \xs -> L.elemBy (<=) 0 xs ||]) +elemBy = $$(compile [||\xs -> L.elemBy (<=) 0 xs||]) nub :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -nub = $$(compile [|| \xs -> L.nub (L.append xs xs) ||]) +nub = $$(compile [||\xs -> L.nub (L.append xs xs)||]) nubBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -nubBy = $$(compile [|| \xs -> L.nubBy (<=) xs ||]) +nubBy = $$(compile [||\xs -> L.nubBy (<=) xs||]) l1 :: CompiledCode (L.BuiltinList Integer) l1 = liftCodeDef $ toBuiltin ([1 .. 10] :: [Integer]) @@ -234,7 +238,7 @@ l2 :: CompiledCode (L.BuiltinList BuiltinBool) l2 = liftCodeDef $ toBuiltin ([True, False, True, False] :: [Bool]) l3 :: CompiledCode (L.BuiltinList (BuiltinPair Integer Integer)) -l3 = liftCodeDef $ toBuiltin ([ (1, 2), (3, 4), (5, 6) ] :: [(Integer, Integer)]) +l3 = liftCodeDef $ toBuiltin ([(1, 2), (3, 4), (5, 6)] :: [(Integer, Integer)]) l4 :: CompiledCode (L.BuiltinList (L.BuiltinList Integer)) l4 = liftCodeDef $ toBuiltin ([[1, 2], [3, 4]] :: [[Integer]]) @@ -244,29 +248,39 @@ l4 = liftCodeDef $ toBuiltin ([[1, 2], [3, 4]] :: [[Integer]]) -- See `class MkNil` in PlutusTx.Builtins.HasOpaque. concat :: CompiledCode (L.BuiltinList (L.BuiltinList Integer) -> L.BuiltinList Integer) -concat = $$(compile [|| \xss -> L.concat xss ||]) +concat = $$(compile [||\xss -> L.concat xss||]) concatMap :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -concatMap = $$(compile [|| \xss -> L.concatMap (L.replicate 2) xss ||]) +concatMap = $$(compile [||\xss -> L.concatMap (L.replicate 2) xss||]) splitAt - :: CompiledCode ( - L.BuiltinList Integer -> BuiltinPair (L.BuiltinList Integer) (L.BuiltinList Integer) - ) -splitAt = undefined -- $$(compile [|| \xs -> L.splitAt 2 xs ||]) + :: CompiledCode + (L.BuiltinList Integer -> BuiltinPair (L.BuiltinList Integer) (L.BuiltinList Integer)) +splitAt = undefined + +-- \$$(compile [|| \xs -> L.splitAt 2 xs ||]) partition :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -partition = undefined -- $$(compile [|| L.partition ||]) +partition = undefined + +-- \$$(compile [|| L.partition ||]) sort :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -sort = undefined -- $$(compile [|| \xs -> L.sort xs ||]) +sort = undefined + +-- \$$(compile [|| \xs -> L.sort xs ||]) sortBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -sortBy = undefined -- $$(compile [|| \xs -> L.sortBy (<=) xs ||]) +sortBy = undefined + +-- \$$(compile [|| \xs -> L.sortBy (<=) xs ||]) unzip :: CompiledCode (L.BuiltinList (BuiltinPair a b) -> L.BuiltinList Integer) -unzip = undefined -- $$(compile [|| \xs -> L.unzip xs ||]) +unzip = undefined + +-- \$$(compile [|| \xs -> L.unzip xs ||]) zip :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList (BuiltinPair Integer Integer)) -zip = undefined -- $$(compile [|| \xs -> L.zip xs xs ||]) +zip = undefined +-- \$$(compile [|| \xs -> L.zip xs xs ||]) diff --git a/plutus-tx/src/PlutusTx/BuiltinList.hs b/plutus-tx/src/PlutusTx/BuiltinList.hs index d17b841fe88..2c21ea2d7a9 100644 --- a/plutus-tx/src/PlutusTx/BuiltinList.hs +++ b/plutus-tx/src/PlutusTx/BuiltinList.hs @@ -47,14 +47,7 @@ module PlutusTx.BuiltinList ( elemBy, nub, nubBy, - zipWith - -- TODO uncomment when done https://github.com/IntersectMBO/plutus-private/issues/1604 - -- unzip, - -- zip, - -- splitAt, - -- partition, - -- sort, - -- sortBy, + zipWith, ) where import PlutusTx.Builtins qualified as B @@ -72,6 +65,7 @@ cons = BI.mkCons -- | Infix version of 'cons'. infixr 5 <| + (<|) :: forall a. a -> BuiltinList a -> BuiltinList a (<|) = cons {-# INLINEABLE (<|) #-} @@ -98,26 +92,28 @@ singleton x = x <| empty caseList' :: forall a r. r -> (a -> BuiltinList a -> r) -> BuiltinList a -> r caseList' = B.caseList' -{-# INLINABLE caseList' #-} +{-# INLINEABLE caseList' #-} caseList :: forall a r. (() -> r) -> (a -> BuiltinList a -> r) -> BuiltinList a -> r caseList = B.caseList -{-# INLINABLE caseList #-} +{-# INLINEABLE caseList #-} -- | Plutus Tx version of 'Data.List.map' for 'BuiltinList'. map :: forall a b. (MkNil b) => (a -> b) -> BuiltinList a -> BuiltinList b map f = go - where - go :: BuiltinList a -> BuiltinList b - go = caseList' empty ( \x xs -> f x <| go xs ) + where + go :: BuiltinList a -> BuiltinList b + go = caseList' empty (\x xs -> f x <| go xs) {-# INLINEABLE map #-} -- | Plutus Tx version of 'Data.List.mapMaybe' for 'BuiltinList'. mapMaybe :: forall a b. (MkNil b) => (a -> Maybe b) -> BuiltinList a -> BuiltinList b mapMaybe f = go - where - go :: BuiltinList a -> BuiltinList b - go = caseList' empty + where + go :: BuiltinList a -> BuiltinList b + go = + caseList' + empty ( \x xs -> case f x of Nothing -> go xs Just y -> y <| go xs @@ -127,56 +123,56 @@ mapMaybe f = go -- | Does the element occur in the list? elem :: forall a. (Eq a) => a -> BuiltinList a -> Bool elem a = go - where - go :: BuiltinList a -> Bool - go = caseList' False ( \x xs -> if a == x then True else go xs ) + where + go :: BuiltinList a -> Bool + go = caseList' False (\x xs -> if a == x then True else go xs) {-# INLINEABLE elem #-} -- | Returns the leftmost element matching the predicate, or `Nothing` if there's no such element. find :: forall a. (a -> Bool) -> BuiltinList a -> Maybe a find p = go - where - go :: BuiltinList a -> Maybe a - go = caseList' Nothing ( \x xs -> if p x then Just x else go xs ) + where + go :: BuiltinList a -> Maybe a + go = caseList' Nothing (\x xs -> if p x then Just x else go xs) {-# INLINEABLE find #-} -- | Determines whether any element of the structure satisfies the predicate. any :: forall a. (a -> Bool) -> BuiltinList a -> Bool any p = go - where - go :: BuiltinList a -> Bool - go = caseList' False ( \x xs -> if p x then True else go xs ) + where + go :: BuiltinList a -> Bool + go = caseList' False (\x xs -> if p x then True else go xs) {-# INLINEABLE any #-} -- | Determines whether all elements of the list satisfy the predicate. all :: forall a. (a -> Bool) -> BuiltinList a -> Bool all p = go - where - go :: BuiltinList a -> Bool - go = caseList' True ( \x xs -> if p x then go xs else False ) + where + go :: BuiltinList a -> Bool + go = caseList' True (\x xs -> if p x then go xs else False) {-# INLINEABLE all #-} {-| Get the element at a given index. This function throws an error if the index is negative or larger than the length -of the list. -} +of the list. +-} infixl 9 !! + (!!) :: forall a. BuiltinList a -> Integer -> a (!!) xs i - | i `B.lessThanInteger` 0 = traceError builtinListNegativeIndexError - | otherwise = - B.caseList - (\_ann -> traceError builtinListIndexTooLargeError) - (\y _rest _ann -> y) - (BI.drop i xs) - () + | i `B.lessThanInteger` 0 = traceError builtinListNegativeIndexError + | otherwise = + B.caseList + (\_ann -> traceError builtinListIndexTooLargeError) + (\y _rest _ann -> y) + (BI.drop i xs) + () {-# INLINEABLE (!!) #-} --- TODO add tests and changelog for Data.List - -- | Plutus Tx version of 'Data.List.length' for 'BuiltinList'. length :: forall a. BuiltinList a -> Integer -length = foldr ( \_ -> B.addInteger 1 ) 0 -{-# INLINABLE length #-} +length = foldr (\_ -> B.addInteger 1) 0 +{-# INLINEABLE length #-} -- | Returns the conjunction of a list of Bools. and :: BuiltinList BuiltinBool -> Bool @@ -185,171 +181,187 @@ and = all (\x -> BI.ifThenElse x True False) -- | Returns the disjunction of a list of Bools. or :: BuiltinList BuiltinBool -> Bool or = any (\x -> BI.ifThenElse x True False) -{-# INLINABLE or #-} +{-# INLINEABLE or #-} -- | The negation of `elem`. notElem :: forall a. (Eq a) => a -> BuiltinList a -> Bool notElem a = not . elem a -{-# INLINABLE notElem #-} +{-# INLINEABLE notElem #-} -- | Plutus Tx version of 'Data.List.foldr' for 'BuiltinList'. foldr :: forall a b. (a -> b -> b) -> b -> BuiltinList a -> b foldr f acc = go - where - go :: BuiltinList a -> b - go = caseList' acc ( \x xs -> f x (go xs) ) -{-# INLINABLE foldr #-} + where + go :: BuiltinList a -> b + go = caseList' acc (\x xs -> f x (go xs)) +{-# INLINEABLE foldr #-} -- | Plutus Tx velsion of 'Data.List.foldl' for 'BuiltinList'. foldl :: forall a b. (b -> a -> b) -> b -> BuiltinList a -> b foldl f = go - where - go :: b -> BuiltinList a -> b - go acc = caseList' acc ( \x xs -> go (f acc x) xs ) -{-# INLINABLE foldl #-} + where + go :: b -> BuiltinList a -> b + go acc = caseList' acc (\x xs -> go (f acc x) xs) +{-# INLINEABLE foldl #-} -- | Plutus Tx version of '(Data.List.++)' for 'BuiltinList'. infixr 5 ++ + (++) :: forall a. BuiltinList a -> BuiltinList a -> BuiltinList a (++) l r = foldr (<|) r l -{-# INLINABLE (++) #-} +{-# INLINEABLE (++) #-} -- | Plutus Tx version of 'Data.List.append' for 'BuiltinList'. append :: forall a. BuiltinList a -> BuiltinList a -> BuiltinList a append = (++) -{-# INLINABLE append #-} +{-# INLINEABLE append #-} -- | Plutus Tx version of 'Data.List.concat' for 'BuiltinList'. concat :: forall a. (MkNil a) => BuiltinList (BuiltinList a) -> BuiltinList a concat = foldr (++) empty -{-# INLINABLE concat #-} +{-# INLINEABLE concat #-} -- | Plutus Tx version of 'Data.List.concatMap' for 'BuiltinList'. concatMap :: forall a b. (MkNil b) => (a -> BuiltinList b) -> BuiltinList a -> BuiltinList b -concatMap f = foldr ( \x ys -> f x ++ ys ) empty -{-# INLINABLE concatMap #-} +concatMap f = foldr (\x ys -> f x ++ ys) empty +{-# INLINEABLE concatMap #-} -- | Plutus Tx version of 'Data.List.filter' for 'BuiltinList'. filter :: forall a. (MkNil a) => (a -> Bool) -> BuiltinList a -> BuiltinList a -filter p = foldr ( \x xs -> if p x then x <| xs else xs ) empty -{-# INLINABLE filter #-} +filter p = foldr (\x xs -> if p x then x <| xs else xs) empty +{-# INLINEABLE filter #-} -- | Plutus Tx version of 'Data.List.listToMaybe' for 'BuiltinList'. listToMaybe :: forall a. BuiltinList a -> Maybe a -listToMaybe = caseList' Nothing ( \x _ -> Just x ) -{-# INLINABLE listToMaybe #-} +listToMaybe = caseList' Nothing (\x _ -> Just x) +{-# INLINEABLE listToMaybe #-} -- | Return the element in the list, if there is precisely one. uniqueElement :: forall a. BuiltinList a -> Maybe a -uniqueElement = caseList' Nothing - ( \x -> caseList' (Just x) ( \_ _ -> Nothing ) - ) -{-# INLINABLE uniqueElement #-} +uniqueElement = + caseList' + Nothing + (\x -> caseList' (Just x) (\_ _ -> Nothing)) +{-# INLINEABLE uniqueElement #-} -- | Plutus Tx version of 'Data.List.findIndices' for 'BuiltinList'. findIndices :: forall a. (a -> Bool) -> BuiltinList a -> BuiltinList Integer findIndices p = go 0 - where - go :: Integer -> BuiltinList a -> BuiltinList Integer - go i = caseList' empty + where + go :: Integer -> BuiltinList a -> BuiltinList Integer + go i = + caseList' + empty ( \x xs -> let indices = go (B.addInteger i 1) xs - in if p x then i <| indices else indices + in if p x then i <| indices else indices ) -{-# INLINABLE findIndices #-} +{-# INLINEABLE findIndices #-} -- | Plutus Tx version of 'Data.List.findIndex'. findIndex :: forall a. (a -> Bool) -> BuiltinList a -> Maybe Integer findIndex f = go 0 - where - go :: Integer -> BuiltinList a -> Maybe Integer - go i = caseList' Nothing - ( \x xs -> if f x then Just i else go (B.addInteger i 1) xs - ) -{-# INLINABLE findIndex #-} - --- | Cons each element of the first list to the second one in reverse order --- (i.e. the last element of the first list is the head of the result). --- --- > revAppend xs ys === reverse xs ++ ys + where + go :: Integer -> BuiltinList a -> Maybe Integer + go i = + caseList' + Nothing + (\x xs -> if f x then Just i else go (B.addInteger i 1) xs) +{-# INLINEABLE findIndex #-} + +{-| Cons each element of the first list to the second one in reverse order +(i.e. the last element of the first list is the head of the result). + +> revAppend xs ys === reverse xs ++ ys +-} revAppend :: forall a. BuiltinList a -> BuiltinList a -> BuiltinList a -revAppend l r = caseList' r ( \x xs -> revAppend xs (x <| r) ) l -{-# INLINABLE revAppend #-} +revAppend l r = caseList' r (\x xs -> revAppend xs (x <| r)) l +{-# INLINEABLE revAppend #-} -- | Plutus Tx version of 'Data.List.reverse' for 'BuiltinList'. reverse :: forall a. (MkNil a) => BuiltinList a -> BuiltinList a reverse xs = revAppend xs empty -{-# INLINABLE reverse #-} +{-# INLINEABLE reverse #-} -- | Plutus Tx version of 'Data.List.zip' for 'BuiltinList'. _zip - :: forall a b. (MkNil a, MkNil b) + :: forall a b + . (MkNil a, MkNil b) => BuiltinList a -> BuiltinList b -> BuiltinList (BuiltinPair a b) _zip = zipWith (curry BI.BuiltinPair) -{-# INLINABLE _zip #-} +{-# INLINEABLE _zip #-} -- | Plutus Tx version of 'Data.List.unzip' for 'BuiltinList'. _unzip - :: forall a b. (MkNil a, MkNil b) + :: forall a b + . (MkNil a, MkNil b) => BuiltinList (BuiltinPair a b) -> BuiltinPair (BuiltinList a) (BuiltinList b) -_unzip = caseList' emptyPair - ( \p l -> do - let x = BI.fst p - let y = BI.snd p - let l' = _unzip l - let xs' = BI.fst l' - let ys' = BI.snd l' - BI.BuiltinPair (x <| xs', y <| ys') - ) - where - emptyPair :: BuiltinPair (BuiltinList a) (BuiltinList b) - emptyPair = BI.BuiltinPair (empty, empty) -{-# INLINABLE _unzip #-} +_unzip = + caseList' + emptyPair + ( \p l -> do + let x = BI.fst p + let y = BI.snd p + let l' = _unzip l + let xs' = BI.fst l' + let ys' = BI.snd l' + BI.BuiltinPair (x <| xs', y <| ys') + ) + where + emptyPair :: BuiltinPair (BuiltinList a) (BuiltinList b) + emptyPair = BI.BuiltinPair (empty, empty) +{-# INLINEABLE _unzip #-} -- | Plutus Tx version of 'Data.List.head' for 'BuiltinList'. head :: forall a. BuiltinList a -> a -head = caseList - ( \_ -> traceError headEmptyBuiltinListError ) - ( \x _ -> x ) -{-# INLINABLE head #-} +head = + caseList + (\_ -> traceError headEmptyBuiltinListError) + (\x _ -> x) +{-# INLINEABLE head #-} -- | Plutus Tx version of 'Data.List.last' for 'BuiltinList'. last :: forall a. BuiltinList a -> a -last = caseList - ( \_ -> traceError lastEmptyBuiltinListError ) - ( \x xs -> caseList' x ( \_ _ -> last xs ) xs - ) -{-# INLINABLE last #-} +last = + caseList + (\_ -> traceError lastEmptyBuiltinListError) + (\x xs -> caseList' x (\_ _ -> last xs) xs) +{-# INLINEABLE last #-} -- | Plutus Tx version of 'Data.List.tail' for 'BuiltinList'. tail :: forall a. BuiltinList a -> BuiltinList a -tail = caseList ( \_ -> traceError lastEmptyBuiltinListError ) ( \_ xs -> xs ) -{-# INLINABLE tail #-} +tail = caseList (\_ -> traceError lastEmptyBuiltinListError) (\_ xs -> xs) +{-# INLINEABLE tail #-} -- | Plutus Tx version of 'Data.List.take' for 'BuiltinList'. take :: forall a. (MkNil a) => Integer -> BuiltinList a -> BuiltinList a take n l | n `B.lessThanEqualsInteger` 0 = empty - | otherwise = caseList' empty - ( \x xs -> x <| take (B.subtractInteger n 1) xs - ) l -{-# INLINABLE take #-} + | otherwise = + caseList' + empty + (\x xs -> x <| take (B.subtractInteger n 1) xs) + l +{-# INLINEABLE take #-} -- | Plutus Tx version of 'Data.List.drop' for 'BuiltinList'. drop :: forall a. (MkNil a) => Integer -> BuiltinList a -> BuiltinList a drop n l | n `B.lessThanEqualsInteger` 0 = l - | otherwise = caseList' empty - ( \_ xs -> drop (B.subtractInteger n 1) xs - ) l -{-# INLINABLE drop #-} + | otherwise = + caseList' + empty + (\_ xs -> drop (B.subtractInteger n 1) xs) + l +{-# INLINEABLE drop #-} -- | Plutus Tx version of 'Data.List.splitAt' for 'BuiltinList'. _splitAt - :: forall a. (MkNil a) + :: forall a + . (MkNil a) => Integer -> BuiltinList a -> BuiltinPair (BuiltinList a) (BuiltinList a) @@ -360,137 +372,145 @@ _splitAt n xs let (x, xs') = B.unsafeUncons xs let BI.BuiltinPair (xs'', xs''') = _splitAt (n `B.subtractInteger` 1) xs' BI.BuiltinPair (x <| xs'', xs''') -{-# INLINABLE _splitAt #-} +{-# INLINEABLE _splitAt #-} -- | Plutus Tx version of 'Data.List.nub' for 'BuiltinList'. nub :: forall a. (Eq a, MkNil a) => BuiltinList a -> BuiltinList a nub = nubBy (==) -{-# INLINABLE nub #-} +{-# INLINEABLE nub #-} -- | Plutus Tx version of 'Data.List.elemBy' for 'BuiltinList'. elemBy :: forall a. (a -> a -> Bool) -> a -> BuiltinList a -> Bool elemBy eq y = go - where - go :: BuiltinList a -> Bool - go = caseList' False ( \x xs -> if eq x y then True else go xs ) -{-# INLINABLE elemBy #-} + where + go :: BuiltinList a -> Bool + go = caseList' False (\x xs -> if eq x y then True else go xs) +{-# INLINEABLE elemBy #-} -- | Plutus Tx version of 'Data.List.nubBy' for 'BuiltinList'. nubBy :: forall a. (MkNil a) => (a -> a -> Bool) -> BuiltinList a -> BuiltinList a nubBy eq = flip go empty - where - go :: BuiltinList a -> BuiltinList a -> BuiltinList a - go l xs = caseList' empty + where + go :: BuiltinList a -> BuiltinList a -> BuiltinList a + go l xs = + caseList' + empty ( \y ys -> if elemBy eq y xs - then go ys xs - else y <| go ys (y <| xs) - ) l -{-# INLINABLE nubBy #-} + then go ys xs + else y <| go ys (y <| xs) + ) + l +{-# INLINEABLE nubBy #-} -- | Plutus Tx version of 'Data.List.zipWith' for 'BuiltinList'. zipWith - :: forall a b c. (MkNil c) + :: forall a b c + . (MkNil c) => (a -> b -> c) -> BuiltinList a -> BuiltinList b -> BuiltinList c zipWith f = go - where - go :: BuiltinList a -> BuiltinList b -> BuiltinList c - go xs ys = - caseList' empty - ( \x xs' -> - caseList' empty - ( \y ys' -> f x y <| go xs' ys' - ) ys - ) xs -{-# INLINABLE zipWith #-} + where + go :: BuiltinList a -> BuiltinList b -> BuiltinList c + go xs ys = + caseList' + empty + ( \x xs' -> + caseList' + empty + (\y ys' -> f x y <| go xs' ys') + ys + ) + xs +{-# INLINEABLE zipWith #-} -- | Plutus Tx version of 'Data.List.dropWhile' for 'BuiltinList'. dropWhile :: forall a. (a -> Bool) -> BuiltinList a -> BuiltinList a dropWhile p = go - where - go :: BuiltinList a -> BuiltinList a - go xs = caseList' xs ( \x xs' -> if p x then go xs' else xs ) xs -{-# INLINABLE dropWhile #-} + where + go :: BuiltinList a -> BuiltinList a + go xs = caseList' xs (\x xs' -> if p x then go xs' else xs) xs +{-# INLINEABLE dropWhile #-} -- | Plutus Tx version of 'Data.List.replicate' for 'BuiltinList'. replicate :: forall a. (MkNil a) => Integer -> a -> BuiltinList a replicate n0 x = go n0 - where - go :: Integer -> BuiltinList a - go n - | n `B.lessThanEqualsInteger` 0 = empty - | otherwise = x <| go (B.subtractInteger n 1) -{-# INLINABLE replicate #-} + where + go :: Integer -> BuiltinList a + go n + | n `B.lessThanEqualsInteger` 0 = empty + | otherwise = x <| go (B.subtractInteger n 1) +{-# INLINEABLE replicate #-} -- | Plutus Tx version of 'Data.List.partition' for 'BuiltinList'. _partition - :: forall a. (MkNil a) + :: forall a + . (MkNil a) => (a -> Bool) -> BuiltinList a -> BuiltinPair (BuiltinList a) (BuiltinList a) _partition p = BI.BuiltinPair . foldr select (empty, empty) - where - select :: a -> (BuiltinList a, BuiltinList a) -> (BuiltinList a, BuiltinList a) - select x ~(ts, fs) = if p x then (x <| ts, fs) else (ts, x <| fs) -{-# INLINABLE _partition #-} + where + select :: a -> (BuiltinList a, BuiltinList a) -> (BuiltinList a, BuiltinList a) + select x ~(ts, fs) = if p x then (x <| ts, fs) else (ts, x <| fs) +{-# INLINEABLE _partition #-} -- | Plutus Tx version of 'Data.List.sort' for 'BuiltinList'. _sort :: (MkNil a, Ord a) => BuiltinList a -> BuiltinList a _sort = _sortBy compare -{-# INLINABLE _sort #-} +{-# INLINEABLE _sort #-} -- | Plutus Tx version of 'Data.List.sortBy' for 'BuiltinList'. -_sortBy :: MkNil a => (a -> a -> Ordering) -> BuiltinList a -> BuiltinList a +_sortBy :: (MkNil a) => (a -> a -> Ordering) -> BuiltinList a -> BuiltinList a _sortBy cmp = mergeAll . sequences - where - sequences = caseList'' empty (singleton . singleton) f - where - f a b xs - | a `cmp` b == GT = descending b (singleton a) xs - | otherwise = ascending b (cons a) xs - - descending a as l = caseList' d f l - where - d = (a <| as) <| sequences l - f b bs - | a `cmp` b == GT = descending b (a <| as) bs - | otherwise = d - - ascending a as l = caseList' d f l - where - d = as (singleton a) <| sequences l - f b bs - | a `cmp` b /= GT = ascending b (as . cons a) bs - | otherwise = d - - mergeAll l = - case uniqueElement l of - Nothing -> - mergeAll (mergePairs l) - Just x -> - x - - mergePairs = caseList'' empty singleton f - where - f a b xs = merge a b <| mergePairs xs - - merge as bs - | null as = bs - | null bs = as - | otherwise = do - let a = head as - let b = head bs - let as' = tail as - let bs' = tail bs - if a `cmp` b == GT then + where + sequences = caseList'' empty (singleton . singleton) f + where + f a b xs + | a `cmp` b == GT = descending b (singleton a) xs + | otherwise = ascending b (cons a) xs + + descending a as l = caseList' d f l + where + d = (a <| as) <| sequences l + f b bs + | a `cmp` b == GT = descending b (a <| as) bs + | otherwise = d + + ascending a as l = caseList' d f l + where + d = as (singleton a) <| sequences l + f b bs + | a `cmp` b /= GT = ascending b (as . cons a) bs + | otherwise = d + + mergeAll l = + case uniqueElement l of + Nothing -> + mergeAll (mergePairs l) + Just x -> + x + + mergePairs = caseList'' empty singleton f + where + f a b xs = merge a b <| mergePairs xs + + merge as bs + | null as = bs + | null bs = as + | otherwise = do + let a = head as + let b = head bs + let as' = tail as + let bs' = tail bs + if a `cmp` b == GT + then b <| merge as bs' else a <| merge as' bs - caseList'' :: forall a r. r -> (a -> r) -> (a -> a -> BuiltinList a -> r) -> BuiltinList a -> r - caseList'' f0 f1 f2 = caseList' f0 ( \x xs -> caseList' (f1 x) ( \y ys -> f2 x y ys ) xs ) -{-# INLINABLE _sortBy #-} - + caseList'' :: forall a r. r -> (a -> r) -> (a -> a -> BuiltinList a -> r) -> BuiltinList a -> r + caseList'' f0 f1 f2 = caseList' f0 (\x xs -> caseList' (f1 x) (\y ys -> f2 x y ys) xs) +{-# INLINEABLE _sortBy #-} diff --git a/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs b/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs index fc7f8f5bbf6..73249224495 100644 --- a/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs +++ b/plutus-tx/src/PlutusTx/Builtins/HasOpaque.hs @@ -274,9 +274,6 @@ class MkNil arep where instance MkNil BuiltinInteger instance MkNil BuiltinBool instance MkNil BuiltinData --- TODO: the following two instances are not implemented in the plugin. --- They require changes to PlutusTx.Compiler.Expr.compileExpr --- See https://github.com/IntersectMBO/plutus-private/issues/1604 instance (MkNil a) => MkNil (BuiltinList a) instance (MkNil a, MkNil b) => MkNil (BuiltinPair a b) From 090d021538a3c5568a12c7ffeb8d0f0bacc8293f Mon Sep 17 00:00:00 2001 From: zeme Date: Wed, 28 May 2025 17:05:21 +0200 Subject: [PATCH 22/30] done --- .../test/BuiltinList/Budget/Spec.hs | 37 +++---------------- 1 file changed, 6 insertions(+), 31 deletions(-) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index da93151d3aa..09248316cbf 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -76,15 +76,6 @@ tests = , goldenBundle "concat" concat (concat `unsafeApplyCode` l4) , goldenBundle "concatMap" concatMap (concatMap `unsafeApplyCode` l1) , goldenBundle "zipWith" zipWith (zipWith `unsafeApplyCode` l1) - -- TODO The following tests are ignored because they require implementation of - -- arbitrarily nested BuiltinList types. - -- See `class MkNil` in PlutusTx.Builtins.HasOpaque. - -- , goldenBundle "unzip" unzip (unzip `unsafeApplyCode` l3) - -- , goldenBundle "zip" zip (zip `unsafeApplyCode` l1) - -- , goldenBundle "splitAt" splitAt (splitAt `unsafeApplyCode` l1) - -- , goldenBundle "partition" partition (partition `unsafeApplyCode` l1) - -- , goldenBundle "sort" sort (sort `unsafeApplyCode` l1) - -- , goldenBundle "sortBy" sortBy (sortBy `unsafeApplyCode` l1) ] map :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) @@ -243,10 +234,6 @@ l3 = liftCodeDef $ toBuiltin ([(1, 2), (3, 4), (5, 6)] :: [(Integer, Integer)]) l4 :: CompiledCode (L.BuiltinList (L.BuiltinList Integer)) l4 = liftCodeDef $ toBuiltin ([[1, 2], [3, 4]] :: [[Integer]]) --- TODO The following functions cannot compile because they require implementation of --- arbitrarily nested BuiltinList types. --- See `class MkNil` in PlutusTx.Builtins.HasOpaque. - concat :: CompiledCode (L.BuiltinList (L.BuiltinList Integer) -> L.BuiltinList Integer) concat = $$(compile [||\xss -> L.concat xss||]) @@ -256,31 +243,19 @@ concatMap = $$(compile [||\xss -> L.concatMap (L.replicate 2) xss||]) splitAt :: CompiledCode (L.BuiltinList Integer -> BuiltinPair (L.BuiltinList Integer) (L.BuiltinList Integer)) -splitAt = undefined - --- \$$(compile [|| \xs -> L.splitAt 2 xs ||]) +splitAt = undefined -- \$$(compile [|| \xs -> L.splitAt 2 xs ||]) partition :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -partition = undefined - --- \$$(compile [|| L.partition ||]) +partition = undefined -- \$$(compile [|| L.partition ||]) sort :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -sort = undefined - --- \$$(compile [|| \xs -> L.sort xs ||]) +sort = undefined -- \$$(compile [|| \xs -> L.sort xs ||]) sortBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -sortBy = undefined - --- \$$(compile [|| \xs -> L.sortBy (<=) xs ||]) +sortBy = undefined -- \$$(compile [|| \xs -> L.sortBy (<=) xs ||]) unzip :: CompiledCode (L.BuiltinList (BuiltinPair a b) -> L.BuiltinList Integer) -unzip = undefined - --- \$$(compile [|| \xs -> L.unzip xs ||]) +unzip = undefined -- \$$(compile [|| \xs -> L.unzip xs ||]) zip :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList (BuiltinPair Integer Integer)) -zip = undefined - --- \$$(compile [|| \xs -> L.zip xs xs ||]) +zip = undefined -- \$$(compile [|| \xs -> L.zip xs xs ||]) From 037c27b541f4ffc815a15329a0ae255a82889b1f Mon Sep 17 00:00:00 2001 From: zeme Date: Wed, 28 May 2025 18:40:09 +0200 Subject: [PATCH 23/30] wip --- .../Budget/9.6/dropWhile.pir.golden | 2 +- .../Budget/9.6/dropWhile.uplc.golden | 2 +- .../BuiltinList/Budget/9.6/index.pir.golden | 6 +- .../BuiltinList/Budget/9.6/index.uplc.golden | 6 +- .../Budget/9.6/indexNegative.pir.golden | 35 ++---------- .../Budget/9.6/indexNegative.uplc.golden | 23 +------- .../Budget/9.6/indexTooLarge.pir.golden | 55 ++++++++----------- .../Budget/9.6/indexTooLarge.uplc.golden | 31 ++++------- .../Budget/9.6/zipWith.eval.golden | 5 ++ .../BuiltinList/Budget/9.6/zipWith.pir.golden | 30 ++++++++++ .../Budget/9.6/zipWith.uplc.golden | 18 ++++++ 11 files changed, 103 insertions(+), 110 deletions(-) create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.pir.golden create mode 100644 plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.uplc.golden diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.pir.golden index 221261db453..6f9f7e63e67 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.pir.golden @@ -17,7 +17,7 @@ letrec (/\dead -> z) (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) {r}) - [] + xs (\(x : integer) (xs' : list integer) -> Bool_match (ifThenElse {Bool} (lessThanInteger x 5) True False) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden index 298568c5d68..486b764e6ba 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden @@ -6,7 +6,7 @@ force (force (force chooseList) xs - (delay []) + (delay xs) (delay ((\xs' -> force diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden index e6b8fa84d8e..a8b60f469a2 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden @@ -5,9 +5,9 @@ let data Unit | Unit_match where Unit : Unit in -\(v : list integer) -> +\(xs : list integer) -> let - !l : list integer = dropList {integer} 5 v + !l : list integer = dropList {integer} 5 xs in (let r = Unit -> Unit -> integer @@ -25,7 +25,7 @@ in !x : Unit = trace {Unit} "PT22" Unit in error {Unit -> integer}) - (\(x : integer) (xs : list integer) (ds : Unit) (eta : Unit) -> x) + (\(x : integer) (xs : list integer) (ds : Unit) (_ann : Unit) -> x) l Unit Unit \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden index f3f8a849b92..b6edaa999fd 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden @@ -1,6 +1,6 @@ (program 1.1.0 - (\v -> + (\xs -> (\l -> force (force (force chooseList) @@ -8,7 +8,7 @@ (delay (\_ann -> (\x -> error) (force trace "PT22" (constr 0 [])))) (delay - ((\x xs ds eta -> x) (force headList l) (force tailList l)))) + ((\x xs ds _ann -> x) (force headList l) (force tailList l)))) (constr 0 []) (constr 0 [])) - (force dropList 5 v))) \ No newline at end of file + (force dropList 5 xs))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.pir.golden index d63dd6006a7..8595d7bfcc1 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.pir.golden @@ -4,34 +4,9 @@ let False : Bool data Unit | Unit_match where Unit : Unit - !traceError : all a. string -> a - = /\a -> - \(str : string) -> let !x : Unit = trace {Unit} str Unit in error {a} in -letrec - !go : list integer -> integer -> integer - = \(xs : list integer) (i : integer) -> - (let - r = Unit -> Unit -> integer - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - (\(ds : Unit) -> traceError {Unit -> integer} "PT22") - (\(x : integer) (xs : list integer) (ds : Unit) (ds : Unit) -> - Bool_match - (ifThenElse {Bool} (equalsInteger 0 i) True False) - {all dead. integer} - (/\dead -> x) - (/\dead -> go xs (subtractInteger i 1)) - {all dead. dead}) - xs - Unit - Unit -in -\(xs : list integer) -> traceError {integer} "PT21" \ No newline at end of file +\(xs : list integer) -> + let + !x : Unit = trace {Unit} "PT21" Unit + in + error {integer} \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden index 66da482c999..59f1aaeb038 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden @@ -1,22 +1 @@ -(program - 1.1.0 - ((\traceError -> - (\go xs -> traceError "PT21") - ((\s -> s s) - (\s xs i -> - force - (force (force chooseList) - xs - (delay (\ds -> traceError "PT22")) - (delay - ((\x xs ds ds -> - force - (force ifThenElse - (equalsInteger 0 i) - (delay x) - (delay (s s xs (subtractInteger i 1))))) - (force headList xs) - (force tailList xs)))) - (constr 0 []) - (constr 0 [])))) - (\str -> (\x -> error) (force trace str (constr 0 []))))) \ No newline at end of file +(program 1.1.0 (\xs -> (\x -> error) (force trace "PT21" (constr 0 [])))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.pir.golden index c099fd4aeb8..3bc9c55b6eb 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.pir.golden @@ -5,34 +5,27 @@ let data Unit | Unit_match where Unit : Unit in -letrec - !go : list integer -> integer -> integer - = \(xs : list integer) (i : integer) -> - (let - r = Unit -> Unit -> integer - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - (\(ds : Unit) -> - let - !x : Unit = trace {Unit} "PT22" Unit - in - error {Unit -> integer}) - (\(x : integer) (xs : list integer) (ds : Unit) (ds : Unit) -> - Bool_match - (ifThenElse {Bool} (equalsInteger 0 i) True False) - {all dead. integer} - (/\dead -> x) - (/\dead -> go xs (subtractInteger i 1)) - {all dead. dead}) - xs - Unit - Unit -in -\(xs : list integer) -> go xs 10 \ No newline at end of file +\(xs : list integer) -> + let + !l : list integer = dropList {integer} 10 xs + in + (let + r = Unit -> Unit -> integer + in + \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + chooseList + {integer} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) + {r}) + (\(_ann : Unit) -> + let + !x : Unit = trace {Unit} "PT22" Unit + in + error {Unit -> integer}) + (\(x : integer) (xs : list integer) (ds : Unit) (_ann : Unit) -> x) + l + Unit + Unit \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden index ce84f14ce5e..5e3af4cfb84 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden @@ -1,21 +1,14 @@ (program 1.1.0 - ((\go xs -> go xs 10) - ((\s -> s s) - (\s xs i -> - force - (force (force chooseList) - xs - (delay - (\ds -> (\x -> error) (force trace "PT22" (constr 0 [])))) - (delay - ((\x xs ds ds -> - force - (force ifThenElse - (equalsInteger 0 i) - (delay x) - (delay (s s xs (subtractInteger i 1))))) - (force headList xs) - (force tailList xs)))) - (constr 0 []) - (constr 0 []))))) \ No newline at end of file + (\xs -> + (\l -> + force + (force (force chooseList) + l + (delay + (\_ann -> (\x -> error) (force trace "PT22" (constr 0 [])))) + (delay + ((\x xs ds _ann -> x) (force headList l) (force tailList l)))) + (constr 0 []) + (constr 0 [])) + (force dropList 10 xs))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden new file mode 100644 index 00000000000..f5d26d1cccc --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden @@ -0,0 +1,5 @@ +cpu: 20752934 +mem: 83192 +size: 72 + +(con (list integer) [2,4,6,8,10,12,14,16,18,20]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.pir.golden new file mode 100644 index 00000000000..a101fa13848 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.pir.golden @@ -0,0 +1,30 @@ +let + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} +in +letrec + !go : list integer -> list integer -> list integer + = \(xs : list integer) (ys : list integer) -> + caseList' + {integer} + {list integer} + [] + (\(x : integer) (xs' : list integer) -> + caseList' + {integer} + {list integer} + [] + (\(y : integer) (ys' : list integer) -> + mkCons {integer} (addInteger x y) (go xs' ys')) + ys) + xs +in +\(xs : list integer) -> go xs xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.uplc.golden new file mode 100644 index 00000000000..3a84c0a43e4 --- /dev/null +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.uplc.golden @@ -0,0 +1,18 @@ +(program + 1.1.0 + ((\go xs -> go xs xs) + ((\s -> s s) + (\s xs ys -> + (\cse -> + cse + (\x xs' -> + cse + (\y ys' -> force mkCons (addInteger x y) (s s xs' ys')) + ys) + xs) + (\f xs -> + force + (force (force chooseList) + xs + (delay []) + (delay (f (force headList xs) (force tailList xs))))))))) \ No newline at end of file From 8406c9229193de063a291d2e27faf3c1c768ece4 Mon Sep 17 00:00:00 2001 From: zeme Date: Tue, 3 Jun 2025 14:48:14 +0200 Subject: [PATCH 24/30] wip --- .../BuiltinList/Budget/9.6/(++).eval.golden | 6 +- .../BuiltinList/Budget/9.6/(++).pir.golden | 73 +++-- .../BuiltinList/Budget/9.6/(++).uplc.golden | 109 ++++++- .../BuiltinList/Budget/9.6/(<|).eval.golden | 6 +- .../BuiltinList/Budget/9.6/(<|).pir.golden | 6 +- .../BuiltinList/Budget/9.6/(<|).uplc.golden | 9 +- .../BuiltinList/Budget/9.6/all.eval.golden | 6 +- .../BuiltinList/Budget/9.6/all.pir.golden | 61 +++- .../BuiltinList/Budget/9.6/all.uplc.golden | 144 +++++++-- .../BuiltinList/Budget/9.6/and.eval.golden | 6 +- .../BuiltinList/Budget/9.6/and.pir.golden | 66 ++-- .../BuiltinList/Budget/9.6/and.uplc.golden | 105 ++++++- .../BuiltinList/Budget/9.6/any.eval.golden | 6 +- .../BuiltinList/Budget/9.6/any.pir.golden | 61 +++- .../BuiltinList/Budget/9.6/any.uplc.golden | 144 +++++++-- .../BuiltinList/Budget/9.6/append.eval.golden | 6 +- .../BuiltinList/Budget/9.6/append.pir.golden | 74 +++-- .../BuiltinList/Budget/9.6/append.uplc.golden | 114 ++++++- .../BuiltinList/Budget/9.6/concat.eval.golden | 6 +- .../BuiltinList/Budget/9.6/concat.pir.golden | 82 +++-- .../BuiltinList/Budget/9.6/concat.uplc.golden | 134 ++++++-- .../Budget/9.6/concatMap.eval.golden | 6 +- .../Budget/9.6/concatMap.pir.golden | 136 +++++--- .../Budget/9.6/concatMap.uplc.golden | 250 ++++++++++++--- .../BuiltinList/Budget/9.6/cons.eval.golden | 6 +- .../BuiltinList/Budget/9.6/cons.pir.golden | 6 +- .../BuiltinList/Budget/9.6/cons.uplc.golden | 9 +- .../BuiltinList/Budget/9.6/drop.eval.golden | 6 +- .../BuiltinList/Budget/9.6/drop.pir.golden | 69 +++-- .../BuiltinList/Budget/9.6/drop.uplc.golden | 121 ++++++-- .../Budget/9.6/dropWhile.eval.golden | 6 +- .../Budget/9.6/dropWhile.pir.golden | 85 +++-- .../Budget/9.6/dropWhile.uplc.golden | 112 ++++++- .../BuiltinList/Budget/9.6/elem.eval.golden | 6 +- .../BuiltinList/Budget/9.6/elem.pir.golden | 72 +++-- .../BuiltinList/Budget/9.6/elem.uplc.golden | 147 ++++++--- .../BuiltinList/Budget/9.6/elemBy.eval.golden | 6 +- .../BuiltinList/Budget/9.6/elemBy.pir.golden | 82 +++-- .../BuiltinList/Budget/9.6/elemBy.uplc.golden | 112 ++++++- .../BuiltinList/Budget/9.6/empty.eval.golden | 6 +- .../BuiltinList/Budget/9.6/empty.pir.golden | 8 +- .../BuiltinList/Budget/9.6/empty.uplc.golden | 8 +- .../BuiltinList/Budget/9.6/filter.eval.golden | 6 +- .../BuiltinList/Budget/9.6/filter.pir.golden | 91 ++++-- .../BuiltinList/Budget/9.6/filter.uplc.golden | 123 ++++++-- .../BuiltinList/Budget/9.6/find.eval.golden | 6 +- .../BuiltinList/Budget/9.6/find.pir.golden | 76 +++-- .../BuiltinList/Budget/9.6/find.uplc.golden | 162 ++++++++-- .../Budget/9.6/findIndexJust.eval.golden | 6 +- .../Budget/9.6/findIndexJust.pir.golden | 88 ++++-- .../Budget/9.6/findIndexJust.uplc.golden | 143 ++++++++- .../Budget/9.6/findIndexNothing.eval.golden | 6 +- .../Budget/9.6/findIndexNothing.pir.golden | 88 ++++-- .../Budget/9.6/findIndexNothing.uplc.golden | 143 ++++++++- .../Budget/9.6/findIndices.eval.golden | 6 +- .../Budget/9.6/findIndices.pir.golden | 106 ++++--- .../Budget/9.6/findIndices.uplc.golden | 135 ++++++-- .../BuiltinList/Budget/9.6/foldl.eval.golden | 6 +- .../BuiltinList/Budget/9.6/foldl.pir.golden | 75 ++++- .../BuiltinList/Budget/9.6/foldl.uplc.golden | 88 +++++- .../BuiltinList/Budget/9.6/foldr.eval.golden | 6 +- .../BuiltinList/Budget/9.6/foldr.pir.golden | 61 +++- .../BuiltinList/Budget/9.6/foldr.uplc.golden | 86 +++++- .../Budget/9.6/headEmpty.pir.golden | 83 +++-- .../Budget/9.6/headEmpty.uplc.golden | 91 +++++- .../BuiltinList/Budget/9.6/headOk.eval.golden | 6 +- .../BuiltinList/Budget/9.6/headOk.pir.golden | 79 +++-- .../BuiltinList/Budget/9.6/headOk.uplc.golden | 95 +++++- .../BuiltinList/Budget/9.6/index.eval.golden | 6 +- .../BuiltinList/Budget/9.6/index.pir.golden | 84 +++-- .../BuiltinList/Budget/9.6/index.uplc.golden | 139 ++++++++- .../Budget/9.6/indexNegative.pir.golden | 64 +++- .../Budget/9.6/indexNegative.uplc.golden | 136 +++++++- .../Budget/9.6/indexTooLarge.pir.golden | 84 +++-- .../Budget/9.6/indexTooLarge.uplc.golden | 139 ++++++++- .../Budget/9.6/lastEmpty.pir.golden | 69 ++++- .../Budget/9.6/lastEmpty.uplc.golden | 130 ++++++-- .../BuiltinList/Budget/9.6/lastOk.eval.golden | 6 +- .../BuiltinList/Budget/9.6/lastOk.pir.golden | 65 +++- .../BuiltinList/Budget/9.6/lastOk.uplc.golden | 119 +++++-- .../BuiltinList/Budget/9.6/length.eval.golden | 6 +- .../BuiltinList/Budget/9.6/length.pir.golden | 44 ++- .../BuiltinList/Budget/9.6/length.uplc.golden | 57 +++- .../Budget/9.6/listToMaybeJust.eval.golden | 6 +- .../Budget/9.6/listToMaybeJust.pir.golden | 33 +- .../Budget/9.6/listToMaybeJust.uplc.golden | 40 ++- .../Budget/9.6/listToMaybeNothing.eval.golden | 6 +- .../Budget/9.6/listToMaybeNothing.pir.golden | 37 ++- .../Budget/9.6/listToMaybeNothing.uplc.golden | 35 ++- .../BuiltinList/Budget/9.6/map.eval.golden | 6 +- .../BuiltinList/Budget/9.6/map.pir.golden | 57 +++- .../BuiltinList/Budget/9.6/map.uplc.golden | 89 +++++- .../Budget/9.6/mapMaybe.eval.golden | 6 +- .../Budget/9.6/mapMaybe.pir.golden | 119 ++++--- .../Budget/9.6/mapMaybe.uplc.golden | 180 +++++++++-- .../Budget/9.6/notElem.eval.golden | 6 +- .../BuiltinList/Budget/9.6/notElem.pir.golden | 101 ++++-- .../Budget/9.6/notElem.uplc.golden | 152 +++++++-- .../BuiltinList/Budget/9.6/nub.eval.golden | 6 +- .../BuiltinList/Budget/9.6/nub.pir.golden | 181 ++++++++--- .../BuiltinList/Budget/9.6/nub.uplc.golden | 291 +++++++++++++++--- .../BuiltinList/Budget/9.6/nubBy.eval.golden | 6 +- .../BuiltinList/Budget/9.6/nubBy.pir.golden | 126 ++++++-- .../BuiltinList/Budget/9.6/nubBy.uplc.golden | 209 +++++++++++-- .../BuiltinList/Budget/9.6/null.eval.golden | 6 +- .../BuiltinList/Budget/9.6/null.pir.golden | 13 +- .../BuiltinList/Budget/9.6/null.uplc.golden | 30 +- .../BuiltinList/Budget/9.6/or.eval.golden | 6 +- .../test/BuiltinList/Budget/9.6/or.pir.golden | 66 ++-- .../BuiltinList/Budget/9.6/or.uplc.golden | 105 ++++++- .../Budget/9.6/replicate.eval.golden | 6 +- .../Budget/9.6/replicate.pir.golden | 42 ++- .../Budget/9.6/replicate.uplc.golden | 95 +++++- .../Budget/9.6/revAppend.eval.golden | 6 +- .../Budget/9.6/revAppend.pir.golden | 52 +++- .../Budget/9.6/revAppend.uplc.golden | 67 +++- .../Budget/9.6/reverse.eval.golden | 6 +- .../BuiltinList/Budget/9.6/reverse.pir.golden | 66 +++- .../Budget/9.6/reverse.uplc.golden | 83 ++++- .../Budget/9.6/singleton.eval.golden | 6 +- .../Budget/9.6/singleton.pir.golden | 13 +- .../Budget/9.6/singleton.uplc.golden | 12 +- .../Budget/9.6/tailEmpty.pir.golden | 90 ++++-- .../Budget/9.6/tailEmpty.uplc.golden | 91 +++++- .../BuiltinList/Budget/9.6/tailOk.eval.golden | 6 +- .../BuiltinList/Budget/9.6/tailOk.pir.golden | 86 ++++-- .../BuiltinList/Budget/9.6/tailOk.uplc.golden | 95 +++++- .../BuiltinList/Budget/9.6/take.eval.golden | 6 +- .../BuiltinList/Budget/9.6/take.pir.golden | 77 +++-- .../BuiltinList/Budget/9.6/take.uplc.golden | 130 ++++++-- .../Budget/9.6/unconsJust.eval.golden | 6 +- .../Budget/9.6/unconsJust.pir.golden | 44 +-- .../Budget/9.6/unconsJust.uplc.golden | 57 +++- .../Budget/9.6/unconsNothing.eval.golden | 6 +- .../Budget/9.6/unconsNothing.pir.golden | 48 +-- .../Budget/9.6/unconsNothing.uplc.golden | 51 ++- .../Budget/9.6/uniqueElementJust.eval.golden | 6 +- .../Budget/9.6/uniqueElementJust.pir.golden | 83 +++-- .../Budget/9.6/uniqueElementJust.uplc.golden | 177 +++++++++-- .../9.6/uniqueElementNothing.eval.golden | 6 +- .../9.6/uniqueElementNothing.pir.golden | 31 +- .../9.6/uniqueElementNothing.uplc.golden | 49 ++- .../Budget/9.6/zipWith.eval.golden | 6 +- .../BuiltinList/Budget/9.6/zipWith.pir.golden | 89 ++++-- .../Budget/9.6/zipWith.uplc.golden | 119 ++++++- .../test/BuiltinList/Budget/Spec.hs | 3 + 146 files changed, 7364 insertions(+), 1862 deletions(-) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden index 9d0530c2037..d13081a0da9 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden @@ -1,5 +1,5 @@ -cpu: 9002784 -mem: 33712 -size: 42 +cpu: 15994784 +mem: 77412 +size: 162 (con (list integer) [1,2,3,4,5,6,7,8,9,10,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).pir.golden index 2cb7c10b472..2bf0de201cc 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).pir.golden @@ -1,25 +1,48 @@ -\(xs : list integer) -> - (let - b = list integer - in - \(f : integer -> b -> b) (acc : b) -> - letrec - !go : list integer -> b - = \(xs : list integer) -> - chooseList - {integer} - {all dead. b} - xs - (/\dead -> acc) - (/\dead -> - let - !x : integer = headList {integer} xs - !xs : list integer = tailList {integer} xs - in - f x (go xs)) - {b} - in - go) - (mkCons {integer}) - xs - xs \ No newline at end of file +let + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~foldr : all a b. (a -> b -> b) -> b -> list a -> b + = /\a b -> + \(f : a -> b -> b) -> + let + !f : a -> b -> b = f + in + \(acc : b) -> + let + !acc : b = acc + in + letrec + ~go : list a -> b + = caseList' + {a} + {b} + acc + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> let !xs : list a = xs in f x (go xs)) + in + go + !mkCons : all a. a -> list a -> list a = mkCons + ~`++` : all a. list a -> list a -> list a + = /\a -> + \(l : list a) -> + let + !l : list a = l + in + \(r : list a) -> + let + !r : list a = r + in + foldr {a} {list a} (mkCons {a}) r l +in +\(xs : list integer) -> let !xs : list integer = xs in `++` {integer} xs xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).uplc.golden index 96fab57f85d..6a9ee885e8e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).uplc.golden @@ -1,14 +1,99 @@ (program 1.1.0 - (\xs -> - (\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay xs) - (delay - (force mkCons - (force headList xs) - ((\x -> s s x) (force tailList xs)))))) - xs)) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + ((\`++` -> + force `++`) + (delay + (delay + (\l -> + (\l + r -> + (\r -> + force + (force + ((\foldr -> + force foldr) + (delay + (delay + (delay + (\f -> + (\f + acc -> + (\acc -> + (\caseList' -> + (\tup -> + (\go -> + (\go -> + force go) + (go + (delay + (\x -> + x)))) + (force tup + (\arg_0 -> + arg_0))) + (delay + (\f -> + f + (force + (force + fix1) + (\go + arg -> + delay + (force + (force + caseList') + acc + (\x -> + (\x + xs -> + (\xs -> + f + x + (force + (go + (delay + (\x -> + x))) + xs)) + xs) + x))))))) + (delay + (delay + (\z + f + xs -> + force + (force + (force + chooseList) + xs + (delay + z) + (delay + (f + (force + headList + xs) + (force + tailList + xs)))))))) + acc) + f)))))) + (force ((\mkCons -> mkCons) mkCons)) + r + l) + r) + l)))) + xs + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden index ba51fd9d80e..6e75b247019 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden @@ -1,5 +1,5 @@ -cpu: 216462 -mem: 1032 -size: 9 +cpu: 392462 +mem: 2132 +size: 20 (con (list integer) [42,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).pir.golden index 71090410f42..4e9ff0d9231 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).pir.golden @@ -1 +1,5 @@ -\(xs : list integer) -> mkCons {integer} 42 xs \ No newline at end of file +let + !mkCons : all a. a -> list a -> list a = mkCons + ~`<|` : all a. a -> list a -> list a = mkCons +in +\(xs : list integer) -> let !xs : list integer = xs in `<|` {integer} 42 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).uplc.golden index 5d97b79876d..aaccbae3117 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).uplc.golden @@ -1 +1,8 @@ -(program 1.1.0 (\xs -> force mkCons 42 xs)) \ No newline at end of file +(program + 1.1.0 + (\xs -> + (\xs -> + force ((\`<|` -> force `<|`) (delay ((\mkCons -> mkCons) mkCons))) + 42 + xs) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.eval.golden index 763e1bc8b5b..9aab1e5bba3 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.eval.golden @@ -1,5 +1,5 @@ -cpu: 14535700 -mem: 62410 -size: 86 +cpu: 26311700 +mem: 136010 +size: 241 (constr 0 (constr 1) (constr 0)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.pir.golden index 23793433b8b..ed60d11be74 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.pir.golden @@ -1,24 +1,40 @@ let + ~v : integer = 0 + ~v : integer = 8 data (Tuple2 :: * -> * -> *) a b | Tuple2_match where Tuple2 : a -> b -> Tuple2 a b + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} data Bool | Bool_match where True : Bool False : Bool - !all : all a. (a -> Bool) -> list a -> Bool + ~all : all a. (a -> Bool) -> list a -> Bool = /\a -> \(p : a -> Bool) -> + let + !p : a -> Bool = p + in letrec - !go : list a -> Bool - = \(xs : list a) -> - chooseList - {a} - {all dead. Bool} - xs - (/\dead -> True) - (/\dead -> + ~go : list a -> Bool + = caseList' + {a} + {Bool} + True + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> let - !x : a = headList {a} xs - !xs : list a = tailList {a} xs + !xs : list a = xs in Bool_match (p x) @@ -26,16 +42,27 @@ let (/\dead -> go xs) (/\dead -> False) {all dead. dead}) - {Bool} in go - !greaterThanEqualsInteger : integer -> integer -> Bool - = \(x : integer) (y : integer) -> - ifThenElse {Bool} (lessThanInteger x y) False True + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanInteger : integer -> integer -> bool = lessThanInteger + ~greaterThanEqualsInteger : integer -> integer -> Bool + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> + let + !y : integer = y + in + ifThenElse {Bool} (lessThanInteger x y) False True in \(xs : list integer) -> + let + !xs : list integer = xs + in Tuple2 {Bool} {Bool} - (all {integer} (\(v : integer) -> greaterThanEqualsInteger v 8) xs) - (all {integer} (\(v : integer) -> greaterThanEqualsInteger v 0) xs) \ No newline at end of file + (all {integer} (\(v : integer) -> greaterThanEqualsInteger v v) xs) + (all {integer} (\(v : integer) -> greaterThanEqualsInteger v v) xs) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.uplc.golden index bf5c5290259..d0a86c4a784 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.uplc.golden @@ -1,27 +1,121 @@ (program 1.1.0 - (\xs -> - (\greaterThanEqualsInteger -> - (\all -> - constr 0 - [ (all (\v -> greaterThanEqualsInteger v 8) xs) - , (all (\v -> greaterThanEqualsInteger v 0) xs) ]) - (\p -> - (\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay (constr 0 [])) - (delay - ((\x -> - (\xs -> - force - (case - (p x) - [ (delay (s s xs)) - , (delay (constr 1 [])) ])) - (force tailList xs)) - (force headList xs))))))) - (\x y -> - force ifThenElse (lessThanInteger x y) (constr 1 []) (constr 0 [])))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + (\lessThanInteger -> + (\ifThenElse -> + force + (delay + (\True + False + Bool_match -> + (\greaterThanEqualsInteger -> + (\caseList' -> + (\all -> + force + (force + (force + (delay + (\Tuple2 Tuple2_match -> Tuple2)) + (delay + (delay + (\arg_0 arg_1 -> + constr 0 [arg_0, arg_1]))) + (delay + (delay + (\x -> + delay + (\case_Tuple2 -> + case + x + [case_Tuple2])))))) + (force (force all) + (\v -> + force greaterThanEqualsInteger + v + ((\v -> force v) (delay 8))) + xs) + (force (force all) + (\v -> + force greaterThanEqualsInteger + v + ((\v -> force v) (delay 0))) + xs)) + (delay + (delay + (\p -> + (\p -> + (\tup -> + (\go -> + (\go -> force go) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force + caseList') + True + (\x -> + (\x + xs -> + (\xs -> + force + (force + (Bool_match + (p + x)) + (delay + (force + (go + (delay + (\x -> + x))) + xs)) + (delay + False))) + xs) + x))))))) + p)))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList xs)))))))) + (delay + (\x -> + (\x y -> + (\y -> + force ifThenElse + (lessThanInteger x y) + False + True) + y) + x)))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True case_False -> + case x [case_True, case_False]))) + ifThenElse) + lessThanInteger) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden index 752d9c11fea..88e4ca25e92 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden @@ -1,5 +1,5 @@ -cpu: 2091812 -mem: 8694 -size: 53 +cpu: 4667812 +mem: 24794 +size: 176 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.pir.golden index b4f4af65b83..f9e0ff8c43c 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.pir.golden @@ -2,26 +2,48 @@ let data Bool | Bool_match where True : Bool False : Bool + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~all : all a. (a -> Bool) -> list a -> Bool + = /\a -> + \(p : a -> Bool) -> + let + !p : a -> Bool = p + in + letrec + ~go : list a -> Bool + = caseList' + {a} + {Bool} + True + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + Bool_match + (p x) + {all dead. Bool} + (/\dead -> go xs) + (/\dead -> False) + {all dead. dead}) + in + go + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + ~and : list bool -> Bool + = all + {bool} + (\(x : bool) -> let !x : bool = x in ifThenElse {Bool} x True False) in -letrec - !go : list bool -> Bool - = \(xs : list bool) -> - chooseList - {bool} - {all dead. Bool} - xs - (/\dead -> True) - (/\dead -> - let - !x : bool = headList {bool} xs - !xs : list bool = tailList {bool} xs - in - Bool_match - (ifThenElse {Bool} x True False) - {all dead. Bool} - (/\dead -> go xs) - (/\dead -> False) - {all dead. dead}) - {Bool} -in -\(xs : list bool) -> go xs \ No newline at end of file +\(xs : list bool) -> let !xs : list bool = xs in and xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.uplc.golden index 196bca20f03..7046ab03f98 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.uplc.golden @@ -1,19 +1,90 @@ (program 1.1.0 - ((\go xs -> go xs) - ((\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay (constr 0 [])) - (delay - ((\x -> - (\xs -> - force - (force ifThenElse - x - (delay (s s xs)) - (delay (constr 1 [])))) - (force tailList xs)) - (force headList xs)))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + (delay + (\True + False + Bool_match -> + (\and -> + force and) + (delay + (force + ((\all -> + force all) + (delay + (delay + (\p -> + (\p -> + (\caseList' -> + (\tup -> + (\go -> + (\go -> force go) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force + caseList') + True + (\x -> + (\x + xs -> + (\xs -> + force + (force + (Bool_match + (p + x)) + (delay + (force + (go + (delay + (\x -> + x))) + xs)) + (delay + False))) + xs) + x))))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList + xs) + (force tailList + xs)))))))) + p)))) + (\x -> + (\x -> + force ((\ifThenElse -> ifThenElse) ifThenElse) + x + True + False) + x))))) + (constr 0 []) + (constr 1 []) + (\x -> + delay (\case_True case_False -> case x [case_True, case_False])) + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.eval.golden index 216aca2b2f7..6596a7683c2 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.eval.golden @@ -1,5 +1,5 @@ -cpu: 23293722 -mem: 99496 -size: 86 +cpu: 41341722 +mem: 212296 +size: 241 (constr 0 (constr 0) (constr 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.pir.golden index 758714fa3f2..6cf466ec176 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.pir.golden @@ -1,24 +1,40 @@ let + ~v : integer = 12 + ~v : integer = 8 data (Tuple2 :: * -> * -> *) a b | Tuple2_match where Tuple2 : a -> b -> Tuple2 a b + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} data Bool | Bool_match where True : Bool False : Bool - !any : all a. (a -> Bool) -> list a -> Bool + ~any : all a. (a -> Bool) -> list a -> Bool = /\a -> \(p : a -> Bool) -> + let + !p : a -> Bool = p + in letrec - !go : list a -> Bool - = \(xs : list a) -> - chooseList - {a} - {all dead. Bool} - xs - (/\dead -> False) - (/\dead -> + ~go : list a -> Bool + = caseList' + {a} + {Bool} + False + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> let - !x : a = headList {a} xs - !xs : list a = tailList {a} xs + !xs : list a = xs in Bool_match (p x) @@ -26,16 +42,27 @@ let (/\dead -> True) (/\dead -> go xs) {all dead. dead}) - {Bool} in go - !greaterThanEqualsInteger : integer -> integer -> Bool - = \(x : integer) (y : integer) -> - ifThenElse {Bool} (lessThanInteger x y) False True + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanInteger : integer -> integer -> bool = lessThanInteger + ~greaterThanEqualsInteger : integer -> integer -> Bool + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> + let + !y : integer = y + in + ifThenElse {Bool} (lessThanInteger x y) False True in \(xs : list integer) -> + let + !xs : list integer = xs + in Tuple2 {Bool} {Bool} - (any {integer} (\(v : integer) -> greaterThanEqualsInteger v 8) xs) - (any {integer} (\(v : integer) -> greaterThanEqualsInteger v 12) xs) \ No newline at end of file + (any {integer} (\(v : integer) -> greaterThanEqualsInteger v v) xs) + (any {integer} (\(v : integer) -> greaterThanEqualsInteger v v) xs) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.uplc.golden index d766f2eb6ad..a574e2647ac 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.uplc.golden @@ -1,27 +1,121 @@ (program 1.1.0 - (\xs -> - (\greaterThanEqualsInteger -> - (\any -> - constr 0 - [ (any (\v -> greaterThanEqualsInteger v 8) xs) - , (any (\v -> greaterThanEqualsInteger v 12) xs) ]) - (\p -> - (\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay (constr 1 [])) - (delay - ((\x -> - (\xs -> - force - (case - (p x) - [ (delay (constr 0 [])) - , (delay (s s xs)) ])) - (force tailList xs)) - (force headList xs))))))) - (\x y -> - force ifThenElse (lessThanInteger x y) (constr 1 []) (constr 0 [])))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + (\lessThanInteger -> + (\ifThenElse -> + force + (delay + (\True + False + Bool_match -> + (\greaterThanEqualsInteger -> + (\caseList' -> + (\any -> + force + (force + (force + (delay + (\Tuple2 Tuple2_match -> Tuple2)) + (delay + (delay + (\arg_0 arg_1 -> + constr 0 [arg_0, arg_1]))) + (delay + (delay + (\x -> + delay + (\case_Tuple2 -> + case + x + [case_Tuple2])))))) + (force (force any) + (\v -> + force greaterThanEqualsInteger + v + ((\v -> force v) (delay 8))) + xs) + (force (force any) + (\v -> + force greaterThanEqualsInteger + v + ((\v -> force v) (delay 12))) + xs)) + (delay + (delay + (\p -> + (\p -> + (\tup -> + (\go -> + (\go -> force go) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force + caseList') + False + (\x -> + (\x + xs -> + (\xs -> + force + (force + (Bool_match + (p + x)) + (delay + True) + (delay + (force + (go + (delay + (\x -> + x))) + xs)))) + xs) + x))))))) + p)))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList xs)))))))) + (delay + (\x -> + (\x y -> + (\y -> + force ifThenElse + (lessThanInteger x y) + False + True) + y) + x)))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True case_False -> + case x [case_True, case_False]))) + ifThenElse) + lessThanInteger) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden index 9d0530c2037..34e4493ca8b 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden @@ -1,5 +1,5 @@ -cpu: 9002784 -mem: 33712 -size: 42 +cpu: 16074784 +mem: 77912 +size: 167 (con (list integer) [1,2,3,4,5,6,7,8,9,10,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.pir.golden index 2cb7c10b472..9ed3d5871b0 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.pir.golden @@ -1,25 +1,49 @@ -\(xs : list integer) -> - (let - b = list integer - in - \(f : integer -> b -> b) (acc : b) -> - letrec - !go : list integer -> b - = \(xs : list integer) -> - chooseList - {integer} - {all dead. b} - xs - (/\dead -> acc) - (/\dead -> - let - !x : integer = headList {integer} xs - !xs : list integer = tailList {integer} xs - in - f x (go xs)) - {b} - in - go) - (mkCons {integer}) - xs - xs \ No newline at end of file +let + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~foldr : all a b. (a -> b -> b) -> b -> list a -> b + = /\a b -> + \(f : a -> b -> b) -> + let + !f : a -> b -> b = f + in + \(acc : b) -> + let + !acc : b = acc + in + letrec + ~go : list a -> b + = caseList' + {a} + {b} + acc + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> let !xs : list a = xs in f x (go xs)) + in + go + !mkCons : all a. a -> list a -> list a = mkCons + ~`++` : all a. list a -> list a -> list a + = /\a -> + \(l : list a) -> + let + !l : list a = l + in + \(r : list a) -> + let + !r : list a = r + in + foldr {a} {list a} (mkCons {a}) r l + ~append : all a. list a -> list a -> list a = `++` +in +\(xs : list integer) -> let !xs : list integer = xs in append {integer} xs xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.uplc.golden index 96fab57f85d..e1852e0968e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.uplc.golden @@ -1,14 +1,104 @@ (program 1.1.0 - (\xs -> - (\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay xs) - (delay - (force mkCons - (force headList xs) - ((\x -> s s x) (force tailList xs)))))) - xs)) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + ((\append -> + force append) + (delay + ((\`++` -> + force `++`) + (delay + (delay + (\l -> + (\l + r -> + (\r -> + force + (force + ((\foldr -> + force foldr) + (delay + (delay + (delay + (\f -> + (\f + acc -> + (\acc -> + (\caseList' -> + (\tup -> + (\go -> + (\go -> + force + go) + (go + (delay + (\x -> + x)))) + (force + tup + (\arg_0 -> + arg_0))) + (delay + (\f -> + f + (force + (force + fix1) + (\go + arg -> + delay + (force + (force + caseList') + acc + (\x -> + (\x + xs -> + (\xs -> + f + x + (force + (go + (delay + (\x -> + x))) + xs)) + xs) + x))))))) + (delay + (delay + (\z + f + xs -> + force + (force + (force + chooseList) + xs + (delay + z) + (delay + (f + (force + headList + xs) + (force + tailList + xs)))))))) + acc) + f)))))) + (force ((\mkCons -> mkCons) mkCons)) + r + l) + r) + l)))))) + xs + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden index 7b47bf3084d..b3c14b0e80f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden @@ -1,5 +1,5 @@ -cpu: 7467372 -mem: 32100 -size: 75 +cpu: 12811372 +mem: 65500 +size: 216 (con (list integer) [1,2,3,4]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden index e6f0d202d3d..0ec97c0815b 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.pir.golden @@ -1,4 +1,5 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r = /\a r -> \(z : r) (f : a -> list a -> r) (xs : list a) -> @@ -9,34 +10,57 @@ let (/\dead -> z) (/\dead -> f (headList {a} xs) (tailList {a} xs)) {r} + ~foldr : all a b. (a -> b -> b) -> b -> list a -> b + = /\a b -> + \(f : a -> b -> b) -> + let + !f : a -> b -> b = f + in + \(acc : b) -> + let + !acc : b = acc + in + letrec + ~go : list a -> b + = caseList' + {a} + {b} + acc + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> let !xs : list a = xs in f x (go xs)) + in + go + !mkCons : all a. a -> list a -> list a = mkCons + ~concat : all a. (\arep -> list arep) a -> list (list a) -> list a + = /\a -> + \(`$dMkNil` : (\arep -> list arep) a) -> + let + !acc : list a = `$dMkNil` + in + letrec + ~go : list (list a) -> list a + = caseList' + {list a} + {list a} + acc + (\(x : list a) -> + let + !x : list a = x + in + \(xs : list (list a)) -> + let + !xs : list (list a) = xs + !r : list a = go xs + in + foldr {a} {list a} (mkCons {a}) r x) + in + go in \(xss : list (list integer)) -> - (letrec - !go : list (list integer) -> list integer - = caseList' - {list integer} - {list integer} - [] - (\(x : list integer) (xs : list (list integer)) -> - let - !r : list integer = go xs - in - (let - b = list integer - in - \(f : integer -> b -> b) (acc : b) -> - letrec - !go : list integer -> b - = caseList' - {integer} - {b} - acc - (\(x : integer) (xs : list integer) -> f x (go xs)) - in - go) - (mkCons {integer}) - r - x) - in - go) - xss \ No newline at end of file + let + !xss : list (list integer) = xss + in + concat {integer} `$fMkNilInteger` xss \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden index c79e107e23b..bd51b7d79c4 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden @@ -1,22 +1,116 @@ (program 1.1.0 - (\xss -> - (\caseList' -> - (\s -> s s) - (\s -> - caseList' - [] - (\x xs -> - (\acc -> - (\s -> s s) - (\s -> - caseList' acc (\x xs -> force mkCons x (s s xs)))) - (s s xs) - x))) - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay (f (force headList xs) (force tailList xs))))) - xss)) \ No newline at end of file + ((\fix1 + xss -> + (\xss -> + force + ((\concat -> + force concat) + (delay + (delay + (\`$dMkNil` -> + (\acc -> + (\mkCons -> + (\caseList' -> + (\foldr -> + (\tup -> + (\go -> + (\go -> force go) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force caseList') + acc + (\x -> + (\x + xs -> + (\xs -> + (\r -> + force + (force + (force + foldr)) + (force + mkCons) + r + x) + (force + (go + (delay + (\x -> + x))) + xs)) + xs) + x))))))) + (delay + (delay + (delay + (\f -> + (\f + acc -> + (\acc -> + (\tup -> + (\go -> + (\go -> force go) + (go + (delay + (\x -> x)))) + (force tup + (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force + caseList') + acc + (\x -> + (\x + xs -> + (\xs -> + f + x + (force + (go + (delay + (\x -> + x))) + xs)) + xs) + x))))))) + acc) + f))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList xs)))))))) + mkCons) + `$dMkNil`)))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) + xss) + xss) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden index 8b602509874..8a5f2a5511b 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden @@ -1,5 +1,5 @@ -cpu: 56224464 -mem: 237912 -size: 120 +cpu: 98528464 +mem: 502312 +size: 352 (con (list integer) [1,1,2,2,3,3,4,4,5,5,6,6,7,7,8,8,9,9,10,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.pir.golden index ed94210abf4..b8d4a82639c 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.pir.golden @@ -1,4 +1,5 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r = /\a r -> \(z : r) (f : a -> list a -> r) (xs : list a) -> @@ -9,54 +10,99 @@ let (/\dead -> z) (/\dead -> f (headList {a} xs) (tailList {a} xs)) {r} + ~foldr : all a b. (a -> b -> b) -> b -> list a -> b + = /\a b -> + \(f : a -> b -> b) -> + let + !f : a -> b -> b = f + in + \(acc : b) -> + let + !acc : b = acc + in + letrec + ~go : list a -> b + = caseList' + {a} + {b} + acc + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> let !xs : list a = xs in f x (go xs)) + in + go + !mkCons : all a. a -> list a -> list a = mkCons + ~concatMap : + all a b. (\arep -> list arep) b -> (a -> list b) -> list a -> list b + = /\a b -> + \(`$dMkNil` : (\arep -> list arep) b) -> + let + !acc : list b = `$dMkNil` + in + \(f : a -> list b) -> + let + !f : a -> list b = f + in + letrec + ~go : list a -> list b + = caseList' + {a} + {list b} + acc + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + !ys : list b = go xs + !l : list b = f x + in + foldr {b} {list b} (mkCons {b}) ys l) + in + go data Bool | Bool_match where True : Bool False : Bool + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanEqualsInteger : integer -> integer -> bool = lessThanEqualsInteger + !subtractInteger : integer -> integer -> integer = subtractInteger + ~replicate : all a. (\arep -> list arep) a -> integer -> a -> list a + = /\a -> + \(`$dMkNil` : (\arep -> list arep) a) (n : integer) -> + let + !n : integer = n + in + \(x : a) -> + let + !x : a = x + in + letrec + ~go : integer -> list a + = \(n : integer) -> + let + !n : integer = n + !b : bool = lessThanEqualsInteger n 0 + in + Bool_match + (ifThenElse {Bool} b True False) + {all dead. list a} + (/\dead -> `$dMkNil`) + (/\dead -> mkCons {a} x (go (subtractInteger n 1))) + {all dead. dead} + in + go n in \(xss : list integer) -> - (letrec - !go : list integer -> list integer - = caseList' - {integer} - {list integer} - [] - (\(x : integer) -> - letrec - !go : integer -> list integer - = \(n : integer) -> - Bool_match - (ifThenElse - {Bool} - (lessThanEqualsInteger n 0) - True - False) - {all dead. list integer} - (/\dead -> []) - (/\dead -> - mkCons {integer} x (go (subtractInteger n 1))) - {all dead. dead} - in - \(xs : list integer) -> - let - !ys : list integer = go xs - !l : list integer = go 2 - in - (let - b = list integer - in - \(f : integer -> b -> b) (acc : b) -> - letrec - !go : list integer -> b - = caseList' - {integer} - {b} - acc - (\(x : integer) (xs : list integer) -> f x (go xs)) - in - go) - (mkCons {integer}) - ys - l) - in - go) + let + !xss : list integer = xss + in + concatMap + {integer} + {integer} + `$fMkNilInteger` + (replicate {integer} `$fMkNilInteger` 2) xss \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.uplc.golden index 1d8408b64ed..8267b9023ea 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.uplc.golden @@ -1,38 +1,216 @@ (program 1.1.0 - (\xss -> - (\caseList' -> - (\s -> s s) - (\s -> - caseList' - [] - (\x -> - (\go xs -> - (\ys -> - (\l -> - (\s -> s s) - (\s -> - caseList' - ys - (\x xs -> force mkCons x (s s xs))) - l) - (go 2)) - (s s xs)) - ((\s -> s s) - (\s n -> - force - (force ifThenElse - (lessThanEqualsInteger n 0) - (delay []) - (delay - (force mkCons - x - ((\x -> s s x) - (subtractInteger n 1)))))))))) - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay (f (force headList xs) (force tailList xs))))) - xss)) \ No newline at end of file + ((\fix1 + xss -> + (\xss -> + (\mkCons -> + (\`$fMkNilInteger` -> + force + (force + ((\concatMap -> + force concatMap) + (delay + (delay + (delay + (\`$dMkNil` -> + (\acc + f -> + (\f -> + (\caseList' -> + (\foldr -> + (\tup -> + (\go -> + (\go -> force go) + (go (delay (\x -> x)))) + (force tup + (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force + caseList') + acc + (\x -> + (\x + xs -> + (\xs -> + (\ys -> + (\l -> + force + (force + (force + foldr)) + (force + mkCons) + ys + l) + (f + x)) + (force + (go + (delay + (\x -> + x))) + xs)) + xs) + x))))))) + (delay + (delay + (delay + (\f -> + (\f + acc -> + (\acc -> + (\tup -> + (\go -> + (\go -> + force + go) + (go + (delay + (\x -> + x)))) + (force + tup + (\arg_0 -> + arg_0))) + (delay + (\f -> + f + (force + (force + fix1) + (\go + arg -> + delay + (force + (force + caseList') + acc + (\x -> + (\x + xs -> + (\xs -> + f + x + (force + (go + (delay + (\x -> + x))) + xs)) + xs) + x))))))) + acc) + f))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList + xs) + (force tailList + xs)))))))) + f) + `$dMkNil`)))))) + (force `$fMkNilInteger`) + (force + ((\subtractInteger -> + (\lessThanEqualsInteger -> + (\ifThenElse -> + force + (delay + (\True + False + Bool_match -> + (\replicate -> + force replicate) + (delay + (delay + (\`$dMkNil` + n -> + (\n + x -> + (\x -> + (\tup -> + (\go -> + (\go -> + force go n) + (go + (delay + (\x -> + x)))) + (force tup + (\arg_0 -> + arg_0))) + (delay + (\f -> + f + (force + (force + fix1) + (\go + arg -> + delay + (\n -> + (\n -> + (\b -> + force + (force + (Bool_match + (force + ifThenElse + b + True + False)) + (delay + `$dMkNil`) + (delay + (force + mkCons + x + (force + (go + (delay + (\x -> + x))) + (subtractInteger + n + 1)))))) + (lessThanEqualsInteger + n + 0)) + n)))))) + x) + n))))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True case_False -> + case x [case_True, case_False]))) + ifThenElse) + lessThanEqualsInteger) + subtractInteger) + (force `$fMkNilInteger`) + 2)) + (delay [])) + mkCons + xss) + xss) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden index 4eec5a3badc..59b15d35277 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden @@ -1,5 +1,5 @@ -cpu: 216462 -mem: 1032 -size: 9 +cpu: 392462 +mem: 2132 +size: 20 (con (list integer) [0,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.pir.golden index ed3cc42f4cf..7cf5e6f34f0 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.pir.golden @@ -1 +1,5 @@ -\(xs : list integer) -> mkCons {integer} 0 xs \ No newline at end of file +let + !mkCons : all a. a -> list a -> list a = mkCons + ~cons : all a. a -> list a -> list a = mkCons +in +\(xs : list integer) -> let !xs : list integer = xs in cons {integer} 0 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.uplc.golden index f4626f1cdc2..f610a9ebf43 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.uplc.golden @@ -1 +1,8 @@ -(program 1.1.0 (\xs -> force mkCons 0 xs)) \ No newline at end of file +(program + 1.1.0 + (\xs -> + (\xs -> + force ((\cons -> force cons) (delay ((\mkCons -> mkCons) mkCons))) + 0 + xs) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden index 084b26d837c..69c85ba76a0 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden @@ -1,5 +1,5 @@ -cpu: 7834491 -mem: 32602 -size: 83 +cpu: 13258491 +mem: 66502 +size: 193 (con (list integer) [6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.pir.golden index c0bbd86e804..ad0bb4546a8 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.pir.golden @@ -1,32 +1,53 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] data Bool | Bool_match where True : Bool False : Bool + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanEqualsInteger : integer -> integer -> bool = lessThanEqualsInteger + !subtractInteger : integer -> integer -> integer = subtractInteger in letrec - !drop : all a. (\arep -> list arep) a -> integer -> list a -> list a + ~drop : all a. (\arep -> list arep) a -> integer -> list a -> list a = /\a -> - \(`$dMkNil` : (\arep -> list arep) a) (n : integer) (l : list a) -> - Bool_match - (ifThenElse {Bool} (lessThanEqualsInteger n 0) True False) - {all dead. list a} - (/\dead -> l) - (/\dead -> - (let - r = list a - in - \(z : r) (f : a -> list a -> r) (xs : list a) -> - chooseList - {a} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {a} xs) (tailList {a} xs)) - {r}) - `$dMkNil` - (\(ds : a) (xs : list a) -> - drop {a} `$dMkNil` (subtractInteger n 1) xs) - l) - {all dead. dead} + \(`$dMkNil` : (\arep -> list arep) a) (n : integer) -> + let + !n : integer = n + in + \(l : list a) -> + let + !l : list a = l + !b : bool = lessThanEqualsInteger n 0 + in + Bool_match + (ifThenElse {Bool} b True False) + {all dead. list a} + (/\dead -> l) + (/\dead -> + caseList' + {a} + {list a} + `$dMkNil` + (\(ds : a) (xs : list a) -> + let + !xs : list a = xs + in + drop {a} `$dMkNil` (subtractInteger n 1) xs) + l) + {all dead. dead} in -\(xs : list integer) -> drop {integer} [] 5 xs \ No newline at end of file +\(xs : list integer) -> + let + !xs : list integer = xs + in + drop {integer} `$fMkNilInteger` 5 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden index 5e05913f523..bfff191cd0d 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden @@ -1,25 +1,100 @@ (program 1.1.0 - ((\drop xs -> force drop [] 5 xs) - ((\s -> s s) - (\s arg -> - delay - (\`$dMkNil` n l -> - force - (force ifThenElse - (lessThanEqualsInteger n 0) - (delay l) - (delay - (force - (force (force chooseList) - l - (delay `$dMkNil`) - (delay - ((\ds xs -> - force (s s (delay (\x -> x))) - `$dMkNil` - (subtractInteger n 1) - xs) - (force headList l) - (force tailList l))))))))) - (delay (\x -> x))))) \ No newline at end of file + ((\fix1 -> + (\subtractInteger -> + (\lessThanEqualsInteger -> + (\ifThenElse -> + (\caseList' -> + force + (delay + (\True + False + Bool_match -> + (\`$fMkNilInteger` -> + (\tup -> + (\drop -> + (\drop xs -> + (\xs -> + force (force drop) + (force `$fMkNilInteger`) + 5 + xs) + xs) + (drop (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\drop + arg -> + delay + (delay + (\`$dMkNil` + n -> + (\n + l -> + (\l -> + (\b -> + force + (force + (Bool_match + (force + ifThenElse + b + True + False)) + (delay l) + (delay + (force + (force + caseList') + `$dMkNil` + (\ds + xs -> + (\xs -> + force + (force + (drop + (delay + (\x -> + x)))) + `$dMkNil` + (subtractInteger + n + 1) + xs) + xs) + l)))) + (lessThanEqualsInteger + n + 0)) + l) + n))))))) + (delay []))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True case_False -> + case x [case_True, case_False]))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList xs)))))))) + ifThenElse) + lessThanEqualsInteger) + subtractInteger) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden index 208e37b12cc..e921026974a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden @@ -1,5 +1,5 @@ -cpu: 5295830 -mem: 20590 -size: 54 +cpu: 13151830 +mem: 69690 +size: 209 (con (list integer) [5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.pir.golden index 6f9f7e63e67..ad7f046b99a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.pir.golden @@ -1,30 +1,67 @@ let + ~v : integer = 5 + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} data Bool | Bool_match where True : Bool False : Bool -in -letrec - !go : list integer -> list integer - = \(xs : list integer) -> - (let - r = list integer + ~dropWhile : all a. (a -> Bool) -> list a -> list a + = /\a -> + \(p : a -> Bool) -> + let + !p : a -> Bool = p + in + letrec + ~go : list a -> list a + = \(xs : list a) -> + let + !xs : list a = xs + in + caseList' + {a} + {list a} + xs + (\(x : a) -> + let + !x : a = x + in + \(xs' : list a) -> + let + !xs' : list a = xs' + in + Bool_match + (p x) + {all dead. list a} + (/\dead -> go xs') + (/\dead -> xs) + {all dead. dead}) + xs + in + \(eta : list a) -> go eta + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanInteger : integer -> integer -> bool = lessThanInteger + ~lessThanInteger : integer -> integer -> Bool + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> + let + !y : integer = y + !b : bool = lessThanInteger x y in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - xs - (\(x : integer) (xs' : list integer) -> - Bool_match - (ifThenElse {Bool} (lessThanInteger x 5) True False) - {all dead. list integer} - (/\dead -> go xs') - (/\dead -> xs) - {all dead. dead}) - xs + ifThenElse {Bool} b True False in -\(xs : list integer) -> go xs \ No newline at end of file +\(xs : list integer) -> + let + !xs : list integer = xs + in + dropWhile {integer} (\(v : integer) -> lessThanInteger v v) xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden index 486b764e6ba..b106f42c10a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden @@ -1,17 +1,99 @@ (program 1.1.0 - ((\go xs -> go xs) - ((\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay xs) - (delay - ((\xs' -> - force - (force ifThenElse - (lessThanInteger (force headList xs) 5) - (delay (s s xs')) - (delay xs))) - (force tailList xs)))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + (delay + (\True + False + Bool_match -> + force + ((\dropWhile -> + force dropWhile) + (delay + (delay + (\p -> + (\p -> + (\caseList' -> + (\tup -> + (\go -> + (\go eta -> force go eta) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (\xs -> + (\xs -> + force + (force + caseList') + xs + (\x -> + (\x + xs' -> + (\xs' -> + force + (force + (Bool_match + (p + x)) + (delay + (force + (go + (delay + (\x -> + x))) + xs')) + (delay + xs))) + xs') + x) + xs) + xs)))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList + xs)))))))) + p)))) + (\v -> + (\lessThanInteger -> + (\ifThenElse -> + (\lessThanInteger -> force lessThanInteger) + (delay + (\x -> + (\x y -> + (\y -> + (\b -> force ifThenElse b True False) + (lessThanInteger x y)) + y) + x))) + ifThenElse) + lessThanInteger + v + ((\v -> force v) (delay 5))))) + (constr 0 []) + (constr 1 []) + (\x -> + delay (\case_True case_False -> case x [case_True, case_False])) + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.eval.golden index 48dee373482..5f220aecc55 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.eval.golden @@ -1,5 +1,5 @@ -cpu: 22604496 -mem: 94396 -size: 93 +cpu: 41356496 +mem: 211596 +size: 236 (constr 0 (constr 0) (constr 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.pir.golden index 3c282934b3c..dd1b82e7769 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.pir.golden @@ -1,24 +1,52 @@ let - data (Tuple2 :: * -> * -> *) a b | Tuple2_match where - Tuple2 : a -> b -> Tuple2 a b data Bool | Bool_match where True : Bool False : Bool - !elem : all a. (\a -> a -> a -> Bool) a -> a -> list a -> Bool + !equalsInteger : integer -> integer -> bool = equalsInteger + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + ~equalsInteger : integer -> integer -> Bool + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> + let + !y : integer = y + !b : bool = equalsInteger x y + in + ifThenElse {Bool} b True False + ~`$fEqInteger` : (\a -> a -> a -> Bool) integer = equalsInteger + data (Tuple2 :: * -> * -> *) a b | Tuple2_match where + Tuple2 : a -> b -> Tuple2 a b + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~elem : all a. (\a -> a -> a -> Bool) a -> a -> list a -> Bool = /\a -> \(`$dEq` : (\a -> a -> a -> Bool) a) (a : a) -> + let + !a : a = a + in letrec - !go : list a -> Bool - = \(xs : list a) -> - chooseList - {a} - {all dead. Bool} - xs - (/\dead -> False) - (/\dead -> + ~go : list a -> Bool + = caseList' + {a} + {Bool} + False + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> let - !x : a = headList {a} xs - !xs : list a = tailList {a} xs + !xs : list a = xs in Bool_match (`$dEq` a x) @@ -26,23 +54,15 @@ let (/\dead -> True) (/\dead -> go xs) {all dead. dead}) - {Bool} in go in \(xs : list integer) -> + let + !xs : list integer = xs + in Tuple2 {Bool} {Bool} - (elem - {integer} - (\(x : integer) (y : integer) -> - ifThenElse {Bool} (equalsInteger x y) True False) - 8 - xs) - (elem - {integer} - (\(x : integer) (y : integer) -> - ifThenElse {Bool} (equalsInteger x y) True False) - 12 - xs) \ No newline at end of file + (elem {integer} `$fEqInteger` 8 xs) + (elem {integer} `$fEqInteger` 12 xs) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.uplc.golden index ec6f5566fcf..3d4f5c8c4dc 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.uplc.golden @@ -1,37 +1,114 @@ (program 1.1.0 - (\xs -> - (\elem -> - constr 0 - [ (elem - (\x y -> - force ifThenElse - (equalsInteger x y) - (constr 0 []) - (constr 1 [])) - 8 - xs) - , (elem - (\x y -> - force ifThenElse - (equalsInteger x y) - (constr 0 []) - (constr 1 [])) - 12 - xs) ]) - (\`$dEq` a -> - (\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay (constr 1 [])) - (delay - ((\x -> - (\xs -> - force - (case - (`$dEq` a x) - [(delay (constr 0 [])), (delay (s s xs))])) - (force tailList xs)) - (force headList xs)))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + (\caseList' -> + force + (delay + (\True + False + Bool_match -> + (\elem -> + (\equalsInteger -> + (\`$fEqInteger` -> + force + (force + (force + (delay (\Tuple2 Tuple2_match -> Tuple2)) + (delay + (delay + (\arg_0 arg_1 -> + constr 0 [arg_0, arg_1]))) + (delay + (delay + (\x -> + delay + (\case_Tuple2 -> + case x [case_Tuple2])))))) + (force (force elem) (force `$fEqInteger`) 8 xs) + (force (force elem) + (force `$fEqInteger`) + 12 + xs)) + (delay (force equalsInteger))) + (delay + (\x -> + (\x y -> + (\y -> + (\b -> + force + ((\ifThenElse -> ifThenElse) + ifThenElse) + b + True + False) + ((\equalsInteger -> equalsInteger) + equalsInteger + x + y)) + y) + x))) + (delay + (delay + (\`$dEq` + a -> + (\a -> + (\tup -> + (\go -> + (\go -> force go) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force caseList') + False + (\x -> + (\x + xs -> + (\xs -> + force + (force + (Bool_match + (`$dEq` + a + x)) + (delay + True) + (delay + (force + (go + (delay + (\x -> + x))) + xs)))) + xs) + x))))))) + a))))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True case_False -> case x [case_True, case_False]))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f (force headList xs) (force tailList xs)))))))) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden index f90d707746f..49d3c7d5659 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden @@ -1,5 +1,5 @@ -cpu: 11286024 -mem: 44712 -size: 57 +cpu: 22342024 +mem: 113812 +size: 198 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.pir.golden index de3fbfd9a10..2b33b96f6e6 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.pir.golden @@ -1,27 +1,65 @@ let + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} data Bool | Bool_match where True : Bool False : Bool + ~elemBy : all a. (a -> a -> Bool) -> a -> list a -> Bool + = /\a -> + \(eq : a -> a -> Bool) -> + let + !eq : a -> a -> Bool = eq + in + \(y : a) -> + let + !y : a = y + in + letrec + ~go : list a -> Bool + = caseList' + {a} + {Bool} + False + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + Bool_match + (eq x y) + {all dead. Bool} + (/\dead -> True) + (/\dead -> go xs) + {all dead. dead}) + in + go + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanEqualsInteger : integer -> integer -> bool = lessThanEqualsInteger + ~lessThanEqualsInteger : integer -> integer -> Bool + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> + let + !y : integer = y + !b : bool = lessThanEqualsInteger x y + in + ifThenElse {Bool} b True False in -letrec - !go : list integer -> Bool - = \(xs : list integer) -> - chooseList - {integer} - {all dead. Bool} - xs - (/\dead -> False) - (/\dead -> - let - !x : integer = headList {integer} xs - !xs : list integer = tailList {integer} xs - in - Bool_match - (ifThenElse {Bool} (lessThanEqualsInteger x 0) True False) - {all dead. Bool} - (/\dead -> True) - (/\dead -> go xs) - {all dead. dead}) - {Bool} -in -\(xs : list integer) -> go xs \ No newline at end of file +\(xs : list integer) -> + let + !xs : list integer = xs + in + elemBy {integer} lessThanEqualsInteger 0 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.uplc.golden index 8ecadadefad..a64f6bd0daa 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.uplc.golden @@ -1,19 +1,97 @@ (program 1.1.0 - ((\go xs -> go xs) - ((\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay (constr 1 [])) - (delay - ((\x -> - (\xs -> - force - (force ifThenElse - (lessThanEqualsInteger x 0) - (delay (constr 0 [])) - (delay (s s xs)))) - (force tailList xs)) - (force headList xs)))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + (delay + (\True + False + Bool_match -> + force + ((\elemBy -> + force elemBy) + (delay + (delay + (\eq -> + (\eq + y -> + (\y -> + (\caseList' -> + (\tup -> + (\go -> + (\go -> force go) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force caseList') + False + (\x -> + (\x + xs -> + (\xs -> + force + (force + (Bool_match + (eq + x + y)) + (delay + True) + (delay + (force + (go + (delay + (\x -> + x))) + xs)))) + xs) + x))))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList + xs)))))))) + y) + eq)))) + ((\lessThanEqualsInteger -> + (\ifThenElse -> + (\lessThanEqualsInteger -> + force lessThanEqualsInteger) + (delay + (\x -> + (\x y -> + (\y -> + (\b -> force ifThenElse b True False) + (lessThanEqualsInteger x y)) + y) + x))) + ifThenElse) + lessThanEqualsInteger))) + (constr 0 []) + (constr 1 []) + (\x -> + delay (\case_True case_False -> case x [case_True, case_False])) + 0 + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden index 906f70b6c08..4792048209b 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden @@ -1,5 +1,5 @@ -cpu: 64100 -mem: 500 -size: 4 +cpu: 384100 +mem: 2500 +size: 24 (con (list integer) []) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.pir.golden index 907987c8f2b..49038720c08 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.pir.golden @@ -1 +1,7 @@ -\(ds : list integer) -> [] \ No newline at end of file +let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] + ~mkNil : all arep. (\arep -> list arep) arep -> list arep + = /\arep -> \(v : (\arep -> list arep) arep) -> v + ~empty : all a. (\arep -> list arep) a -> list a = mkNil +in +\(ds : list integer) -> empty {integer} `$fMkNilInteger` \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.uplc.golden index c2725f32aa6..395a8da9f59 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.uplc.golden @@ -1 +1,7 @@ -(program 1.1.0 (\ds -> [])) \ No newline at end of file +(program + 1.1.0 + (\ds -> + force + ((\empty -> force empty) + (delay ((\mkNil -> force mkNil) (delay (delay (\v -> v)))))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden index e0deb5d9e5a..979cc415dd9 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden @@ -1,5 +1,5 @@ -cpu: 14524094 -mem: 54082 -size: 66 +cpu: 25324094 +mem: 121582 +size: 218 (con (list integer) [2,4,6,8,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.pir.golden index 992ee3c35f0..24f771b0605 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.pir.golden @@ -1,37 +1,66 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] + !equalsInteger : integer -> integer -> bool = equalsInteger data Bool | Bool_match where True : Bool False : Bool + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !modInteger : integer -> integer -> integer = modInteger + ~even : integer -> Bool + = \(n : integer) -> + let + !n : integer = n + !x : integer = modInteger n 2 + !b : bool = equalsInteger x 0 + in + ifThenElse {Bool} b True False + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + !mkCons : all a. a -> list a -> list a = mkCons + ~filter : all a. (\arep -> list arep) a -> (a -> Bool) -> list a -> list a + = /\a -> + \(`$dMkNil` : (\arep -> list arep) a) -> + let + !acc : list a = `$dMkNil` + in + \(p : a -> Bool) -> + let + !p : a -> Bool = p + in + letrec + ~go : list a -> list a + = caseList' + {a} + {list a} + acc + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + !xs : list a = go xs + in + Bool_match + (p x) + {all dead. list a} + (/\dead -> mkCons {a} x xs) + (/\dead -> xs) + {all dead. dead}) + in + go in \(xs : list integer) -> - (letrec - !go : list integer -> list integer - = (let - r = list integer - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - [] - (\(x : integer) (xs : list integer) -> - let - !xs : list integer = go xs - in - Bool_match - (ifThenElse - {Bool} - (equalsInteger 0 (modInteger x 2)) - True - False) - {all dead. list integer} - (/\dead -> mkCons {integer} x xs) - (/\dead -> xs) - {all dead. dead}) - in - go) - xs \ No newline at end of file + let + !xs : list integer = xs + in + filter {integer} `$fMkNilInteger` even xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.uplc.golden index 787246eefc0..4643be45682 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.uplc.golden @@ -1,20 +1,107 @@ (program 1.1.0 - (\xs -> - (\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay []) - (delay - ((\x -> - (\xs -> - force - (force ifThenElse - (equalsInteger 0 (modInteger x 2)) - (delay (force mkCons x xs)) - (delay xs))) - ((\x -> s s x) (force tailList xs))) - (force headList xs))))) - xs)) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + (delay + (\True + False + Bool_match -> + force + ((\filter -> + force filter) + (delay + (delay + (\`$dMkNil` -> + (\acc + p -> + (\p -> + (\mkCons -> + (\caseList' -> + (\tup -> + (\go -> + (\go -> force go) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force + caseList') + acc + (\x -> + (\x + xs -> + (\xs -> + (\xs -> + force + (force + (Bool_match + (p + x)) + (delay + (force + mkCons + x + xs)) + (delay + xs))) + (force + (go + (delay + (\x -> + x))) + xs)) + xs) + x))))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList + xs) + (force tailList + xs)))))))) + mkCons) + p) + `$dMkNil`)))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) + ((\modInteger -> + (\ifThenElse -> + (\equalsInteger -> + (\even -> force even) + (delay + (\n -> + (\n -> + (\x -> + (\b -> + force ifThenElse b True False) + (equalsInteger x 0)) + (modInteger n 2)) + n))) + equalsInteger) + ifThenElse) + modInteger))) + (constr 0 []) + (constr 1 []) + (\x -> + delay (\case_True case_False -> case x [case_True, case_False])) + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.eval.golden index 094647521fa..aaed420f5f8 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.eval.golden @@ -1,5 +1,5 @@ -cpu: 23309722 -mem: 99596 -size: 87 +cpu: 42221722 +mem: 217796 +size: 268 (constr 0 (constr 0 (con integer 8)) (constr 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.pir.golden index b4315edec7f..5fe6116d349 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.pir.golden @@ -1,45 +1,71 @@ let + ~v : integer = 12 + ~v : integer = 8 data (Tuple2 :: * -> * -> *) a b | Tuple2_match where Tuple2 : a -> b -> Tuple2 a b data (Maybe :: * -> *) a | Maybe_match where Just : a -> Maybe a Nothing : Maybe a + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} data Bool | Bool_match where True : Bool False : Bool - !find : all a. (a -> Bool) -> list a -> Maybe a + ~find : all a. (a -> Bool) -> list a -> Maybe a = /\a -> \(p : a -> Bool) -> + let + !p : a -> Bool = p + in letrec - !go : list a -> Maybe a - = (let - r = Maybe a - in - \(z : r) (f : a -> list a -> r) (xs : list a) -> - chooseList - {a} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {a} xs) (tailList {a} xs)) - {r}) + ~go : list a -> Maybe a + = caseList' + {a} + {Maybe a} (Nothing {a}) - (\(x : a) (xs : list a) -> - Bool_match - (p x) - {all dead. Maybe a} - (/\dead -> Just {a} x) - (/\dead -> go xs) - {all dead. dead}) + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + Bool_match + (p x) + {all dead. Maybe a} + (/\dead -> Just {a} x) + (/\dead -> go xs) + {all dead. dead}) in go - !greaterThanEqualsInteger : integer -> integer -> Bool - = \(x : integer) (y : integer) -> - ifThenElse {Bool} (lessThanInteger x y) False True + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanInteger : integer -> integer -> bool = lessThanInteger + ~greaterThanEqualsInteger : integer -> integer -> Bool + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> + let + !y : integer = y + in + ifThenElse {Bool} (lessThanInteger x y) False True in \(xs : list integer) -> + let + !xs : list integer = xs + in Tuple2 {Maybe integer} {Maybe integer} - (find {integer} (\(v : integer) -> greaterThanEqualsInteger v 8) xs) - (find {integer} (\(v : integer) -> greaterThanEqualsInteger v 12) xs) \ No newline at end of file + (find {integer} (\(v : integer) -> greaterThanEqualsInteger v v) xs) + (find {integer} (\(v : integer) -> greaterThanEqualsInteger v v) xs) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.uplc.golden index 0851a59fbf1..5c2e5607723 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.uplc.golden @@ -1,25 +1,141 @@ (program 1.1.0 - (\xs -> - (\greaterThanEqualsInteger -> - (\find -> - constr 0 - [ (find (\v -> greaterThanEqualsInteger v 8) xs) - , (find (\v -> greaterThanEqualsInteger v 12) xs) ]) - (\p -> - (\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay (constr 1 [])) - (delay - ((\x xs -> - force - (case - (p x) - [(delay (constr 0 [x])), (delay (s s xs))])) - (force headList xs) - (force tailList xs))))))) - (\x y -> - force ifThenElse (lessThanInteger x y) (constr 1 []) (constr 0 [])))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + (\lessThanInteger -> + (\ifThenElse -> + force + (delay + (\True + False + Bool_match -> + (\greaterThanEqualsInteger -> + (\caseList' -> + force + (delay + (\Just + Nothing + Maybe_match -> + (\find -> + force + (force + (force + (delay + (\Tuple2 Tuple2_match -> + Tuple2)) + (delay + (delay + (\arg_0 arg_1 -> + constr 0 + [arg_0, arg_1]))) + (delay + (delay + (\x -> + delay + (\case_Tuple2 -> + case + x + [ case_Tuple2 ])))))) + (force (force find) + (\v -> + force greaterThanEqualsInteger + v + ((\v -> force v) (delay 8))) + xs) + (force (force find) + (\v -> + force greaterThanEqualsInteger + v + ((\v -> force v) (delay 12))) + xs)) + (delay + (delay + (\p -> + (\p -> + (\tup -> + (\go -> + (\go -> force go) + (go + (delay + (\x -> x)))) + (force tup + (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force + caseList') + (force + Nothing) + (\x -> + (\x + xs -> + (\xs -> + force + (force + (Bool_match + (p + x)) + (delay + (force + Just + x)) + (delay + (force + (go + (delay + (\x -> + x))) + xs)))) + xs) + x))))))) + p))))) + (delay (\arg_0 -> constr 0 [arg_0])) + (delay (constr 1 [])) + (delay + (\x -> + delay + (\case_Just case_Nothing -> + case x [case_Just, case_Nothing])))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList xs)))))))) + (delay + (\x -> + (\x y -> + (\y -> + force ifThenElse + (lessThanInteger x y) + False + True) + y) + x)))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True case_False -> + case x [case_True, case_False]))) + ifThenElse) + lessThanInteger) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden index 369f791ff5a..1303bbe252a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden @@ -1,5 +1,5 @@ -cpu: 5144480 -mem: 20098 -size: 67 +cpu: 12920480 +mem: 68698 +size: 262 (constr 0 (con integer 3)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.pir.golden index f958ac99c46..fed3d1ac82c 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.pir.golden @@ -1,32 +1,74 @@ let + ~v : integer = 4 + !equalsInteger : integer -> integer -> bool = equalsInteger data Bool | Bool_match where True : Bool False : Bool + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + ~equalsInteger : integer -> integer -> Bool + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> + let + !y : integer = y + !b : bool = equalsInteger x y + in + ifThenElse {Bool} b True False + ~`$fEqInteger` : (\a -> a -> a -> Bool) integer = equalsInteger + ~`==` : all a. (\a -> a -> a -> Bool) a -> a -> a -> Bool + = /\a -> \(v : (\a -> a -> a -> Bool) a) -> v + ~v : integer -> integer -> Bool = `==` {integer} `$fEqInteger` data (Maybe :: * -> *) a | Maybe_match where Just : a -> Maybe a Nothing : Maybe a -in -letrec - !go : integer -> list integer -> Maybe integer - = \(i : integer) -> - (let - r = Maybe integer + !addInteger : integer -> integer -> integer = addInteger + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~findIndex : all a. (a -> Bool) -> list a -> Maybe integer + = /\a -> + \(f : a -> Bool) -> + let + !f : a -> Bool = f + in + letrec + ~go : integer -> list a -> Maybe integer + = \(i : integer) -> + let + !i : integer = i + in + caseList' + {a} + {Maybe integer} + (Nothing {integer}) + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + Bool_match + (f x) + {all dead. Maybe integer} + (/\dead -> Just {integer} i) + (/\dead -> go (addInteger i 1) xs) + {all dead. dead}) in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - (Nothing {integer}) - (\(x : integer) (xs : list integer) -> - Bool_match - (ifThenElse {Bool} (equalsInteger 4 x) True False) - {all dead. Maybe integer} - (/\dead -> Just {integer} i) - (/\dead -> go (addInteger 1 i) xs) - {all dead. dead}) + go 0 in -\(xs : list integer) -> go 0 xs \ No newline at end of file +\(xs : list integer) -> + let + !xs : list integer = xs + in + findIndex {integer} (\(v : integer) -> v v v) xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.uplc.golden index bcc1a4f3992..8fb1bfc4c42 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.uplc.golden @@ -1,17 +1,130 @@ (program 1.1.0 - ((\go xs -> go 0 xs) - ((\s -> s s) - (\s i xs -> - force - (force (force chooseList) - xs - (delay (constr 1 [])) - (delay - ((\xs -> - force - (force ifThenElse - (equalsInteger 4 (force headList xs)) - (delay (constr 0 [i])) - (delay ((\x -> s s x) (addInteger 1 i) xs)))) - (force tailList xs)))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + (delay + (\True + False + Bool_match -> + force + (force + (delay + (\Just + Nothing + Maybe_match -> + (\findIndex -> + force findIndex) + (delay + (delay + (\f -> + (\f -> + (\caseList' -> + (\addInteger -> + (\tup -> + (\go -> + (\go -> force go 0) + (go (delay (\x -> x)))) + (force tup + (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (\i -> + (\i -> + force + (force + caseList') + (force + Nothing) + (\x -> + (\x + xs -> + (\xs -> + force + (force + (Bool_match + (f + x)) + (delay + (force + Just + i)) + (delay + (force + (go + (delay + (\x -> + x))) + (addInteger + i + 1) + xs)))) + xs) + x)) + i)))))) + addInteger) + (delay + (delay + (\z f xs -> + force + (force + (force chooseList) + xs + (delay z) + (delay + (f + (force headList + xs) + (force tailList + xs)))))))) + f))))) + (delay (\arg_0 -> constr 0 [arg_0])) + (delay (constr 1 [])) + (delay + (\x -> + delay + (\case_Just case_Nothing -> + case x [case_Just, case_Nothing])))) + (\v -> + (\`==` -> + (\ifThenElse -> + (\equalsInteger -> + (\equalsInteger -> + (\`$fEqInteger` -> + (\v -> force v) + (delay + (force (force `==`) + (force `$fEqInteger`)))) + (delay (force equalsInteger))) + (delay + (\x -> + (\x y -> + (\y -> + (\b -> + force ifThenElse b True False) + (equalsInteger x y)) + y) + x))) + equalsInteger) + ifThenElse) + (delay (delay (\v -> v))) + v + ((\v -> force v) (delay 4))))) + (constr 0 []) + (constr 1 []) + (\x -> + delay (\case_True case_False -> case x [case_True, case_False])) + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden index 11f4c84d736..0f598c161c3 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden @@ -1,5 +1,5 @@ -cpu: 13551064 -mem: 52032 -size: 67 +cpu: 31679064 +mem: 165332 +size: 262 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.pir.golden index 25c92f13699..f1e9efba8b0 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.pir.golden @@ -1,32 +1,74 @@ let + ~v : integer = 99 + !equalsInteger : integer -> integer -> bool = equalsInteger data Bool | Bool_match where True : Bool False : Bool + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + ~equalsInteger : integer -> integer -> Bool + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> + let + !y : integer = y + !b : bool = equalsInteger x y + in + ifThenElse {Bool} b True False + ~`$fEqInteger` : (\a -> a -> a -> Bool) integer = equalsInteger + ~`==` : all a. (\a -> a -> a -> Bool) a -> a -> a -> Bool + = /\a -> \(v : (\a -> a -> a -> Bool) a) -> v + ~v : integer -> integer -> Bool = `==` {integer} `$fEqInteger` data (Maybe :: * -> *) a | Maybe_match where Just : a -> Maybe a Nothing : Maybe a -in -letrec - !go : integer -> list integer -> Maybe integer - = \(i : integer) -> - (let - r = Maybe integer + !addInteger : integer -> integer -> integer = addInteger + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~findIndex : all a. (a -> Bool) -> list a -> Maybe integer + = /\a -> + \(f : a -> Bool) -> + let + !f : a -> Bool = f + in + letrec + ~go : integer -> list a -> Maybe integer + = \(i : integer) -> + let + !i : integer = i + in + caseList' + {a} + {Maybe integer} + (Nothing {integer}) + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + Bool_match + (f x) + {all dead. Maybe integer} + (/\dead -> Just {integer} i) + (/\dead -> go (addInteger i 1) xs) + {all dead. dead}) in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - (Nothing {integer}) - (\(x : integer) (xs : list integer) -> - Bool_match - (ifThenElse {Bool} (equalsInteger 99 x) True False) - {all dead. Maybe integer} - (/\dead -> Just {integer} i) - (/\dead -> go (addInteger 1 i) xs) - {all dead. dead}) + go 0 in -\(xs : list integer) -> go 0 xs \ No newline at end of file +\(xs : list integer) -> + let + !xs : list integer = xs + in + findIndex {integer} (\(v : integer) -> v v v) xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.uplc.golden index 99ad4a6b8d8..e8d19fa4e92 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.uplc.golden @@ -1,17 +1,130 @@ (program 1.1.0 - ((\go xs -> go 0 xs) - ((\s -> s s) - (\s i xs -> - force - (force (force chooseList) - xs - (delay (constr 1 [])) - (delay - ((\xs -> - force - (force ifThenElse - (equalsInteger 99 (force headList xs)) - (delay (constr 0 [i])) - (delay ((\x -> s s x) (addInteger 1 i) xs)))) - (force tailList xs)))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + (delay + (\True + False + Bool_match -> + force + (force + (delay + (\Just + Nothing + Maybe_match -> + (\findIndex -> + force findIndex) + (delay + (delay + (\f -> + (\f -> + (\caseList' -> + (\addInteger -> + (\tup -> + (\go -> + (\go -> force go 0) + (go (delay (\x -> x)))) + (force tup + (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (\i -> + (\i -> + force + (force + caseList') + (force + Nothing) + (\x -> + (\x + xs -> + (\xs -> + force + (force + (Bool_match + (f + x)) + (delay + (force + Just + i)) + (delay + (force + (go + (delay + (\x -> + x))) + (addInteger + i + 1) + xs)))) + xs) + x)) + i)))))) + addInteger) + (delay + (delay + (\z f xs -> + force + (force + (force chooseList) + xs + (delay z) + (delay + (f + (force headList + xs) + (force tailList + xs)))))))) + f))))) + (delay (\arg_0 -> constr 0 [arg_0])) + (delay (constr 1 [])) + (delay + (\x -> + delay + (\case_Just case_Nothing -> + case x [case_Just, case_Nothing])))) + (\v -> + (\`==` -> + (\ifThenElse -> + (\equalsInteger -> + (\equalsInteger -> + (\`$fEqInteger` -> + (\v -> force v) + (delay + (force (force `==`) + (force `$fEqInteger`)))) + (delay (force equalsInteger))) + (delay + (\x -> + (\x y -> + (\y -> + (\b -> + force ifThenElse b True False) + (equalsInteger x y)) + y) + x))) + equalsInteger) + ifThenElse) + (delay (delay (\v -> v))) + v + ((\v -> force v) (delay 99))))) + (constr 0 []) + (constr 1 []) + (\x -> + delay (\case_True case_False -> case x [case_True, case_False])) + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden index 59d0960ad98..39a825dea34 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden @@ -1,5 +1,5 @@ -cpu: 17232174 -mem: 64702 -size: 81 +cpu: 31632174 +mem: 154702 +size: 243 (con (list integer) [0,2,4,6,8]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.pir.golden index 28c9d47971a..a18a73cf484 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.pir.golden @@ -1,41 +1,77 @@ let + !addInteger : integer -> integer -> integer = addInteger + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + !mkCons : all a. a -> list a -> list a = mkCons data Bool | Bool_match where True : Bool False : Bool -in -letrec - !go : integer -> list integer -> list integer - = \(i : integer) -> - (let - r = list integer + ~findIndices : all a. (a -> Bool) -> list a -> list integer + = /\a -> + \(p : a -> Bool) -> + let + !p : a -> Bool = p + in + letrec + ~go : integer -> list a -> list integer + = \(i : integer) -> + let + !i : integer = i + in + caseList' + {a} + {list integer} + [] + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + !indices : list integer = go (addInteger i 1) xs + in + Bool_match + (p x) + {all dead. list integer} + (/\dead -> mkCons {integer} i indices) + (/\dead -> indices) + {all dead. dead}) in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - [] - (\(x : integer) (xs : list integer) -> - let - !indices : list integer = go (addInteger 1 i) xs - in - Bool_match - (Bool_match - (ifThenElse - {Bool} - (equalsInteger 0 (modInteger x 2)) - True - False) - {all dead. Bool} - (/\dead -> False) - (/\dead -> True) - {all dead. dead}) - {all dead. list integer} - (/\dead -> mkCons {integer} i indices) - (/\dead -> indices) - {all dead. dead}) + go 0 + !equalsInteger : integer -> integer -> bool = equalsInteger + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !modInteger : integer -> integer -> integer = modInteger + ~even : integer -> Bool + = \(n : integer) -> + let + !n : integer = n + !x : integer = modInteger n 2 + !b : bool = equalsInteger x 0 + in + ifThenElse {Bool} b True False + ~odd : integer -> Bool + = \(n : integer) -> + let + !n : integer = n + in + Bool_match + (even n) + {all dead. Bool} + (/\dead -> False) + (/\dead -> True) + {all dead. dead} in -\(xs : list integer) -> go 0 xs \ No newline at end of file +\(xs : list integer) -> + let + !xs : list integer = xs + in + findIndices {integer} odd xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.uplc.golden index 9e292caca94..738e6b909d3 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.uplc.golden @@ -1,20 +1,119 @@ (program 1.1.0 - ((\go xs -> go 0 xs) - ((\s -> s s) - (\s i xs -> - force - (force (force chooseList) - xs - (delay []) - (delay - ((\x xs -> - (\indices -> - force - (force ifThenElse - (equalsInteger 0 (modInteger x 2)) - (delay indices) - (delay (force mkCons i indices)))) - ((\x -> s s x) (addInteger 1 i) xs)) - (force headList xs) - (force tailList xs)))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + (delay + (\True + False + Bool_match -> + force + ((\findIndices -> + force findIndices) + (delay + (delay + (\p -> + (\p -> + (\mkCons -> + (\caseList' -> + (\addInteger -> + (\tup -> + (\go -> + (\go -> force go 0) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (\i -> + (\i -> + force + (force + caseList') + [] + (\x -> + (\x + xs -> + (\xs -> + (\indices -> + force + (force + (Bool_match + (p + x)) + (delay + (force + mkCons + i + indices)) + (delay + indices))) + (force + (go + (delay + (\x -> + x))) + (addInteger + i + 1) + xs)) + xs) + x)) + i)))))) + addInteger) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList + xs)))))))) + mkCons) + p)))) + ((\modInteger -> + (\ifThenElse -> + (\equalsInteger -> + (\even -> + (\odd -> force odd) + (delay + (\n -> + (\n -> + force + (force (Bool_match (force even n)) + (delay False) + (delay True))) + n))) + (delay + (\n -> + (\n -> + (\x -> + (\b -> + force ifThenElse b True False) + (equalsInteger x 0)) + (modInteger n 2)) + n))) + equalsInteger) + ifThenElse) + modInteger))) + (constr 0 []) + (constr 1 []) + (\x -> + delay (\case_True case_False -> case x [case_True, case_False])) + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden index c1ae4ce26a0..107e5657664 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden @@ -1,5 +1,5 @@ -cpu: 10564694 -mem: 42012 -size: 55 +cpu: 19108694 +mem: 95412 +size: 179 (con integer 3628800) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.pir.golden index 8c537ad0d3e..9bb2b95c24c 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.pir.golden @@ -1,17 +1,60 @@ -letrec - !go : integer -> list integer -> integer - = \(acc : integer) (xs : list integer) -> - chooseList - {integer} - {all dead. integer} - xs - (/\dead -> acc) - (/\dead -> - let - !x : integer = headList {integer} xs - !xs : list integer = tailList {integer} xs - in - go (multiplyInteger acc x) xs) - {integer} +let + !multiplyInteger : integer -> integer -> integer = multiplyInteger + ~multiplyInteger : integer -> integer -> integer + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> let !y : integer = y in multiplyInteger x y + ~`$fMultiplicativeSemigroupInteger` : (\a -> a -> a -> a) integer + = multiplyInteger + ~`*` : all a. (\a -> a -> a -> a) a -> a -> a -> a + = /\a -> \(v : (\a -> a -> a -> a) a) -> v + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~foldl : all a b. (b -> a -> b) -> b -> list a -> b + = /\a b -> + \(f : b -> a -> b) -> + let + !f : b -> a -> b = f + in + letrec + ~go : b -> list a -> b + = \(acc : b) -> + let + !acc : b = acc + in + caseList' + {a} + {b} + acc + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + go (f acc x) xs) + in + \(eta : b) -> go eta in -\(xs : list integer) -> go 1 xs \ No newline at end of file +\(xs : list integer) -> + let + !xs : list integer = xs + in + foldl + {integer} + {integer} + (`*` {integer} `$fMultiplicativeSemigroupInteger`) + 1 + xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden index 4cb7ba65d72..70c3cdd0d1a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden @@ -1,14 +1,78 @@ (program 1.1.0 - ((\go xs -> go 1 xs) - ((\s -> s s) - (\s acc xs -> - force - (force (force chooseList) - xs - (delay acc) - (delay - ((\x -> - (\xs -> (\x -> s s x) (multiplyInteger acc x) xs) - (force tailList xs)) - (force headList xs)))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + (force + ((\foldl -> + force foldl) + (delay + (delay + (delay + (\f -> + (\f -> + (\caseList' -> + (\tup -> + (\go -> + (\go eta -> force go eta) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (\acc -> + (\acc -> + force + (force caseList') + acc + (\x -> + (\x + xs -> + (\xs -> + force + (go + (delay + (\x -> + x))) + (f + acc + x) + xs) + xs) + x)) + acc)))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList + xs)))))))) + f)))))) + (force ((\`*` -> force `*`) (delay (delay (\v -> v)))) + ((\multiplyInteger -> + (\multiplyInteger -> + (\`$fMultiplicativeSemigroupInteger` -> + force `$fMultiplicativeSemigroupInteger`) + (delay (force multiplyInteger))) + (delay (\x -> (\x y -> (\y -> multiplyInteger x y) y) x))) + multiplyInteger)) + 1 + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden index c4e8898d563..bba173fd542 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden @@ -1,5 +1,5 @@ -cpu: 9179244 -mem: 32712 -size: 44 +cpu: 18203244 +mem: 89112 +size: 174 (con integer 55) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.pir.golden index a12b587ff2a..06f2e9a3583 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.pir.golden @@ -1,13 +1,50 @@ -letrec - !go : list integer -> integer - = \(xs : list integer) -> - chooseList - {integer} - {all dead. integer} - xs - (/\dead -> 0) - (/\dead -> - addInteger (headList {integer} xs) (go (tailList {integer} xs))) - {integer} +let + !addInteger : integer -> integer -> integer = addInteger + ~addInteger : integer -> integer -> integer + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> let !y : integer = y in addInteger x y + ~`$fAdditiveSemigroupInteger` : (\a -> a -> a -> a) integer = addInteger + ~`+` : all a. (\a -> a -> a -> a) a -> a -> a -> a + = /\a -> \(v : (\a -> a -> a -> a) a) -> v + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~foldr : all a b. (a -> b -> b) -> b -> list a -> b + = /\a b -> + \(f : a -> b -> b) -> + let + !f : a -> b -> b = f + in + \(acc : b) -> + let + !acc : b = acc + in + letrec + ~go : list a -> b + = caseList' + {a} + {b} + acc + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> let !xs : list a = xs in f x (go xs)) + in + go in -\(xs : list integer) -> go xs \ No newline at end of file +\(xs : list integer) -> + let + !xs : list integer = xs + in + foldr {integer} {integer} (`+` {integer} `$fAdditiveSemigroupInteger`) 0 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.uplc.golden index fe0abf441a2..1d7dd967a92 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.uplc.golden @@ -1,13 +1,77 @@ (program 1.1.0 - ((\go xs -> go xs) - ((\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay 0) - (delay - (addInteger - (force headList xs) - ((\x -> s s x) (force tailList xs))))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + (force + ((\foldr -> + force foldr) + (delay + (delay + (delay + (\f -> + (\f + acc -> + (\acc -> + (\caseList' -> + (\tup -> + (\go -> + (\go -> force go) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force caseList') + acc + (\x -> + (\x + xs -> + (\xs -> + f + x + (force + (go + (delay + (\x -> + x))) + xs)) + xs) + x))))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList + xs)))))))) + acc) + f)))))) + (force ((\`+` -> force `+`) (delay (delay (\v -> v)))) + ((\addInteger -> + (\addInteger -> + (\`$fAdditiveSemigroupInteger` -> + force `$fAdditiveSemigroupInteger`) + (delay (force addInteger))) + (delay (\x -> (\x y -> (\y -> addInteger x y) y) x))) + addInteger)) + 0 + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.pir.golden index ba3a37864af..5d499b837f1 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.pir.golden @@ -1,24 +1,67 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] + ~mkNil : all arep. (\arep -> list arep) arep -> list arep + = /\arep -> \(v : (\arep -> list arep) arep) -> v + ~empty : all a. (\arep -> list arep) a -> list a = mkNil + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} data Unit | Unit_match where Unit : Unit + ~caseList : all a r. (Unit -> r) -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(nilCase : Unit -> r) -> + let + !nilCase : Unit -> r = nilCase + in + \(consCase : a -> list a -> r) -> + let + !consCase : a -> list a -> r = consCase + in + \(l : list a) -> + let + !l : list a = l + in + caseList' + {a} + {Unit -> r} + nilCase + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + \(ds : Unit) -> consCase x xs) + l + Unit + ~headEmptyBuiltinListError : string = "PT23" + !error : all a. unit -> a = /\a -> \(thunk : unit) -> error {a} + !trace : all a. string -> a -> a = trace + !unitval : unit = () + ~traceError : all a. string -> a + = /\a -> + \(str : string) -> + let + !str : string = str + !x : Unit = trace {Unit} str Unit + in + error {a} unitval + ~head : all a. list a -> a + = /\a -> + caseList + {a} + {a} + (\(ds : Unit) -> traceError {a} headEmptyBuiltinListError) + (\(x : a) -> let !x : a = x in \(ds : list a) -> x) in -\(ds : list integer) -> - (let - r = Unit -> integer - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - (\(ds : Unit) -> - let - !x : Unit = trace {Unit} "PT23" Unit - in - error {integer}) - (\(x : integer) (xs : list integer) (ds : Unit) -> x) - [] - Unit \ No newline at end of file +\(ds : list integer) -> head {integer} (empty {integer} `$fMkNilInteger`) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.uplc.golden index 793b96b43d4..663629ecaed 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.uplc.golden @@ -2,8 +2,89 @@ 1.1.0 (\ds -> force - (force (force chooseList) - [] - (delay (\ds -> (\x -> error) (force trace "PT23" (constr 0 [])))) - (delay ((\x xs ds -> x) (force headList []) (force tailList [])))) - (constr 0 []))) \ No newline at end of file + ((\head -> + force head) + (delay + (delay + (force + (delay + (\Unit + Unit_match -> + force + (force + ((\caseList -> + force caseList) + (delay + (delay + (delay + (\nilCase -> + (\nilCase + consCase -> + (\consCase + l -> + (\l -> + force + (force + ((\caseList' -> + caseList') + (delay + (delay + (\z + f + xs -> + force + (force + (force + chooseList) + xs + (delay + z) + (delay + (f + (force + headList + xs) + (force + tailList + xs))))))))) + nilCase + (\x -> + (\x xs -> + (\xs ds -> + consCase x xs) + xs) + x) + l + Unit) + l) + consCase) + nilCase)))))) + (\ds -> + force + ((\unitval -> + (\trace -> + (\error -> + (\traceError -> force traceError) + (delay + (delay + (\str -> + (\str -> + (\x -> + force error unitval) + (force trace + str + Unit)) + str)))) + (delay (\thunk -> error))) + trace) + ()) + ((\headEmptyBuiltinListError -> + force headEmptyBuiltinListError) + (delay "PT23"))))) + (constr 0 []) + (\x -> delay (\case_Unit -> case x [case_Unit])) + (\x -> (\x ds -> x) x))))) + (force + ((\mkNil -> (\empty -> force empty) (delay (force mkNil))) + (delay (delay (\v -> v)))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay []))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden index 80fd21ad390..b8a7fce99d3 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden @@ -1,5 +1,5 @@ -cpu: 761907 -mem: 3096 -size: 39 +cpu: 1977907 +mem: 10696 +size: 152 (con integer 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.pir.golden index de4295e6e50..bd57f7148f7 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.pir.golden @@ -1,24 +1,63 @@ let + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} data Unit | Unit_match where Unit : Unit + ~caseList : all a r. (Unit -> r) -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(nilCase : Unit -> r) -> + let + !nilCase : Unit -> r = nilCase + in + \(consCase : a -> list a -> r) -> + let + !consCase : a -> list a -> r = consCase + in + \(l : list a) -> + let + !l : list a = l + in + caseList' + {a} + {Unit -> r} + nilCase + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + \(ds : Unit) -> consCase x xs) + l + Unit + ~headEmptyBuiltinListError : string = "PT23" + !error : all a. unit -> a = /\a -> \(thunk : unit) -> error {a} + !trace : all a. string -> a -> a = trace + !unitval : unit = () + ~traceError : all a. string -> a + = /\a -> + \(str : string) -> + let + !str : string = str + !x : Unit = trace {Unit} str Unit + in + error {a} unitval + ~head : all a. list a -> a + = /\a -> + caseList + {a} + {a} + (\(ds : Unit) -> traceError {a} headEmptyBuiltinListError) + (\(x : a) -> let !x : a = x in \(ds : list a) -> x) in -\(xs : list integer) -> - (let - r = Unit -> integer - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - (\(ds : Unit) -> - let - !x : Unit = trace {Unit} "PT23" Unit - in - error {integer}) - (\(x : integer) (xs : list integer) (ds : Unit) -> x) - xs - Unit \ No newline at end of file +\(xs : list integer) -> let !xs : list integer = xs in head {integer} xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.uplc.golden index 8a8d6b52439..1a0d4edaa2a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.uplc.golden @@ -1,9 +1,92 @@ (program 1.1.0 (\xs -> - force - (force (force chooseList) - xs - (delay (\ds -> (\x -> error) (force trace "PT23" (constr 0 [])))) - (delay ((\x xs ds -> x) (force headList xs) (force tailList xs)))) - (constr 0 []))) \ No newline at end of file + (\xs -> + force + ((\head -> + force head) + (delay + (delay + (force + (delay + (\Unit + Unit_match -> + force + (force + ((\caseList -> + force caseList) + (delay + (delay + (delay + (\nilCase -> + (\nilCase + consCase -> + (\consCase + l -> + (\l -> + force + (force + ((\caseList' -> + caseList') + (delay + (delay + (\z + f + xs -> + force + (force + (force + chooseList) + xs + (delay + z) + (delay + (f + (force + headList + xs) + (force + tailList + xs))))))))) + nilCase + (\x -> + (\x xs -> + (\xs ds -> + consCase + x + xs) + xs) + x) + l + Unit) + l) + consCase) + nilCase)))))) + (\ds -> + force + ((\unitval -> + (\trace -> + (\error -> + (\traceError -> force traceError) + (delay + (delay + (\str -> + (\str -> + (\x -> + force error + unitval) + (force trace + str + Unit)) + str)))) + (delay (\thunk -> error))) + trace) + ()) + ((\headEmptyBuiltinListError -> + force headEmptyBuiltinListError) + (delay "PT23"))))) + (constr 0 []) + (\x -> delay (\case_Unit -> case x [case_Unit])) + (\x -> (\x ds -> x) x))))) + xs) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden index 4c3ae70e13c..e4db0f2b557 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden @@ -1,5 +1,5 @@ -cpu: 1064403 -mem: 4200 -size: 50 +cpu: 2945742 +mem: 15202 +size: 196 (con integer 6) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden index a8b60f469a2..4d07729ee13 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.pir.golden @@ -2,30 +2,66 @@ let data Bool | Bool_match where True : Bool False : Bool + ~builtinListIndexTooLargeError : string = "PT22" + ~builtinListNegativeIndexError : string = "PT21" + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + !drop : all a. integer -> list a -> list a = dropList + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanInteger : integer -> integer -> bool = lessThanInteger data Unit | Unit_match where Unit : Unit + !error : all a. unit -> a = /\a -> \(thunk : unit) -> error {a} + !trace : all a. string -> a -> a = trace + !unitval : unit = () + ~traceError : all a. string -> a + = /\a -> + \(str : string) -> + let + !str : string = str + !x : Unit = trace {Unit} str Unit + in + error {a} unitval + ~`!!` : all a. list a -> integer -> a + = /\a -> + \(xs : list a) -> + let + !xs : list a = xs + in + \(i : integer) -> + let + !i : integer = i + !b : bool = lessThanInteger i 0 + in + Bool_match + (ifThenElse {Bool} b True False) + {all dead. a} + (/\dead -> traceError {a} builtinListNegativeIndexError) + (/\dead -> + let + !l : list a = drop {a} i xs + in + caseList' + {a} + {Unit -> Unit -> a} + (\(_ann : Unit) -> + traceError {Unit -> a} builtinListIndexTooLargeError) + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) (ds : Unit) (_ann : Unit) -> x) + l + Unit + Unit) + {all dead. dead} in -\(xs : list integer) -> - let - !l : list integer = dropList {integer} 5 xs - in - (let - r = Unit -> Unit -> integer - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - (\(_ann : Unit) -> - let - !x : Unit = trace {Unit} "PT22" Unit - in - error {Unit -> integer}) - (\(x : integer) (xs : list integer) (ds : Unit) (_ann : Unit) -> x) - l - Unit - Unit \ No newline at end of file +\(xs : list integer) -> let !xs : list integer = xs in `!!` {integer} xs 5 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden index b6edaa999fd..a545d303924 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden @@ -1,14 +1,135 @@ (program 1.1.0 (\xs -> - (\l -> + (\xs -> force - (force (force chooseList) - l + ((\`!!` -> + force `!!`) (delay - (\_ann -> (\x -> error) (force trace "PT22" (constr 0 [])))) - (delay - ((\x xs ds _ann -> x) (force headList l) (force tailList l)))) - (constr 0 []) - (constr 0 [])) - (force dropList 5 xs))) \ No newline at end of file + (delay + (\xs -> + (\xs + i -> + (\i -> + (\b -> + force + ((\unitval -> + (\trace -> + (\error -> + force + (delay + (\Unit + Unit_match -> + (\traceError -> + force + (force + (delay + (\True + False + Bool_match -> + Bool_match + (force + ((\ifThenElse -> + ifThenElse) + ifThenElse) + b + True + False))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True + case_False -> + case + x + [ case_True + , case_False ]))) + (delay + (force + (force + traceError) + ((\builtinListNegativeIndexError -> + force + builtinListNegativeIndexError) + (delay + "PT21")))) + (delay + ((\l -> + force + (force + ((\caseList' -> + caseList') + (delay + (delay + (\z + f + xs -> + force + (force + (force + chooseList) + xs + (delay + z) + (delay + (f + (force + headList + xs) + (force + tailList + xs))))))))) + (\_ann -> + force + (force + traceError) + ((\builtinListIndexTooLargeError -> + force + builtinListIndexTooLargeError) + (delay + "PT22"))) + (\x -> + (\x + xs + ds + _ann -> + x) + x) + l + Unit + Unit) + (force + ((\drop -> + drop) + dropList) + i + xs)))) + (delay + (delay + (\str -> + (\str -> + (\x -> + force error + unitval) + (force trace + str + Unit)) + str))))) + (constr 0 []) + (\x -> + delay + (\case_Unit -> + case x [case_Unit]))) + (delay (\thunk -> error))) + trace) + ())) + ((\lessThanInteger -> lessThanInteger) + lessThanInteger + i + 0)) + i) + xs)))) + xs + 5) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.pir.golden index 8595d7bfcc1..73aa369442a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.pir.golden @@ -2,11 +2,71 @@ let data Bool | Bool_match where True : Bool False : Bool + ~builtinListIndexTooLargeError : string = "PT22" + ~builtinListNegativeIndexError : string = "PT21" + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + !drop : all a. integer -> list a -> list a = dropList + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanInteger : integer -> integer -> bool = lessThanInteger data Unit | Unit_match where Unit : Unit + !error : all a. unit -> a = /\a -> \(thunk : unit) -> error {a} + !trace : all a. string -> a -> a = trace + !unitval : unit = () + ~traceError : all a. string -> a + = /\a -> + \(str : string) -> + let + !str : string = str + !x : Unit = trace {Unit} str Unit + in + error {a} unitval + ~`!!` : all a. list a -> integer -> a + = /\a -> + \(xs : list a) -> + let + !xs : list a = xs + in + \(i : integer) -> + let + !i : integer = i + !b : bool = lessThanInteger i 0 + in + Bool_match + (ifThenElse {Bool} b True False) + {all dead. a} + (/\dead -> traceError {a} builtinListNegativeIndexError) + (/\dead -> + let + !l : list a = drop {a} i xs + in + caseList' + {a} + {Unit -> Unit -> a} + (\(_ann : Unit) -> + traceError {Unit -> a} builtinListIndexTooLargeError) + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) (ds : Unit) (_ann : Unit) -> x) + l + Unit + Unit) + {all dead. dead} + !integerNegate : integer -> integer = \(x : integer) -> subtractInteger 0 x in \(xs : list integer) -> let - !x : Unit = trace {Unit} "PT21" Unit + !xs : list integer = xs in - error {integer} \ No newline at end of file + `!!` {integer} xs (integerNegate 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden index 59f1aaeb038..b5f18a18e88 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden @@ -1 +1,135 @@ -(program 1.1.0 (\xs -> (\x -> error) (force trace "PT21" (constr 0 [])))) \ No newline at end of file +(program + 1.1.0 + (\xs -> + (\xs -> + force + ((\`!!` -> + force `!!`) + (delay + (delay + (\xs -> + (\xs + i -> + (\i -> + (\b -> + force + ((\unitval -> + (\trace -> + (\error -> + force + (delay + (\Unit + Unit_match -> + (\traceError -> + force + (force + (delay + (\True + False + Bool_match -> + Bool_match + (force + ((\ifThenElse -> + ifThenElse) + ifThenElse) + b + True + False))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True + case_False -> + case + x + [ case_True + , case_False ]))) + (delay + (force + (force + traceError) + ((\builtinListNegativeIndexError -> + force + builtinListNegativeIndexError) + (delay + "PT21")))) + (delay + ((\l -> + force + (force + ((\caseList' -> + caseList') + (delay + (delay + (\z + f + xs -> + force + (force + (force + chooseList) + xs + (delay + z) + (delay + (f + (force + headList + xs) + (force + tailList + xs))))))))) + (\_ann -> + force + (force + traceError) + ((\builtinListIndexTooLargeError -> + force + builtinListIndexTooLargeError) + (delay + "PT22"))) + (\x -> + (\x + xs + ds + _ann -> + x) + x) + l + Unit + Unit) + (force + ((\drop -> + drop) + dropList) + i + xs)))) + (delay + (delay + (\str -> + (\str -> + (\x -> + force error + unitval) + (force trace + str + Unit)) + str))))) + (constr 0 []) + (\x -> + delay + (\case_Unit -> + case x [case_Unit]))) + (delay (\thunk -> error))) + trace) + ())) + ((\lessThanInteger -> lessThanInteger) + lessThanInteger + i + 0)) + i) + xs)))) + xs + ((\integerNegate -> integerNegate) (\x -> subtractInteger 0 x) 1)) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.pir.golden index 3bc9c55b6eb..6800dac0f2e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.pir.golden @@ -2,30 +2,66 @@ let data Bool | Bool_match where True : Bool False : Bool + ~builtinListIndexTooLargeError : string = "PT22" + ~builtinListNegativeIndexError : string = "PT21" + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + !drop : all a. integer -> list a -> list a = dropList + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanInteger : integer -> integer -> bool = lessThanInteger data Unit | Unit_match where Unit : Unit + !error : all a. unit -> a = /\a -> \(thunk : unit) -> error {a} + !trace : all a. string -> a -> a = trace + !unitval : unit = () + ~traceError : all a. string -> a + = /\a -> + \(str : string) -> + let + !str : string = str + !x : Unit = trace {Unit} str Unit + in + error {a} unitval + ~`!!` : all a. list a -> integer -> a + = /\a -> + \(xs : list a) -> + let + !xs : list a = xs + in + \(i : integer) -> + let + !i : integer = i + !b : bool = lessThanInteger i 0 + in + Bool_match + (ifThenElse {Bool} b True False) + {all dead. a} + (/\dead -> traceError {a} builtinListNegativeIndexError) + (/\dead -> + let + !l : list a = drop {a} i xs + in + caseList' + {a} + {Unit -> Unit -> a} + (\(_ann : Unit) -> + traceError {Unit -> a} builtinListIndexTooLargeError) + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) (ds : Unit) (_ann : Unit) -> x) + l + Unit + Unit) + {all dead. dead} in -\(xs : list integer) -> - let - !l : list integer = dropList {integer} 10 xs - in - (let - r = Unit -> Unit -> integer - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - (\(_ann : Unit) -> - let - !x : Unit = trace {Unit} "PT22" Unit - in - error {Unit -> integer}) - (\(x : integer) (xs : list integer) (ds : Unit) (_ann : Unit) -> x) - l - Unit - Unit \ No newline at end of file +\(xs : list integer) -> let !xs : list integer = xs in `!!` {integer} xs 10 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden index 5e3af4cfb84..969b4dae2b5 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden @@ -1,14 +1,135 @@ (program 1.1.0 (\xs -> - (\l -> + (\xs -> force - (force (force chooseList) - l + ((\`!!` -> + force `!!`) (delay - (\_ann -> (\x -> error) (force trace "PT22" (constr 0 [])))) - (delay - ((\x xs ds _ann -> x) (force headList l) (force tailList l)))) - (constr 0 []) - (constr 0 [])) - (force dropList 10 xs))) \ No newline at end of file + (delay + (\xs -> + (\xs + i -> + (\i -> + (\b -> + force + ((\unitval -> + (\trace -> + (\error -> + force + (delay + (\Unit + Unit_match -> + (\traceError -> + force + (force + (delay + (\True + False + Bool_match -> + Bool_match + (force + ((\ifThenElse -> + ifThenElse) + ifThenElse) + b + True + False))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True + case_False -> + case + x + [ case_True + , case_False ]))) + (delay + (force + (force + traceError) + ((\builtinListNegativeIndexError -> + force + builtinListNegativeIndexError) + (delay + "PT21")))) + (delay + ((\l -> + force + (force + ((\caseList' -> + caseList') + (delay + (delay + (\z + f + xs -> + force + (force + (force + chooseList) + xs + (delay + z) + (delay + (f + (force + headList + xs) + (force + tailList + xs))))))))) + (\_ann -> + force + (force + traceError) + ((\builtinListIndexTooLargeError -> + force + builtinListIndexTooLargeError) + (delay + "PT22"))) + (\x -> + (\x + xs + ds + _ann -> + x) + x) + l + Unit + Unit) + (force + ((\drop -> + drop) + dropList) + i + xs)))) + (delay + (delay + (\str -> + (\str -> + (\x -> + force error + unitval) + (force trace + str + Unit)) + str))))) + (constr 0 []) + (\x -> + delay + (\case_Unit -> + case x [case_Unit]))) + (delay (\thunk -> error))) + trace) + ())) + ((\lessThanInteger -> lessThanInteger) + lessThanInteger + i + 0)) + i) + xs)))) + xs + 10) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.pir.golden index 9033db2f166..bfd724a9d8f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.pir.golden @@ -1,4 +1,8 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] + ~mkNil : all arep. (\arep -> list arep) arep -> list arep + = /\arep -> \(v : (\arep -> list arep) arep) -> v + ~empty : all a. (\arep -> list arep) a -> list a = mkNil !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r = /\a r -> \(z : r) (f : a -> list a -> r) (xs : list a) -> @@ -11,22 +15,63 @@ let {r} data Unit | Unit_match where Unit : Unit + ~caseList : all a r. (Unit -> r) -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(nilCase : Unit -> r) -> + let + !nilCase : Unit -> r = nilCase + in + \(consCase : a -> list a -> r) -> + let + !consCase : a -> list a -> r = consCase + in + \(l : list a) -> + let + !l : list a = l + in + caseList' + {a} + {Unit -> r} + nilCase + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + \(ds : Unit) -> consCase x xs) + l + Unit + ~lastEmptyBuiltinListError : string = "PT25" + !error : all a. unit -> a = /\a -> \(thunk : unit) -> error {a} + !trace : all a. string -> a -> a = trace + !unitval : unit = () + ~traceError : all a. string -> a + = /\a -> + \(str : string) -> + let + !str : string = str + !x : Unit = trace {Unit} str Unit + in + error {a} unitval in letrec - !last : all a. list a -> a + ~last : all a. list a -> a = /\a -> - \(l : list a) -> - caseList' - {a} - {Unit -> a} - (\(ds : Unit) -> + caseList + {a} + {a} + (\(ds : Unit) -> traceError {a} lastEmptyBuiltinListError) + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> let - !x : Unit = trace {Unit} "PT25" Unit + !xs : list a = xs in - error {a}) - (\(x : a) (xs : list a) (ds : Unit) -> caseList' {a} {a} x (\(ds : a) (ds : list a) -> last {a} xs) xs) - l - Unit in -\(ds : list integer) -> last {integer} [] \ No newline at end of file +\(ds : list integer) -> last {integer} (empty {integer} `$fMkNilInteger`) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden index e9503910195..9a0fad96a0b 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden @@ -1,24 +1,110 @@ (program 1.1.0 - ((\caseList' -> - (\last ds -> force last []) - ((\s -> s s) - (\s arg -> - delay - (\l -> - caseList' - (\ds -> (\x -> error) (force trace "PT25" (constr 0 []))) - (\x xs ds -> - caseList' - x - (\ds ds -> force (s s (delay (\x -> x))) xs) - xs) - l - (constr 0 []))) - (delay (\x -> x)))) - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file + ((\fix1 -> + force + (delay + (\Unit + Unit_match -> + (\traceError -> + (\lastEmptyBuiltinListError -> + (\caseList' -> + (\caseList -> + (\empty -> + (\`$fMkNilInteger` -> + (\tup -> + (\last -> + (\last ds -> + force (force last) + (force (force empty) + (force `$fMkNilInteger`))) + (last (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\last + arg -> + delay + (delay + (force + (force + (force caseList)) + (\ds -> + force + (force traceError) + (force + lastEmptyBuiltinListError)) + (\x -> + (\x + xs -> + (\xs -> + force + (force + caseList') + x + (\ds + ds -> + force + (force + (last + (delay + (\x -> + x)))) + xs) + xs) + xs) + x)))))))) + (delay [])) + (delay + ((\mkNil -> force mkNil) + (delay (delay (\v -> v)))))) + (delay + (delay + (delay + (\nilCase -> + (\nilCase consCase -> + (\consCase l -> + (\l -> + force (force caseList') + nilCase + (\x -> + (\x xs -> + (\xs ds -> consCase x xs) + xs) + x) + l + Unit) + l) + consCase) + nilCase))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList xs)))))))) + (delay "PT25")) + (delay + (delay + (\str -> + (\str -> + (\x -> + force + ((\error -> error) (delay (\thunk -> error))) + ((\unitval -> unitval) ())) + (force ((\trace -> trace) trace) str Unit)) + str))))) + (constr 0 []) + (\x -> delay (\case_Unit -> case x [case_Unit]))) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden index 9303a55d91e..e8fe43350d0 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden @@ -1,5 +1,5 @@ -cpu: 17967427 -mem: 78056 -size: 87 +cpu: 28175427 +mem: 141856 +size: 223 (con integer 10) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.pir.golden index 22c3a114a04..23be0f4d65d 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.pir.golden @@ -11,22 +11,63 @@ let {r} data Unit | Unit_match where Unit : Unit + ~caseList : all a r. (Unit -> r) -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(nilCase : Unit -> r) -> + let + !nilCase : Unit -> r = nilCase + in + \(consCase : a -> list a -> r) -> + let + !consCase : a -> list a -> r = consCase + in + \(l : list a) -> + let + !l : list a = l + in + caseList' + {a} + {Unit -> r} + nilCase + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + \(ds : Unit) -> consCase x xs) + l + Unit + ~lastEmptyBuiltinListError : string = "PT25" + !error : all a. unit -> a = /\a -> \(thunk : unit) -> error {a} + !trace : all a. string -> a -> a = trace + !unitval : unit = () + ~traceError : all a. string -> a + = /\a -> + \(str : string) -> + let + !str : string = str + !x : Unit = trace {Unit} str Unit + in + error {a} unitval in letrec - !last : all a. list a -> a + ~last : all a. list a -> a = /\a -> - \(l : list a) -> - caseList' - {a} - {Unit -> a} - (\(ds : Unit) -> + caseList + {a} + {a} + (\(ds : Unit) -> traceError {a} lastEmptyBuiltinListError) + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> let - !x : Unit = trace {Unit} "PT25" Unit + !xs : list a = xs in - error {a}) - (\(x : a) (xs : list a) (ds : Unit) -> caseList' {a} {a} x (\(ds : a) (ds : list a) -> last {a} xs) xs) - l - Unit in -\(xs : list integer) -> last {integer} xs \ No newline at end of file +\(xs : list integer) -> let !xs : list integer = xs in last {integer} xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden index a2aff3024b6..5c3bdbf0016 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden @@ -1,24 +1,99 @@ (program 1.1.0 - ((\caseList' -> - (\last xs -> force last xs) - ((\s -> s s) - (\s arg -> - delay - (\l -> - caseList' - (\ds -> (\x -> error) (force trace "PT25" (constr 0 []))) - (\x xs ds -> - caseList' - x - (\ds ds -> force (s s (delay (\x -> x))) xs) - xs) - l - (constr 0 []))) - (delay (\x -> x)))) - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file + ((\fix1 -> + force + (delay + (\Unit + Unit_match -> + (\traceError -> + (\lastEmptyBuiltinListError -> + (\caseList' -> + (\caseList -> + (\tup -> + (\last -> + (\last xs -> (\xs -> force (force last) xs) xs) + (last (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\last + arg -> + delay + (delay + (force + (force (force caseList)) + (\ds -> + force + (force traceError) + (force + lastEmptyBuiltinListError)) + (\x -> + (\x + xs -> + (\xs -> + force + (force caseList') + x + (\ds + ds -> + force + (force + (last + (delay + (\x -> + x)))) + xs) + xs) + xs) + x)))))))) + (delay + (delay + (delay + (\nilCase -> + (\nilCase consCase -> + (\consCase l -> + (\l -> + force (force caseList') + nilCase + (\x -> + (\x xs -> + (\xs ds -> consCase x xs) + xs) + x) + l + Unit) + l) + consCase) + nilCase))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList xs)))))))) + (delay "PT25")) + (delay + (delay + (\str -> + (\str -> + (\x -> + force + ((\error -> error) (delay (\thunk -> error))) + ((\unitval -> unitval) ())) + (force ((\trace -> trace) trace) str Unit)) + str))))) + (constr 0 []) + (\x -> delay (\case_Unit -> case x [case_Unit]))) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden index 0ff2611645b..0aa1922b1c3 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden @@ -1,5 +1,5 @@ -cpu: 9659244 -mem: 35712 -size: 47 +cpu: 15739244 +mem: 73712 +size: 128 (con integer 10) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.pir.golden index d008c120106..e47a5bc4e06 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.pir.golden @@ -1,16 +1,30 @@ -letrec - !go : list integer -> integer - = \(xs : list integer) -> - chooseList - {integer} - {all dead. integer} - xs - (/\dead -> 0) - (/\dead -> - let - !x : integer = headList {integer} xs - in - addInteger 1 (go (tailList {integer} xs))) - {integer} +let + !addInteger : integer -> integer -> integer = addInteger + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~length : all a. list a -> integer + = /\a -> + letrec + ~go : list a -> integer + = caseList' + {a} + {integer} + 0 + (\(x : a) (xs : list a) -> + let + !xs : list a = xs + !y : integer = go xs + in + addInteger 1 y) + in + go in -\(xs : list integer) -> go xs \ No newline at end of file +\(xs : list integer) -> let !xs : list integer = xs in length {integer} xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.uplc.golden index 51889e0d1ec..5cb666693bf 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.uplc.golden @@ -1,12 +1,49 @@ (program 1.1.0 - ((\go xs -> go xs) - ((\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay 0) - (delay - ((\x -> addInteger 1 ((\x -> s s x) (force tailList xs))) - (force headList xs)))))))) \ No newline at end of file + ((\fix1 xs -> + (\xs -> + force + ((\length -> force length) + (delay + (delay + ((\caseList' -> + (\addInteger -> + (\tup -> + (\go -> (\go -> force go) (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force (force fix1) + (\go arg -> + delay + (force (force caseList') + 0 + (\x xs -> + (\xs -> + (\y -> addInteger 1 y) + (force + (go + (delay + (\x -> x))) + xs)) + xs))))))) + addInteger) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList xs))))))))))) + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden index c51ab8f5ceb..e256823f282 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden @@ -1,5 +1,5 @@ -cpu: 681907 -mem: 2596 -size: 25 +cpu: 1481907 +mem: 7596 +size: 83 (constr 0 (con integer 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.pir.golden index e3b39197e86..24023910697 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.pir.golden @@ -2,19 +2,22 @@ let data (Maybe :: * -> *) a | Maybe_match where Just : a -> Maybe a Nothing : Maybe a + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~listToMaybe : all a. list a -> Maybe a + = /\a -> + caseList' + {a} + {Maybe a} + (Nothing {a}) + (\(x : a) -> let !x : a = x in \(ds : list a) -> Just {a} x) in -\(xs : list integer) -> - (let - r = Maybe integer - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - (Nothing {integer}) - (\(x : integer) (ds : list integer) -> Just {integer} x) - xs \ No newline at end of file +\(xs : list integer) -> let !xs : list integer = xs in listToMaybe {integer} xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.uplc.golden index 6e71d21bd03..d2c935ac931 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.uplc.golden @@ -1,9 +1,37 @@ (program 1.1.0 (\xs -> - force - (force (force chooseList) - xs - (delay (constr 1 [])) - (delay - ((\ds -> constr 0 [(force headList xs)]) (force tailList xs)))))) \ No newline at end of file + (\xs -> + force + (force + (delay + (\Just Nothing Maybe_match -> + (\listToMaybe -> force listToMaybe) + (delay + (delay + (force + (force + ((\caseList' -> caseList') + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList + xs))))))))) + (force Nothing) + (\x -> (\x ds -> force Just x) x)))))) + (delay (\arg_0 -> constr 0 [arg_0])) + (delay (constr 1 [])) + (delay + (\x -> + delay + (\case_Just case_Nothing -> + case x [case_Just, case_Nothing])))) + xs) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden index 6eec30a642f..033a1106036 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden @@ -1,5 +1,5 @@ -cpu: 357094 -mem: 1532 -size: 25 +cpu: 1253094 +mem: 7132 +size: 100 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.pir.golden index d5b9c329d17..8afe104e508 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.pir.golden @@ -1,20 +1,27 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] + ~mkNil : all arep. (\arep -> list arep) arep -> list arep + = /\arep -> \(v : (\arep -> list arep) arep) -> v + ~empty : all a. (\arep -> list arep) a -> list a = mkNil data (Maybe :: * -> *) a | Maybe_match where Just : a -> Maybe a Nothing : Maybe a + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~listToMaybe : all a. list a -> Maybe a + = /\a -> + caseList' + {a} + {Maybe a} + (Nothing {a}) + (\(x : a) -> let !x : a = x in \(ds : list a) -> Just {a} x) in -\(ds : list integer) -> - (let - r = Maybe integer - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - (Nothing {integer}) - (\(x : integer) (ds : list integer) -> Just {integer} x) - [] \ No newline at end of file +\(ds : list integer) -> listToMaybe {integer} (empty {integer} `$fMkNilInteger`) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.uplc.golden index 65216008d85..fe4672ddd54 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.uplc.golden @@ -2,8 +2,37 @@ 1.1.0 (\ds -> force - (force (force chooseList) - [] + (force + (delay + (\Just Nothing Maybe_match -> + (\listToMaybe -> force listToMaybe) + (delay + (delay + (force + (force + ((\caseList' -> caseList') + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList + xs))))))))) + (force Nothing) + (\x -> (\x ds -> force Just x) x)))))) + (delay (\arg_0 -> constr 0 [arg_0])) (delay (constr 1 [])) (delay - ((\ds -> constr 0 [(force headList [])]) (force tailList [])))))) \ No newline at end of file + (\x -> + delay + (\case_Just case_Nothing -> + case x [case_Just, case_Nothing])))) + (force + ((\mkNil -> (\empty -> force empty) (delay (force mkNil))) + (delay (delay (\v -> v)))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay []))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.eval.golden index 1e72d768921..590009edd5e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.eval.golden @@ -1,5 +1,5 @@ -cpu: 10606864 -mem: 37432 -size: 43 +cpu: 25102864 +mem: 128032 +size: 191 (con (list integer) [2,3,4,5,6,7,8,9,10,11]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.pir.golden index d5fd356b0b5..b653ee1a90b 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.pir.golden @@ -1,18 +1,51 @@ -letrec - !go : list integer -> list integer - = (let - r = list integer +let + ~v : integer = 1 + !addInteger : integer -> integer -> integer = addInteger + ~addInteger : integer -> integer -> integer + = \(x : integer) -> + let + !x : integer = x in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + \(y : integer) -> let !y : integer = y in addInteger x y + ~`$fAdditiveSemigroupInteger` : (\a -> a -> a -> a) integer = addInteger + ~`+` : all a. (\a -> a -> a -> a) a -> a -> a -> a + = /\a -> \(v : (\a -> a -> a -> a) a) -> v + ~v : integer -> integer -> integer + = `+` {integer} `$fAdditiveSemigroupInteger` + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> chooseList - {integer} + {a} {all dead. r} xs (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - [] - (\(x : integer) (xs : list integer) -> - mkCons {integer} (addInteger 1 x) (go xs)) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + !mkCons : all a. a -> list a -> list a = mkCons + ~map : all a b. (\arep -> list arep) b -> (a -> b) -> list a -> list b + = /\a b -> + \(`$dMkNil` : (\arep -> list arep) b) (f : a -> b) -> + let + !f : a -> b = f + in + letrec + ~go : list a -> list b + = caseList' + {a} + {list b} + `$dMkNil` + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + mkCons {b} (f x) (go xs)) + in + go in -go \ No newline at end of file +map {integer} {integer} `$fMkNilInteger` (\(v : integer) -> v v v) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden index 124103bfe9f..7f5be9f7c48 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden @@ -1,12 +1,81 @@ (program 1.1.0 - ((\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay []) - (delay - ((\xs -> - force mkCons (addInteger 1 (force headList xs)) (s s xs)) - (force tailList xs))))))) \ No newline at end of file + ((\fix1 -> + force + (force + ((\map -> + force map) + (delay + (delay + (delay + (\`$dMkNil` + f -> + (\f -> + (\mkCons -> + (\caseList' -> + (\tup -> + (\go -> + (\go -> force go) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force caseList') + `$dMkNil` + (\x -> + (\x + xs -> + (\xs -> + force + mkCons + (f x) + (force + (go + (delay + (\x -> + x))) + xs)) + xs) + x))))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList + xs)))))))) + mkCons) + f)))))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) + (\v -> + (\`+` -> + (\addInteger -> + (\addInteger -> + (\`$fAdditiveSemigroupInteger` -> + (\v -> force v) + (delay + (force (force `+`) + (force `$fAdditiveSemigroupInteger`)))) + (delay (force addInteger))) + (delay (\x -> (\x y -> (\y -> addInteger x y) y) x))) + addInteger) + (delay (delay (\v -> v))) + v + ((\v -> force v) (delay 1)))) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden index 9a10cb7525d..9ecb3535d37 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden @@ -1,5 +1,5 @@ -cpu: 14844094 -mem: 56082 -size: 75 +cpu: 37164094 +mem: 195582 +size: 287 (con (list integer) [1,3,5,7,9]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.pir.golden index 201fff9c3e9..94a964d0f4e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.pir.golden @@ -1,48 +1,91 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] data (Maybe :: * -> *) a | Maybe_match where Just : a -> Maybe a Nothing : Maybe a + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + !mkCons : all a. a -> list a -> list a = mkCons + ~mapMaybe : + all a b. (\arep -> list arep) b -> (a -> Maybe b) -> list a -> list b + = /\a b -> + \(`$dMkNil` : (\arep -> list arep) b) (f : a -> Maybe b) -> + let + !f : a -> Maybe b = f + in + letrec + ~go : list a -> list b + = caseList' + {a} + {list b} + `$dMkNil` + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + Maybe_match + {b} + (f x) + {all dead. list b} + (\(y : b) -> /\dead -> mkCons {b} y (go xs)) + (/\dead -> go xs) + {all dead. dead}) + in + go data Bool | Bool_match where True : Bool False : Bool + !equalsInteger : integer -> integer -> bool = equalsInteger + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !modInteger : integer -> integer -> integer = modInteger + ~even : integer -> Bool + = \(n : integer) -> + let + !n : integer = n + !x : integer = modInteger n 2 + !b : bool = equalsInteger x 0 + in + ifThenElse {Bool} b True False + ~odd : integer -> Bool + = \(n : integer) -> + let + !n : integer = n + in + Bool_match + (even n) + {all dead. Bool} + (/\dead -> False) + (/\dead -> True) + {all dead. dead} in \(xs : list integer) -> - (letrec - !go : list integer -> list integer - = (let - r = list integer - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - [] - (\(x : integer) (xs : list integer) -> - Maybe_match - {integer} - (Bool_match - (Bool_match - (ifThenElse - {Bool} - (equalsInteger 0 (modInteger x 2)) - True - False) - {all dead. Bool} - (/\dead -> False) - (/\dead -> True) - {all dead. dead}) - {all dead. Maybe integer} - (/\dead -> Just {integer} x) - (/\dead -> Nothing {integer}) - {all dead. dead}) - {all dead. list integer} - (\(y : integer) -> /\dead -> mkCons {integer} y (go xs)) - (/\dead -> go xs) - {all dead. dead}) - in - go) + let + !xs : list integer = xs + in + mapMaybe + {integer} + {integer} + `$fMkNilInteger` + (\(x : integer) -> + let + !x : integer = x + in + Bool_match + (odd x) + {all dead. Maybe integer} + (/\dead -> Just {integer} x) + (/\dead -> Nothing {integer}) + {all dead. dead}) xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.uplc.golden index dda4598cd03..4194a574fba 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.uplc.golden @@ -1,23 +1,163 @@ (program 1.1.0 - (\xs -> - (\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay []) - (delay - ((\x xs -> - force - (case + ((\fix1 + xs -> + (\xs -> + force + (delay + (\Just + Nothing + Maybe_match -> + force + (force + ((\mapMaybe -> + force mapMaybe) + (delay + (delay + (delay + (\`$dMkNil` + f -> + (\f -> + (\mkCons -> + (\caseList' -> + (\tup -> + (\go -> + (\go -> force go) + (go (delay (\x -> x)))) + (force tup + (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force + caseList') + `$dMkNil` + (\x -> + (\x + xs -> + (\xs -> + force + (force + (force + Maybe_match + (f + x)) + (\y -> + delay + (force + mkCons + y + (force + (go + (delay + (\x -> + x))) + xs))) + (delay + (force + (go + (delay + (\x -> + x))) + xs)))) + xs) + x))))))) + (delay + (delay + (\z f xs -> + force + (force + (force chooseList) + xs + (delay z) + (delay + (f + (force + headList + xs) + (force + tailList + xs)))))))) + mkCons) + f)))))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) + (\x -> + (\x -> + force (force - (force ifThenElse - (equalsInteger 0 (modInteger x 2)) - (delay (constr 1 [])) - (delay (constr 0 [x])))) - [ (\y -> delay (force mkCons y (s s xs))) - , (delay (s s xs)) ])) - (force headList xs) - (force tailList xs))))) - xs)) \ No newline at end of file + (force + (delay + (\True + False + Bool_match -> + Bool_match + ((\modInteger -> + (\ifThenElse -> + (\equalsInteger -> + (\even -> + (\odd -> + force odd) + (delay + (\n -> + (\n -> + force + (force + (Bool_match + (force + even + n)) + (delay + False) + (delay + True))) + n))) + (delay + (\n -> + (\n -> + (\x -> + (\b -> + force + ifThenElse + b + True + False) + (equalsInteger + x + 0)) + (modInteger + n + 2)) + n))) + equalsInteger) + ifThenElse) + modInteger + x))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True case_False -> + case x [case_True, case_False]))) + (delay (force Just x)) + (delay (force Nothing)))) + x))) + (delay (\arg_0 -> constr 0 [arg_0])) + (delay (constr 1 [])) + (delay + (\x -> + delay + (\case_Just case_Nothing -> + case x [case_Just, case_Nothing]))) + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden index 6e7ed93cb18..a177893b8cb 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden @@ -1,5 +1,5 @@ -cpu: 11434984 -mem: 45112 -size: 63 +cpu: 23178984 +mem: 118512 +size: 240 (constr 0) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.pir.golden index 3f9860f20b1..d8ac7b44488 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.pir.golden @@ -1,33 +1,80 @@ let + !equalsInteger : integer -> integer -> bool = equalsInteger + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse data Bool | Bool_match where True : Bool False : Bool -in -letrec - !go : list integer -> Bool - = \(xs : list integer) -> - chooseList - {integer} - {all dead. Bool} - xs - (/\dead -> False) - (/\dead -> - let - !x : integer = headList {integer} xs - !xs : list integer = tailList {integer} xs - in - Bool_match - (ifThenElse {Bool} (equalsInteger 42 x) True False) - {all dead. Bool} - (/\dead -> True) - (/\dead -> go xs) - {all dead. dead}) - {Bool} + ~equalsInteger : integer -> integer -> Bool + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> + let + !y : integer = y + !b : bool = equalsInteger x y + in + ifThenElse {Bool} b True False + ~`$fEqInteger` : (\a -> a -> a -> Bool) integer = equalsInteger + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~elem : all a. (\a -> a -> a -> Bool) a -> a -> list a -> Bool + = /\a -> + \(`$dEq` : (\a -> a -> a -> Bool) a) (a : a) -> + let + !a : a = a + in + letrec + ~go : list a -> Bool + = caseList' + {a} + {Bool} + False + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + Bool_match + (`$dEq` a x) + {all dead. Bool} + (/\dead -> True) + (/\dead -> go xs) + {all dead. dead}) + in + go + ~notElem : all a. (\a -> a -> a -> Bool) a -> a -> list a -> Bool + = /\a -> + \(`$dEq` : (\a -> a -> a -> Bool) a) (a : a) -> + let + !a : a = a + ~g : list a -> Bool = elem {a} `$dEq` a + in + \(eta : list a) -> + let + !x : list a = eta + !g : list a -> Bool = g + in + Bool_match + (g x) + {all dead. Bool} + (/\dead -> False) + (/\dead -> True) + {all dead. dead} in \(xs : list integer) -> - Bool_match - (go xs) - {all dead. Bool} - (/\dead -> False) - (/\dead -> True) - {all dead. dead} \ No newline at end of file + let + !xs : list integer = xs + in + notElem {integer} `$fEqInteger` 42 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.uplc.golden index 3e44f6c9204..d8cee9f0c2f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.uplc.golden @@ -1,20 +1,136 @@ (program 1.1.0 - ((\go xs -> - force (case (go xs) [(delay (constr 1 [])), (delay (constr 0 []))])) - ((\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay (constr 1 [])) - (delay - ((\x -> - (\xs -> - force - (force ifThenElse - (equalsInteger 42 x) - (delay (constr 0 [])) - (delay (s s xs)))) - (force tailList xs)) - (force headList xs)))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + (delay + (\True + False + Bool_match -> + force + ((\notElem -> + force notElem) + (delay + (delay + (\`$dEq` + a -> + (\a + eta -> + (\x -> + (\g -> + force + (force (Bool_match (g x)) + (delay False) + (delay True))) + ((\g -> + force g) + (delay + (force + ((\elem -> + force elem) + (delay + (delay + (\`$dEq` + a -> + (\a -> + (\caseList' -> + (\tup -> + (\go -> + (\go -> + force + go) + (go + (delay + (\x -> + x)))) + (force + tup + (\arg_0 -> + arg_0))) + (delay + (\f -> + f + (force + (force + fix1) + (\go + arg -> + delay + (force + (force + caseList') + False + (\x -> + (\x + xs -> + (\xs -> + force + (force + (Bool_match + (`$dEq` + a + x)) + (delay + True) + (delay + (force + (go + (delay + (\x -> + x))) + xs)))) + xs) + x))))))) + (delay + (delay + (\z + f + xs -> + force + (force + (force + chooseList) + xs + (delay + z) + (delay + (f + (force + headList + xs) + (force + tailList + xs)))))))) + a)))) + `$dEq` + a)))) + eta) + a)))) + ((\ifThenElse -> + (\equalsInteger -> + (\equalsInteger -> + (\`$fEqInteger` -> force `$fEqInteger`) + (delay (force equalsInteger))) + (delay + (\x -> + (\x y -> + (\y -> + (\b -> force ifThenElse b True False) + (equalsInteger x y)) + y) + x))) + equalsInteger) + ifThenElse))) + (constr 0 []) + (constr 1 []) + (\x -> + delay (\case_True case_False -> case x [case_True, case_False])) + 42 + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden index da937161e5e..425cbbca95d 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden @@ -1,5 +1,5 @@ -cpu: 157975998 -mem: 655724 -size: 137 +cpu: 279527998 +mem: 1415424 +size: 446 (con (list integer) [1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden index cf54189252c..93f8ef0d563 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.pir.golden @@ -1,7 +1,22 @@ let + !equalsInteger : integer -> integer -> bool = equalsInteger + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse data Bool | Bool_match where True : Bool False : Bool + ~equalsInteger : integer -> integer -> Bool + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> + let + !y : integer = y + !b : bool = equalsInteger x y + in + ifThenElse {Bool} b True False + ~`$fEqInteger` : (\a -> a -> a -> Bool) integer = equalsInteger + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r = /\a r -> \(z : r) (f : a -> list a -> r) (xs : list a) -> @@ -12,60 +27,126 @@ let (/\dead -> z) (/\dead -> f (headList {a} xs) (tailList {a} xs)) {r} -in -letrec - !go : list integer -> list integer -> list integer - = \(l : list integer) (xs : list integer) -> - caseList' - {integer} - {list integer} - [] - (\(y : integer) (ys : list integer) -> - Bool_match - ((letrec - !go : list integer -> Bool - = caseList' - {integer} - {Bool} - False - (\(x : integer) (xs : list integer) -> - Bool_match - (ifThenElse - {Bool} - (equalsInteger x y) - True - False) - {all dead. Bool} - (/\dead -> True) - (/\dead -> go xs) - {all dead. dead}) - in - go) - xs) - {all dead. list integer} - (/\dead -> go ys xs) - (/\dead -> mkCons {integer} y (go ys (mkCons {integer} y xs))) - {all dead. dead}) - l -in -\(xs : list integer) -> - let - !eta : list integer - = (let - b = list integer + ~foldr : all a b. (a -> b -> b) -> b -> list a -> b + = /\a b -> + \(f : a -> b -> b) -> + let + !f : a -> b -> b = f in - \(f : integer -> b -> b) (acc : b) -> + \(acc : b) -> + let + !acc : b = acc + in letrec - !go : list integer -> b + ~go : list a -> b = caseList' - {integer} + {a} {b} acc - (\(x : integer) (xs : list integer) -> f x (go xs)) + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> let !xs : list a = xs in f x (go xs)) + in + go + !mkCons : all a. a -> list a -> list a = mkCons + ~`++` : all a. list a -> list a -> list a + = /\a -> + \(l : list a) -> + let + !l : list a = l + in + \(r : list a) -> + let + !r : list a = r + in + foldr {a} {list a} (mkCons {a}) r l + ~append : all a. list a -> list a -> list a = `++` + ~elemBy : all a. (a -> a -> Bool) -> a -> list a -> Bool + = /\a -> + \(eq : a -> a -> Bool) -> + let + !eq : a -> a -> Bool = eq + in + \(y : a) -> + let + !y : a = y in - go) - (mkCons {integer}) - xs - xs + letrec + ~go : list a -> Bool + = caseList' + {a} + {Bool} + False + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + Bool_match + (eq x y) + {all dead. Bool} + (/\dead -> True) + (/\dead -> go xs) + {all dead. dead}) + in + go + ~nubBy : all a. (\arep -> list arep) a -> (a -> a -> Bool) -> list a -> list a + = /\a -> + \(`$dMkNil` : (\arep -> list arep) a) -> + let + !x : list a = `$dMkNil` + in + \(eq : a -> a -> Bool) -> + let + !eq : a -> a -> Bool = eq + in + letrec + ~go : list a -> list a -> list a + = \(l : list a) -> + let + !l : list a = l + in + \(xs : list a) -> + let + !xs : list a = xs + in + caseList' + {a} + {list a} + `$dMkNil` + (\(y : a) -> + let + !y : a = y + in + \(ys : list a) -> + let + !ys : list a = ys + in + Bool_match + (elemBy {a} eq y xs) + {all dead. list a} + (/\dead -> go ys xs) + (/\dead -> + mkCons {a} y (go ys (mkCons {a} y xs))) + {all dead. dead}) + l + in + \(eta : list a) -> let !y : list a = eta in go y x + ~nub : + all a. + (\a -> a -> a -> Bool) a -> (\arep -> list arep) a -> list a -> list a + = /\a -> + \(`$dEq` : (\a -> a -> a -> Bool) a) + (`$dMkNil` : (\arep -> list arep) a) -> + nubBy {a} `$dMkNil` `$dEq` +in +\(xs : list integer) -> + let + !xs : list integer = xs in - go eta [] \ No newline at end of file + nub {integer} `$fEqInteger` `$fMkNilInteger` (append {integer} xs xs) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden index 68bf6347fa7..981d112c087 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden @@ -1,37 +1,258 @@ (program 1.1.0 - ((\caseList' -> - (\go xs -> - go - ((\s -> s s) - (\s -> caseList' xs (\x xs -> force mkCons x (s s xs))) - xs) - []) - ((\s -> s s) - (\s l xs -> - caseList' - [] - (\y ys -> - force - (case - ((\s -> s s) - (\s -> - caseList' - (constr 1 []) - (\x xs -> - force - (force ifThenElse - (equalsInteger x y) - (delay (constr 0 [])) - (delay (s s xs))))) - xs) - [ (delay (s s ys xs)) - , (delay - (force mkCons y (s s ys (force mkCons y xs)))) ])) - l))) - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + (\mkCons -> + (\caseList' -> + force + (delay + (\True + False + Bool_match -> + force + ((\nub -> + force nub) + (delay + (delay + (\`$dEq` + `$dMkNil` -> + force + ((\nubBy -> + force nubBy) + (delay + (delay + (\`$dMkNil` -> + (\x + eq -> + (\eq -> + (\elemBy -> + (\tup -> + (\go -> + (\go eta -> + (\y -> + force + go + y + x) + eta) + (go + (delay + (\x -> + x)))) + (force tup + (\arg_0 -> + arg_0))) + (delay + (\f -> + f + (force + (force + fix1) + (\go + arg -> + delay + (\l -> + (\l + xs -> + (\xs -> + force + (force + caseList') + `$dMkNil` + (\y -> + (\y + ys -> + (\ys -> + force + (force + (Bool_match + (force + (force + elemBy) + eq + y + xs)) + (delay + (force + (go + (delay + (\x -> + x))) + ys + xs)) + (delay + (force + mkCons + y + (force + (go + (delay + (\x -> + x))) + ys + (force + mkCons + y + xs)))))) + ys) + y) + l) + xs) + l)))))) + (delay + (delay + (\eq -> + (\eq + y -> + (\y -> + (\tup -> + (\go -> + (\go -> + force + go) + (go + (delay + (\x -> + x)))) + (force + tup + (\arg_0 -> + arg_0))) + (delay + (\f -> + f + (force + (force + fix1) + (\go + arg -> + delay + (force + (force + caseList') + False + (\x -> + (\x + xs -> + (\xs -> + force + (force + (Bool_match + (eq + x + y)) + (delay + True) + (delay + (force + (go + (delay + (\x -> + x))) + xs)))) + xs) + x))))))) + y) + eq)))) + eq) + `$dMkNil`)))) + `$dMkNil` + `$dEq`)))) + ((\ifThenElse -> + (\equalsInteger -> + (\equalsInteger -> + (\`$fEqInteger` -> force `$fEqInteger`) + (delay (force equalsInteger))) + (delay + (\x -> + (\x y -> + (\y -> + (\b -> + force ifThenElse b True False) + (equalsInteger x y)) + y) + x))) + equalsInteger) + ifThenElse))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True case_False -> + case x [case_True, case_False])) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) + (force + ((\foldr -> + (\`++` -> + (\append -> force append) (delay (force `++`))) + (delay + (delay + (\l -> + (\l r -> + (\r -> + force (force (force foldr)) + (force mkCons) + r + l) + r) + l)))) + (delay + (delay + (delay + (\f -> + (\f + acc -> + (\acc -> + (\tup -> + (\go -> + (\go -> force go) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force caseList') + acc + (\x -> + (\x + xs -> + (\xs -> + f + x + (force + (go + (delay + (\x -> + x))) + xs)) + xs) + x))))))) + acc) + f))))) + xs + xs)) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList xs)))))))) + mkCons) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden index bae47f5774e..9617aa85d1b 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden @@ -1,5 +1,5 @@ -cpu: 22604119 -mem: 98670 -size: 114 +cpu: 44700119 +mem: 236770 +size: 326 (con (list integer) [1]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden index 0cccfdb4edb..ec56fcd5c62 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.pir.golden @@ -1,7 +1,21 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanEqualsInteger : integer -> integer -> bool = lessThanEqualsInteger data Bool | Bool_match where True : Bool False : Bool + ~lessThanEqualsInteger : integer -> integer -> Bool + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> + let + !y : integer = y + !b : bool = lessThanEqualsInteger x y + in + ifThenElse {Bool} b True False !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r = /\a r -> \(z : r) (f : a -> list a -> r) (xs : list a) -> @@ -12,40 +26,84 @@ let (/\dead -> z) (/\dead -> f (headList {a} xs) (tailList {a} xs)) {r} -in -letrec - !go : list integer -> list integer -> list integer - = \(l : list integer) (xs : list integer) -> - caseList' - {integer} - {list integer} - [] - (\(y : integer) (ys : list integer) -> - Bool_match - ((letrec - !go : list integer -> Bool - = caseList' - {integer} - {Bool} - False - (\(x : integer) (xs : list integer) -> + ~elemBy : all a. (a -> a -> Bool) -> a -> list a -> Bool + = /\a -> + \(eq : a -> a -> Bool) -> + let + !eq : a -> a -> Bool = eq + in + \(y : a) -> + let + !y : a = y + in + letrec + ~go : list a -> Bool + = caseList' + {a} + {Bool} + False + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + Bool_match + (eq x y) + {all dead. Bool} + (/\dead -> True) + (/\dead -> go xs) + {all dead. dead}) + in + go + !mkCons : all a. a -> list a -> list a = mkCons + ~nubBy : all a. (\arep -> list arep) a -> (a -> a -> Bool) -> list a -> list a + = /\a -> + \(`$dMkNil` : (\arep -> list arep) a) -> + let + !x : list a = `$dMkNil` + in + \(eq : a -> a -> Bool) -> + let + !eq : a -> a -> Bool = eq + in + letrec + ~go : list a -> list a -> list a + = \(l : list a) -> + let + !l : list a = l + in + \(xs : list a) -> + let + !xs : list a = xs + in + caseList' + {a} + {list a} + `$dMkNil` + (\(y : a) -> + let + !y : a = y + in + \(ys : list a) -> + let + !ys : list a = ys + in Bool_match - (ifThenElse - {Bool} - (lessThanEqualsInteger x y) - True - False) - {all dead. Bool} - (/\dead -> True) - (/\dead -> go xs) + (elemBy {a} eq y xs) + {all dead. list a} + (/\dead -> go ys xs) + (/\dead -> + mkCons {a} y (go ys (mkCons {a} y xs))) {all dead. dead}) - in - go) - xs) - {all dead. list integer} - (/\dead -> go ys xs) - (/\dead -> mkCons {integer} y (go ys (mkCons {integer} y xs))) - {all dead. dead}) - l + l + in + \(eta : list a) -> let !y : list a = eta in go y x in -\(xs : list integer) -> go xs [] \ No newline at end of file +\(xs : list integer) -> + let + !xs : list integer = xs + in + nubBy {integer} `$fMkNilInteger` lessThanEqualsInteger xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden index 92444bc80a1..5918acc020d 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden @@ -1,32 +1,181 @@ (program 1.1.0 - ((\caseList' -> - (\go xs -> go xs []) - ((\s -> s s) - (\s l xs -> - caseList' - [] - (\y ys -> - force - (case - ((\s -> s s) - (\s -> - caseList' - (constr 1 []) - (\x xs -> - force - (force ifThenElse - (lessThanEqualsInteger x y) - (delay (constr 0 [])) - (delay (s s xs))))) - xs) - [ (delay (s s ys xs)) - , (delay - (force mkCons y (s s ys (force mkCons y xs)))) ])) - l))) - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + (delay + (\True + False + Bool_match -> + force + ((\nubBy -> + force nubBy) + (delay + (delay + (\`$dMkNil` -> + (\x + eq -> + (\eq -> + (\mkCons -> + (\caseList' -> + (\elemBy -> + (\tup -> + (\go -> + (\go eta -> + (\y -> force go y x) + eta) + (go (delay (\x -> x)))) + (force tup + (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (\l -> + (\l + xs -> + (\xs -> + force + (force + caseList') + `$dMkNil` + (\y -> + (\y + ys -> + (\ys -> + force + (force + (Bool_match + (force + (force + elemBy) + eq + y + xs)) + (delay + (force + (go + (delay + (\x -> + x))) + ys + xs)) + (delay + (force + mkCons + y + (force + (go + (delay + (\x -> + x))) + ys + (force + mkCons + y + xs)))))) + ys) + y) + l) + xs) + l)))))) + (delay + (delay + (\eq -> + (\eq + y -> + (\y -> + (\tup -> + (\go -> + (\go -> + force go) + (go + (delay + (\x -> + x)))) + (force tup + (\arg_0 -> + arg_0))) + (delay + (\f -> + f + (force + (force + fix1) + (\go + arg -> + delay + (force + (force + caseList') + False + (\x -> + (\x + xs -> + (\xs -> + force + (force + (Bool_match + (eq + x + y)) + (delay + True) + (delay + (force + (go + (delay + (\x -> + x))) + xs)))) + xs) + x))))))) + y) + eq)))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList + xs) + (force tailList + xs)))))))) + mkCons) + eq) + `$dMkNil`)))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) + ((\lessThanEqualsInteger -> + (\ifThenElse -> + (\lessThanEqualsInteger -> + force lessThanEqualsInteger) + (delay + (\x -> + (\x y -> + (\y -> + (\b -> force ifThenElse b True False) + (lessThanEqualsInteger x y)) + y) + x))) + ifThenElse) + lessThanEqualsInteger))) + (constr 0 []) + (constr 1 []) + (\x -> + delay (\case_True case_False -> case x [case_True, case_False])) + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden index 01e48473efb..95980926e9c 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden @@ -1,5 +1,5 @@ -cpu: 374582 -mem: 1533 -size: 14 +cpu: 1030582 +mem: 5633 +size: 62 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.pir.golden index 34e911a928f..2a404f9ab03 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.pir.golden @@ -2,5 +2,16 @@ let data Bool | Bool_match where True : Bool False : Bool + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !null : all a. list a -> bool = nullList + ~null : all a. list a -> Bool + = /\a -> + \(l : list a) -> + let + !l : list a = l + !b : bool = null {a} l + in + ifThenElse {Bool} b True False + ~null : all a. list a -> Bool = null in -\(xs : list integer) -> ifThenElse {Bool} (nullList {integer} xs) True False \ No newline at end of file +\(xs : list integer) -> let !xs : list integer = xs in null {integer} xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.uplc.golden index 05a9d295460..c96b8eda181 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.uplc.golden @@ -1,3 +1,31 @@ (program 1.1.0 - (\xs -> force ifThenElse (force nullList xs) (constr 0 []) (constr 1 []))) \ No newline at end of file + (\xs -> + (\xs -> + force + (force + (delay + (\True False Bool_match -> + (\null -> force null) + (delay + ((\null -> force null) + (delay + (delay + (\l -> + (\l -> + (\b -> + force + ((\ifThenElse -> ifThenElse) + ifThenElse) + b + True + False) + (force ((\null -> null) nullList) l)) + l))))))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True case_False -> case x [case_True, case_False]))) + xs) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden index dac90627f55..2b5491f5e73 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden @@ -1,5 +1,5 @@ -cpu: 1125956 -mem: 4897 -size: 53 +cpu: 2837956 +mem: 15597 +size: 176 (constr 0) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.pir.golden index 2a026ae4c03..fc811297042 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.pir.golden @@ -2,26 +2,48 @@ let data Bool | Bool_match where True : Bool False : Bool + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~any : all a. (a -> Bool) -> list a -> Bool + = /\a -> + \(p : a -> Bool) -> + let + !p : a -> Bool = p + in + letrec + ~go : list a -> Bool + = caseList' + {a} + {Bool} + False + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + Bool_match + (p x) + {all dead. Bool} + (/\dead -> True) + (/\dead -> go xs) + {all dead. dead}) + in + go + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + ~or : list bool -> Bool + = any + {bool} + (\(x : bool) -> let !x : bool = x in ifThenElse {Bool} x True False) in -letrec - !go : list bool -> Bool - = \(xs : list bool) -> - chooseList - {bool} - {all dead. Bool} - xs - (/\dead -> False) - (/\dead -> - let - !x : bool = headList {bool} xs - !xs : list bool = tailList {bool} xs - in - Bool_match - (ifThenElse {Bool} x True False) - {all dead. Bool} - (/\dead -> True) - (/\dead -> go xs) - {all dead. dead}) - {Bool} -in -\(xs : list bool) -> go xs \ No newline at end of file +\(xs : list bool) -> let !xs : list bool = xs in or xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.uplc.golden index 6899fdc8a6f..f0891e31df7 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.uplc.golden @@ -1,19 +1,90 @@ (program 1.1.0 - ((\go xs -> go xs) - ((\s -> s s) - (\s xs -> - force - (force (force chooseList) - xs - (delay (constr 1 [])) - (delay - ((\x -> - (\xs -> - force - (force ifThenElse - x - (delay (constr 0 [])) - (delay (s s xs)))) - (force tailList xs)) - (force headList xs)))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + (delay + (\True + False + Bool_match -> + (\or -> + force or) + (delay + (force + ((\any -> + force any) + (delay + (delay + (\p -> + (\p -> + (\caseList' -> + (\tup -> + (\go -> + (\go -> force go) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (force + (force + caseList') + False + (\x -> + (\x + xs -> + (\xs -> + force + (force + (Bool_match + (p + x)) + (delay + True) + (delay + (force + (go + (delay + (\x -> + x))) + xs)))) + xs) + x))))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList + xs) + (force tailList + xs)))))))) + p)))) + (\x -> + (\x -> + force ((\ifThenElse -> ifThenElse) ifThenElse) + x + True + False) + x))))) + (constr 0 []) + (constr 1 []) + (\x -> + delay (\case_True case_False -> case x [case_True, case_False])) + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden index b95204f057d..30afabd4bc6 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden @@ -1,5 +1,5 @@ -cpu: 8478546 -mem: 34362 -size: 46 +cpu: 15246546 +mem: 76662 +size: 162 (con (list integer) [0,0,0,0,0,0,0,0,0,0]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.pir.golden index bfc7347272d..cc79eda05e1 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.pir.golden @@ -1,16 +1,36 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] data Bool | Bool_match where True : Bool False : Bool + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanEqualsInteger : integer -> integer -> bool = lessThanEqualsInteger + !mkCons : all a. a -> list a -> list a = mkCons + !subtractInteger : integer -> integer -> integer = subtractInteger + ~replicate : all a. (\arep -> list arep) a -> integer -> a -> list a + = /\a -> + \(`$dMkNil` : (\arep -> list arep) a) (n : integer) -> + let + !n : integer = n + in + \(x : a) -> + let + !x : a = x + in + letrec + ~go : integer -> list a + = \(n : integer) -> + let + !n : integer = n + !b : bool = lessThanEqualsInteger n 0 + in + Bool_match + (ifThenElse {Bool} b True False) + {all dead. list a} + (/\dead -> `$dMkNil`) + (/\dead -> mkCons {a} x (go (subtractInteger n 1))) + {all dead. dead} + in + go n in -letrec - !go : integer -> list integer - = \(n : integer) -> - Bool_match - (ifThenElse {Bool} (lessThanEqualsInteger n 0) True False) - {all dead. list integer} - (/\dead -> []) - (/\dead -> mkCons {integer} 0 (go (subtractInteger n 1))) - {all dead. dead} -in -\(ds : list integer) -> go 10 \ No newline at end of file +\(ds : list integer) -> replicate {integer} `$fMkNilInteger` 10 0 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.uplc.golden index 79a2423792c..8223fbd1617 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.uplc.golden @@ -1,11 +1,88 @@ (program 1.1.0 - ((\go ds -> go 10) - ((\s -> s s) - (\s n -> - force - (force ifThenElse - (lessThanEqualsInteger n 0) - (delay []) - (delay - (force mkCons 0 ((\x -> s s x) (subtractInteger n 1))))))))) \ No newline at end of file + ((\fix1 + ds -> + force + ((\replicate -> + force replicate) + (delay + (delay + (\`$dMkNil` + n -> + (\n + x -> + (\x -> + (\subtractInteger -> + (\mkCons -> + (\lessThanEqualsInteger -> + (\ifThenElse -> + force + (delay + (\True + False + Bool_match -> + (\tup -> + (\go -> + (\go -> force go n) + (go (delay (\x -> x)))) + (force tup + (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (\n -> + (\n -> + (\b -> + force + (force + (Bool_match + (force + ifThenElse + b + True + False)) + (delay + `$dMkNil`) + (delay + (force + mkCons + x + (force + (go + (delay + (\x -> + x))) + (subtractInteger + n + 1)))))) + (lessThanEqualsInteger + n + 0)) + n))))))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True case_False -> + case + x + [case_True, case_False]))) + ifThenElse) + lessThanEqualsInteger) + mkCons) + subtractInteger) + x) + n)))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) + 10 + 0) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden index c7c5e70c6f5..b67588a7bf9 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden @@ -1,5 +1,5 @@ -cpu: 10938784 -mem: 45812 -size: 65 +cpu: 17962784 +mem: 89712 +size: 139 (con (list integer) [10,9,8,7,6,5,4,3,2,1,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.pir.golden index 947476915ae..a7d205abfb4 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.pir.golden @@ -1,20 +1,40 @@ +let + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + !mkCons : all a. a -> list a -> list a = mkCons +in letrec - !revAppend : all a. list a -> list a -> list a + ~revAppend : all a. list a -> list a -> list a = /\a -> - \(l : list a) (r : list a) -> - (let - r = list a + \(l : list a) -> + let + !l : list a = l + in + \(r : list a) -> + let + !r : list a = r in - \(z : r) (f : a -> list a -> r) (xs : list a) -> - chooseList - {a} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {a} xs) (tailList {a} xs)) - {r}) - r - (\(x : a) (xs : list a) -> revAppend {a} xs (mkCons {a} x r)) - l + caseList' + {a} + {list a} + r + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + revAppend {a} xs (mkCons {a} x r)) + l in -\(xs : list integer) -> revAppend {integer} xs xs \ No newline at end of file +\(xs : list integer) -> let !xs : list integer = xs in revAppend {integer} xs xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.uplc.golden index 5d2e2ecdf08..afa37ead415 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.uplc.golden @@ -1,19 +1,52 @@ (program 1.1.0 - ((\revAppend xs -> force revAppend xs xs) - ((\s -> s s) - (\s arg -> - delay - (\l r -> - force - (force (force chooseList) - l - (delay r) - (delay - ((\x xs -> - force (s s (delay (\x -> x))) - xs - (force mkCons x r)) - (force headList l) - (force tailList l)))))) - (delay (\x -> x))))) \ No newline at end of file + ((\fix1 -> + (\mkCons -> + (\caseList' -> + (\tup -> + (\revAppend -> + (\revAppend xs -> (\xs -> force (force revAppend) xs xs) xs) + (revAppend (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force (force fix1) + (\revAppend arg -> + delay + (delay + (\l -> + (\l r -> + (\r -> + force (force caseList') + r + (\x -> + (\x xs -> + (\xs -> + force + (force + (revAppend + (delay + (\x -> x)))) + xs + (force mkCons x r)) + xs) + x) + l) + r) + l))))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f (force headList xs) (force tailList xs)))))))) + mkCons) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden index 4a0b1fee052..e2ab77168e2 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden @@ -1,5 +1,5 @@ -cpu: 10938784 -mem: 45812 -size: 65 +cpu: 18298784 +mem: 91812 +size: 160 (con (list integer) [10,9,8,7,6,5,4,3,2,1]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.pir.golden index 3d1eee382e9..e643310ef9a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.pir.golden @@ -1,20 +1,54 @@ +let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + !mkCons : all a. a -> list a -> list a = mkCons +in letrec - !revAppend : all a. list a -> list a -> list a + ~revAppend : all a. list a -> list a -> list a = /\a -> - \(l : list a) (r : list a) -> - (let - r = list a + \(l : list a) -> + let + !l : list a = l + in + \(r : list a) -> + let + !r : list a = r in - \(z : r) (f : a -> list a -> r) (xs : list a) -> - chooseList - {a} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {a} xs) (tailList {a} xs)) - {r}) - r - (\(x : a) (xs : list a) -> revAppend {a} xs (mkCons {a} x r)) - l + caseList' + {a} + {list a} + r + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + revAppend {a} xs (mkCons {a} x r)) + l +in +let + ~reverse : all a. (\arep -> list arep) a -> list a -> list a + = /\a -> + \(`$dMkNil` : (\arep -> list arep) a) (xs : list a) -> + let + !xs : list a = xs + in + revAppend {a} xs `$dMkNil` in -\(xs : list integer) -> revAppend {integer} xs [] \ No newline at end of file +\(xs : list integer) -> + let + !xs : list integer = xs + in + reverse {integer} `$fMkNilInteger` xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.uplc.golden index 8f3d26881e8..ab2501f2e27 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.uplc.golden @@ -1,19 +1,68 @@ (program 1.1.0 - ((\revAppend xs -> force revAppend xs []) - ((\s -> s s) - (\s arg -> - delay - (\l r -> - force - (force (force chooseList) - l - (delay r) - (delay - ((\x xs -> - force (s s (delay (\x -> x))) - xs - (force mkCons x r)) - (force headList l) - (force tailList l)))))) - (delay (\x -> x))))) \ No newline at end of file + ((\fix1 -> + (\mkCons -> + (\caseList' -> + (\`$fMkNilInteger` -> + (\tup -> + (\revAppend -> + (\revAppend xs -> + (\xs -> + force + ((\reverse -> force reverse) + (delay + (delay + (\`$dMkNil` xs -> + (\xs -> + force (force revAppend) + xs + `$dMkNil`) + xs)))) + (force `$fMkNilInteger`) + xs) + xs) + (revAppend (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force (force fix1) + (\revAppend arg -> + delay + (delay + (\l -> + (\l r -> + (\r -> + force (force caseList') + r + (\x -> + (\x xs -> + (\xs -> + force + (force + (revAppend + (delay + (\x -> x)))) + xs + (force mkCons x r)) + xs) + x) + l) + r) + l))))))) + (delay [])) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f (force headList xs) (force tailList xs)))))))) + mkCons) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden index 34304684821..94f06afbd59 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden @@ -1,5 +1,5 @@ -cpu: 64100 -mem: 500 -size: 4 +cpu: 600462 +mem: 3432 +size: 33 (con (list integer) [42]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.pir.golden index 32193031548..a1cff213c91 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.pir.golden @@ -1 +1,12 @@ -\(ds : list integer) -> [42] \ No newline at end of file +let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] + !mkCons : all a. a -> list a -> list a = mkCons + ~singleton : all a. (\arep -> list arep) a -> a -> list a + = /\a -> + \(`$dMkNil` : (\arep -> list arep) a) (x : a) -> + let + !x : a = x + in + mkCons {a} x `$dMkNil` +in +\(ds : list integer) -> singleton {integer} `$fMkNilInteger` 42 \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden index 26d8c4ac9b7..9d1ae6095dd 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden @@ -1 +1,11 @@ -(program 1.1.0 (\ds -> [42])) \ No newline at end of file +(program + 1.1.0 + (\ds -> + force + ((\singleton -> force singleton) + (delay + (delay + (\`$dMkNil` x -> + (\x -> force ((\mkCons -> mkCons) mkCons) x `$dMkNil`) x)))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) + 42)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.pir.golden index ba8b0f02986..3f7eff50e4f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.pir.golden @@ -1,33 +1,67 @@ let - data Unit | Unit_match where - Unit : Unit -in -\(ds : list integer) -> - (let - r = list integer - in - \(nilCase : Unit -> r) - (consCase : integer -> list integer -> r) - (l : list integer) -> - (let - r = Unit -> r - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] + ~mkNil : all arep. (\arep -> list arep) arep -> list arep + = /\arep -> \(v : (\arep -> list arep) arep) -> v + ~empty : all a. (\arep -> list arep) a -> list a = mkNil + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> chooseList - {integer} + {a} {all dead. r} xs (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - nilCase - (\(x : integer) (xs : list integer) (ds : Unit) -> consCase x xs) - l - Unit) - (\(ds : Unit) -> - let - !x : Unit = trace {Unit} "PT25" Unit - in - error {list integer}) - (\(ds : integer) (xs : list integer) -> xs) - [] \ No newline at end of file + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + data Unit | Unit_match where + Unit : Unit + ~caseList : all a r. (Unit -> r) -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(nilCase : Unit -> r) -> + let + !nilCase : Unit -> r = nilCase + in + \(consCase : a -> list a -> r) -> + let + !consCase : a -> list a -> r = consCase + in + \(l : list a) -> + let + !l : list a = l + in + caseList' + {a} + {Unit -> r} + nilCase + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + \(ds : Unit) -> consCase x xs) + l + Unit + ~lastEmptyBuiltinListError : string = "PT25" + !error : all a. unit -> a = /\a -> \(thunk : unit) -> error {a} + !trace : all a. string -> a -> a = trace + !unitval : unit = () + ~traceError : all a. string -> a + = /\a -> + \(str : string) -> + let + !str : string = str + !x : Unit = trace {Unit} str Unit + in + error {a} unitval + ~tail : all a. list a -> list a + = /\a -> + caseList + {a} + {list a} + (\(ds : Unit) -> traceError {list a} lastEmptyBuiltinListError) + (\(ds : a) (xs : list a) -> xs) +in +\(ds : list integer) -> tail {integer} (empty {integer} `$fMkNilInteger`) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.uplc.golden index bf34b9f1680..b956778bcc4 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.uplc.golden @@ -2,8 +2,89 @@ 1.1.0 (\ds -> force - (force (force chooseList) - [] - (delay (\ds -> (\x -> error) (force trace "PT25" (constr 0 [])))) - (delay ((\x xs ds -> xs) (force headList []) (force tailList [])))) - (constr 0 []))) \ No newline at end of file + ((\tail -> + force tail) + (delay + (delay + (force + (delay + (\Unit + Unit_match -> + force + (force + ((\caseList -> + force caseList) + (delay + (delay + (delay + (\nilCase -> + (\nilCase + consCase -> + (\consCase + l -> + (\l -> + force + (force + ((\caseList' -> + caseList') + (delay + (delay + (\z + f + xs -> + force + (force + (force + chooseList) + xs + (delay + z) + (delay + (f + (force + headList + xs) + (force + tailList + xs))))))))) + nilCase + (\x -> + (\x xs -> + (\xs ds -> + consCase x xs) + xs) + x) + l + Unit) + l) + consCase) + nilCase)))))) + (\ds -> + force + ((\unitval -> + (\trace -> + (\error -> + (\traceError -> force traceError) + (delay + (delay + (\str -> + (\str -> + (\x -> + force error unitval) + (force trace + str + Unit)) + str)))) + (delay (\thunk -> error))) + trace) + ()) + ((\lastEmptyBuiltinListError -> + force lastEmptyBuiltinListError) + (delay "PT25"))))) + (constr 0 []) + (\x -> delay (\case_Unit -> case x [case_Unit])) + (\ds xs -> xs))))) + (force + ((\mkNil -> (\empty -> force empty) (delay (force mkNil))) + (delay (delay (\v -> v)))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay []))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden index 86aa7f56508..c19f0f15561 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden @@ -1,5 +1,5 @@ -cpu: 761907 -mem: 3096 -size: 39 +cpu: 1929907 +mem: 10396 +size: 149 (con (list integer) [2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.pir.golden index f263763145a..4a71da62851 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.pir.golden @@ -1,33 +1,63 @@ let - data Unit | Unit_match where - Unit : Unit -in -\(xs : list integer) -> - (let - r = list integer - in - \(nilCase : Unit -> r) - (consCase : integer -> list integer -> r) - (l : list integer) -> - (let - r = Unit -> r - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> chooseList - {integer} + {a} {all dead. r} xs (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - nilCase - (\(x : integer) (xs : list integer) (ds : Unit) -> consCase x xs) - l - Unit) - (\(ds : Unit) -> - let - !x : Unit = trace {Unit} "PT25" Unit - in - error {list integer}) - (\(ds : integer) (xs : list integer) -> xs) - xs \ No newline at end of file + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + data Unit | Unit_match where + Unit : Unit + ~caseList : all a r. (Unit -> r) -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(nilCase : Unit -> r) -> + let + !nilCase : Unit -> r = nilCase + in + \(consCase : a -> list a -> r) -> + let + !consCase : a -> list a -> r = consCase + in + \(l : list a) -> + let + !l : list a = l + in + caseList' + {a} + {Unit -> r} + nilCase + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + \(ds : Unit) -> consCase x xs) + l + Unit + ~lastEmptyBuiltinListError : string = "PT25" + !error : all a. unit -> a = /\a -> \(thunk : unit) -> error {a} + !trace : all a. string -> a -> a = trace + !unitval : unit = () + ~traceError : all a. string -> a + = /\a -> + \(str : string) -> + let + !str : string = str + !x : Unit = trace {Unit} str Unit + in + error {a} unitval + ~tail : all a. list a -> list a + = /\a -> + caseList + {a} + {list a} + (\(ds : Unit) -> traceError {list a} lastEmptyBuiltinListError) + (\(ds : a) (xs : list a) -> xs) +in +\(xs : list integer) -> let !xs : list integer = xs in tail {integer} xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.uplc.golden index 266a36fc6ba..d519a628e50 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.uplc.golden @@ -1,9 +1,92 @@ (program 1.1.0 (\xs -> - force - (force (force chooseList) - xs - (delay (\ds -> (\x -> error) (force trace "PT25" (constr 0 [])))) - (delay ((\x xs ds -> xs) (force headList xs) (force tailList xs)))) - (constr 0 []))) \ No newline at end of file + (\xs -> + force + ((\tail -> + force tail) + (delay + (delay + (force + (delay + (\Unit + Unit_match -> + force + (force + ((\caseList -> + force caseList) + (delay + (delay + (delay + (\nilCase -> + (\nilCase + consCase -> + (\consCase + l -> + (\l -> + force + (force + ((\caseList' -> + caseList') + (delay + (delay + (\z + f + xs -> + force + (force + (force + chooseList) + xs + (delay + z) + (delay + (f + (force + headList + xs) + (force + tailList + xs))))))))) + nilCase + (\x -> + (\x xs -> + (\xs ds -> + consCase + x + xs) + xs) + x) + l + Unit) + l) + consCase) + nilCase)))))) + (\ds -> + force + ((\unitval -> + (\trace -> + (\error -> + (\traceError -> force traceError) + (delay + (delay + (\str -> + (\str -> + (\x -> + force error + unitval) + (force trace + str + Unit)) + str)))) + (delay (\thunk -> error))) + trace) + ()) + ((\lastEmptyBuiltinListError -> + force lastEmptyBuiltinListError) + (delay "PT25"))))) + (constr 0 []) + (\x -> delay (\case_Unit -> case x [case_Unit])) + (\ds xs -> xs))))) + xs) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden index 0b6fb76a1c7..99c0cf52688 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden @@ -1,5 +1,5 @@ -cpu: 8356301 -mem: 33762 -size: 85 +cpu: 14308301 +mem: 70962 +size: 204 (con (list integer) [1,2,3,4,5]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.pir.golden index 4b4566fc10f..531b1f2d2ea 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.pir.golden @@ -1,32 +1,61 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] data Bool | Bool_match where True : Bool False : Bool + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanEqualsInteger : integer -> integer -> bool = lessThanEqualsInteger + !mkCons : all a. a -> list a -> list a = mkCons + !subtractInteger : integer -> integer -> integer = subtractInteger in letrec - !take : all a. (\arep -> list arep) a -> integer -> list a -> list a + ~take : all a. (\arep -> list arep) a -> integer -> list a -> list a = /\a -> - \(`$dMkNil` : (\arep -> list arep) a) (n : integer) (l : list a) -> - Bool_match - (ifThenElse {Bool} (lessThanEqualsInteger n 0) True False) - {all dead. list a} - (/\dead -> `$dMkNil`) - (/\dead -> - (let - r = list a - in - \(z : r) (f : a -> list a -> r) (xs : list a) -> - chooseList - {a} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {a} xs) (tailList {a} xs)) - {r}) - `$dMkNil` - (\(x : a) (xs : list a) -> - mkCons {a} x (take {a} `$dMkNil` (subtractInteger n 1) xs)) - l) - {all dead. dead} + \(`$dMkNil` : (\arep -> list arep) a) (n : integer) -> + let + !n : integer = n + in + \(l : list a) -> + let + !l : list a = l + !b : bool = lessThanEqualsInteger n 0 + in + Bool_match + (ifThenElse {Bool} b True False) + {all dead. list a} + (/\dead -> `$dMkNil`) + (/\dead -> + caseList' + {a} + {list a} + `$dMkNil` + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + mkCons + {a} + x + (take {a} `$dMkNil` (subtractInteger n 1) xs)) + l) + {all dead. dead} in -\(xs : list integer) -> take {integer} [] 5 xs \ No newline at end of file +\(xs : list integer) -> + let + !xs : list integer = xs + in + take {integer} `$fMkNilInteger` 5 xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.uplc.golden index 0b887c563e4..3edaab18f33 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.uplc.golden @@ -1,26 +1,108 @@ (program 1.1.0 - ((\take xs -> force take [] 5 xs) - ((\s -> s s) - (\s arg -> - delay - (\`$dMkNil` n l -> - force - (force ifThenElse - (lessThanEqualsInteger n 0) - (delay `$dMkNil`) - (delay - (force - (force (force chooseList) - l - (delay `$dMkNil`) - (delay - ((\xs -> - force mkCons - (force headList l) - (force (s s (delay (\x -> x))) - `$dMkNil` - (subtractInteger n 1) - xs)) - (force tailList l))))))))) - (delay (\x -> x))))) \ No newline at end of file + ((\fix1 -> + (\subtractInteger -> + (\mkCons -> + (\lessThanEqualsInteger -> + (\ifThenElse -> + (\caseList' -> + force + (delay + (\True + False + Bool_match -> + (\`$fMkNilInteger` -> + (\tup -> + (\take -> + (\take xs -> + (\xs -> + force (force take) + (force `$fMkNilInteger`) + 5 + xs) + xs) + (take (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\take + arg -> + delay + (delay + (\`$dMkNil` + n -> + (\n + l -> + (\l -> + (\b -> + force + (force + (Bool_match + (force + ifThenElse + b + True + False)) + (delay + `$dMkNil`) + (delay + (force + (force + caseList') + `$dMkNil` + (\x -> + (\x + xs -> + (\xs -> + force + mkCons + x + (force + (force + (take + (delay + (\x -> + x)))) + `$dMkNil` + (subtractInteger + n + 1) + xs)) + xs) + x) + l)))) + (lessThanEqualsInteger + n + 0)) + l) + n))))))) + (delay []))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True case_False -> + case x [case_True, case_False]))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList xs)))))))) + ifThenElse) + lessThanEqualsInteger) + mkCons) + subtractInteger) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden index 710ffb00b0f..f9c66c25a9b 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden @@ -1,5 +1,5 @@ -cpu: 665907 -mem: 2496 -size: 24 +cpu: 1849907 +mem: 9896 +size: 113 (constr 0 (constr 0 (con integer 1) (con (list integer) [2,3,4,5,6,7,8,9,10]))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.pir.golden index 132ec1c1aa7..0540dab3000 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.pir.golden @@ -4,22 +4,30 @@ let data (Maybe :: * -> *) a | Maybe_match where Just : a -> Maybe a Nothing : Maybe a + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~uncons : all a. list a -> Maybe (Tuple2 a (list a)) + = /\a -> + caseList' + {a} + {Maybe (Tuple2 a (list a))} + (Nothing {Tuple2 a (list a)}) + (\(h : a) -> + let + !h : a = h + in + \(t : list a) -> + let + !t : list a = t + in + Just {Tuple2 a (list a)} (Tuple2 {a} {list a} h t)) in -\(xs : list integer) -> - (let - r = Maybe (Tuple2 integer (list integer)) - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - (Nothing {Tuple2 integer (list integer)}) - (\(h : integer) (t : list integer) -> - Just - {Tuple2 integer (list integer)} - (Tuple2 {integer} {list integer} h t)) - xs \ No newline at end of file +\(xs : list integer) -> let !xs : list integer = xs in uncons {integer} xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.uplc.golden index a4563742bf5..0fb3fd76117 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.uplc.golden @@ -1,10 +1,53 @@ (program 1.1.0 (\xs -> - force - (force (force chooseList) - xs - (delay (constr 1 [])) - (delay - (constr 0 - [(constr 0 [(force headList xs), (force tailList xs)])]))))) \ No newline at end of file + (\xs -> + force + (force + (delay + (\Just Nothing Maybe_match -> + force + (delay + (\Tuple2 Tuple2_match -> + (\uncons -> force uncons) + (delay + (delay + (force + (force + ((\caseList' -> caseList') + (delay + (delay + (\z f xs -> + force + (force + (force chooseList) + xs + (delay z) + (delay + (f + (force headList + xs) + (force tailList + xs))))))))) + (force Nothing) + (\h -> + (\h t -> + (\t -> + force Just + (force (force Tuple2) h t)) + t) + h)))))) + (delay (delay (\arg_0 arg_1 -> constr 0 [arg_0, arg_1]))) + (delay + (delay + (\x -> + delay (\case_Tuple2 -> case x [case_Tuple2])))))) + (delay (\arg_0 -> constr 0 [arg_0])) + (delay (constr 1 [])) + (delay + (\x -> + delay + (\case_Just case_Nothing -> + case x [case_Just, case_Nothing])))) + xs) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden index 6597dd039a7..2e801f04470 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden @@ -1,5 +1,5 @@ -cpu: 357094 -mem: 1532 -size: 24 +cpu: 1381094 +mem: 7932 +size: 130 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.pir.golden index f9c38536296..e94540d5de8 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.pir.golden @@ -1,25 +1,37 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] + ~mkNil : all arep. (\arep -> list arep) arep -> list arep + = /\arep -> \(v : (\arep -> list arep) arep) -> v + ~empty : all a. (\arep -> list arep) a -> list a = mkNil data (Tuple2 :: * -> * -> *) a b | Tuple2_match where Tuple2 : a -> b -> Tuple2 a b data (Maybe :: * -> *) a | Maybe_match where Just : a -> Maybe a Nothing : Maybe a + !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r + = /\a r -> + \(z : r) (f : a -> list a -> r) (xs : list a) -> + chooseList + {a} + {all dead. r} + xs + (/\dead -> z) + (/\dead -> f (headList {a} xs) (tailList {a} xs)) + {r} + ~uncons : all a. list a -> Maybe (Tuple2 a (list a)) + = /\a -> + caseList' + {a} + {Maybe (Tuple2 a (list a))} + (Nothing {Tuple2 a (list a)}) + (\(h : a) -> + let + !h : a = h + in + \(t : list a) -> + let + !t : list a = t + in + Just {Tuple2 a (list a)} (Tuple2 {a} {list a} h t)) in -\(ds : list integer) -> - (let - r = Maybe (Tuple2 integer (list integer)) - in - \(z : r) (f : integer -> list integer -> r) (xs : list integer) -> - chooseList - {integer} - {all dead. r} - xs - (/\dead -> z) - (/\dead -> f (headList {integer} xs) (tailList {integer} xs)) - {r}) - (Nothing {Tuple2 integer (list integer)}) - (\(h : integer) (t : list integer) -> - Just - {Tuple2 integer (list integer)} - (Tuple2 {integer} {list integer} h t)) - [] \ No newline at end of file +\(ds : list integer) -> uncons {integer} (empty {integer} `$fMkNilInteger`) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.uplc.golden index 1facba8acf0..6020571bc48 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.uplc.golden @@ -2,9 +2,52 @@ 1.1.0 (\ds -> force - (force (force chooseList) - [] + (force + (delay + (\Just Nothing Maybe_match -> + force + (delay + (\Tuple2 Tuple2_match -> + (\uncons -> force uncons) + (delay + (delay + (force + (force + ((\caseList' -> caseList') + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList + xs) + (force tailList + xs))))))))) + (force Nothing) + (\h -> + (\h t -> + (\t -> + force Just + (force (force Tuple2) h t)) + t) + h)))))) + (delay (delay (\arg_0 arg_1 -> constr 0 [arg_0, arg_1]))) + (delay + (delay + (\x -> + delay (\case_Tuple2 -> case x [case_Tuple2])))))) + (delay (\arg_0 -> constr 0 [arg_0])) (delay (constr 1 [])) (delay - (constr 0 - [(constr 0 [(force headList []), (force tailList [])])]))))) \ No newline at end of file + (\x -> + delay + (\case_Just case_Nothing -> + case x [case_Just, case_Nothing])))) + (force + ((\mkNil -> (\empty -> force empty) (delay (force mkNil))) + (delay (delay (\v -> v)))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay []))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden index 2c99798921c..007da693932 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden @@ -1,5 +1,5 @@ -cpu: 3718050 -mem: 16462 -size: 114 +cpu: 6358050 +mem: 32962 +size: 259 (constr 0 (con integer 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.pir.golden index 8c9c2507c56..709ba08242e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.pir.golden @@ -1,7 +1,12 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] data Bool | Bool_match where True : Bool False : Bool + !ifThenElse : all a. bool -> a -> a -> a = ifThenElse + !lessThanEqualsInteger : integer -> integer -> bool = lessThanEqualsInteger + !mkCons : all a. a -> list a -> list a = mkCons + !subtractInteger : integer -> integer -> integer = subtractInteger !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r = /\a r -> \(z : r) (f : a -> list a -> r) (xs : list a) -> @@ -14,37 +19,63 @@ let {r} in letrec - !take : all a. (\arep -> list arep) a -> integer -> list a -> list a + ~take : all a. (\arep -> list arep) a -> integer -> list a -> list a = /\a -> - \(`$dMkNil` : (\arep -> list arep) a) (n : integer) (l : list a) -> - Bool_match - (ifThenElse {Bool} (lessThanEqualsInteger n 0) True False) - {all dead. list a} - (/\dead -> `$dMkNil`) - (/\dead -> - caseList' - {a} - {list a} - `$dMkNil` - (\(x : a) (xs : list a) -> - mkCons {a} x (take {a} `$dMkNil` (subtractInteger n 1) xs)) - l) - {all dead. dead} + \(`$dMkNil` : (\arep -> list arep) a) (n : integer) -> + let + !n : integer = n + in + \(l : list a) -> + let + !l : list a = l + !b : bool = lessThanEqualsInteger n 0 + in + Bool_match + (ifThenElse {Bool} b True False) + {all dead. list a} + (/\dead -> `$dMkNil`) + (/\dead -> + caseList' + {a} + {list a} + `$dMkNil` + (\(x : a) -> + let + !x : a = x + in + \(xs : list a) -> + let + !xs : list a = xs + in + mkCons + {a} + x + (take {a} `$dMkNil` (subtractInteger n 1) xs)) + l) + {all dead. dead} in let data (Maybe :: * -> *) a | Maybe_match where Just : a -> Maybe a Nothing : Maybe a + ~uniqueElement : all a. list a -> Maybe a + = /\a -> + caseList' + {a} + {Maybe a} + (Nothing {a}) + (\(x : a) -> + let + !x : a = x + in + caseList' + {a} + {Maybe a} + (Just {a} x) + (\(ds : a) (ds : list a) -> Nothing {a})) in \(xs : list integer) -> - caseList' - {integer} - {Maybe integer} - (Nothing {integer}) - (\(x : integer) -> - caseList' - {integer} - {Maybe integer} - (Just {integer} x) - (\(ds : integer) (ds : list integer) -> Nothing {integer})) - (take {integer} [] 1 xs) \ No newline at end of file + let + !xs : list integer = xs + in + uniqueElement {integer} (take {integer} `$fMkNilInteger` 1 xs) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden index cd265454aa9..b4dfc0bf4c5 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden @@ -1,34 +1,147 @@ (program 1.1.0 - ((\caseList' -> - (\take xs -> - caseList' - (constr 1 []) - (\x -> caseList' (constr 0 [x]) (\ds ds -> constr 1 [])) - (force take [] 1 xs)) - ((\s -> s s) - (\s arg -> - delay - (\`$dMkNil` n l -> - force - (force ifThenElse - (lessThanEqualsInteger n 0) - (delay `$dMkNil`) - (delay - (caseList' - `$dMkNil` - (\x xs -> - force mkCons - x - (force (s s (delay (\x -> x))) - `$dMkNil` - (subtractInteger n 1) - xs)) - l))))) - (delay (\x -> x)))) - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file + ((\fix1 -> + (\caseList' -> + (\subtractInteger -> + (\mkCons -> + (\lessThanEqualsInteger -> + (\ifThenElse -> + force + (delay + (\True + False + Bool_match -> + (\`$fMkNilInteger` -> + (\tup -> + (\take -> + (\take + xs -> + (\xs -> + force + (force + (delay + (\Just + Nothing + Maybe_match -> + (\uniqueElement -> + force uniqueElement) + (delay + (delay + (force + (force + caseList') + (force + Nothing) + (\x -> + (\x -> + force + (force + caseList') + (force + Just + x) + (\ds + ds -> + force + Nothing)) + x)))))) + (delay + (\arg_0 -> + constr 0 [arg_0])) + (delay (constr 1 [])) + (delay + (\x -> + delay + (\case_Just + case_Nothing -> + case + x + [ case_Just + , case_Nothing ])))) + (force (force take) + (force `$fMkNilInteger`) + 1 + xs)) + xs) + (take (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\take + arg -> + delay + (delay + (\`$dMkNil` + n -> + (\n + l -> + (\l -> + (\b -> + force + (force + (Bool_match + (force + ifThenElse + b + True + False)) + (delay + `$dMkNil`) + (delay + (force + (force + caseList') + `$dMkNil` + (\x -> + (\x + xs -> + (\xs -> + force + mkCons + x + (force + (force + (take + (delay + (\x -> + x)))) + `$dMkNil` + (subtractInteger + n + 1) + xs)) + xs) + x) + l)))) + (lessThanEqualsInteger + n + 0)) + l) + n))))))) + (delay []))) + (constr 0 []) + (constr 1 []) + (\x -> + delay + (\case_True case_False -> + case x [case_True, case_False]))) + ifThenElse) + lessThanEqualsInteger) + mkCons) + subtractInteger) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs)))))))) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden index 01ce14fd5fd..d453e46980e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden @@ -1,5 +1,5 @@ -cpu: 549094 -mem: 2732 -size: 45 +cpu: 1253094 +mem: 7132 +size: 108 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.pir.golden index efb969694c4..434f291083b 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.pir.golden @@ -1,4 +1,8 @@ let + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] + ~mkNil : all arep. (\arep -> list arep) arep -> list arep + = /\arep -> \(v : (\arep -> list arep) arep) -> v + ~empty : all a. (\arep -> list arep) a -> list a = mkNil data (Maybe :: * -> *) a | Maybe_match where Just : a -> Maybe a Nothing : Maybe a @@ -12,16 +16,21 @@ let (/\dead -> z) (/\dead -> f (headList {a} xs) (tailList {a} xs)) {r} + ~uniqueElement : all a. list a -> Maybe a + = /\a -> + caseList' + {a} + {Maybe a} + (Nothing {a}) + (\(x : a) -> + let + !x : a = x + in + caseList' + {a} + {Maybe a} + (Just {a} x) + (\(ds : a) (ds : list a) -> Nothing {a})) in \(ds : list integer) -> - caseList' - {integer} - {Maybe integer} - (Nothing {integer}) - (\(x : integer) -> - caseList' - {integer} - {Maybe integer} - (Just {integer} x) - (\(ds : integer) (ds : list integer) -> Nothing {integer})) - [] \ No newline at end of file + uniqueElement {integer} (empty {integer} `$fMkNilInteger`) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.uplc.golden index 61a01732fec..c3122437b79 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.uplc.golden @@ -1,14 +1,41 @@ (program 1.1.0 (\ds -> - (\caseList' -> - caseList' - (constr 1 []) - (\x -> caseList' (constr 0 [x]) (\ds ds -> constr 1 []))) - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay (f (force headList xs) (force tailList xs))))) - [])) \ No newline at end of file + force + (force + (delay + (\Just Nothing Maybe_match -> + (\uniqueElement -> force uniqueElement) + (delay + (delay + ((\caseList' -> + force (force caseList') + (force Nothing) + (\x -> + (\x -> + force (force caseList') + (force Just x) + (\ds ds -> force Nothing)) + x)) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList xs) + (force tailList xs)))))))))))) + (delay (\arg_0 -> constr 0 [arg_0])) + (delay (constr 1 [])) + (delay + (\x -> + delay + (\case_Just case_Nothing -> + case x [case_Just, case_Nothing])))) + (force + ((\mkNil -> (\empty -> force empty) (delay (force mkNil))) + (delay (delay (\v -> v)))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay []))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden index f5d26d1cccc..5a3a300d075 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden @@ -1,5 +1,5 @@ -cpu: 20752934 -mem: 83192 -size: 72 +cpu: 31584934 +mem: 150892 +size: 222 (con (list integer) [2,4,6,8,10,12,14,16,18,20]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.pir.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.pir.golden index a101fa13848..f4a95e0ab8d 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.pir.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.pir.golden @@ -1,4 +1,15 @@ let + !addInteger : integer -> integer -> integer = addInteger + ~addInteger : integer -> integer -> integer + = \(x : integer) -> + let + !x : integer = x + in + \(y : integer) -> let !y : integer = y in addInteger x y + ~`$fAdditiveSemigroupInteger` : (\a -> a -> a -> a) integer = addInteger + ~`$fMkNilInteger` : (\arep -> list arep) integer = [] + ~`+` : all a. (\a -> a -> a -> a) a -> a -> a -> a + = /\a -> \(v : (\a -> a -> a -> a) a) -> v !caseList' : all a r. r -> (a -> list a -> r) -> list a -> r = /\a r -> \(z : r) (f : a -> list a -> r) (xs : list a) -> @@ -9,22 +20,64 @@ let (/\dead -> z) (/\dead -> f (headList {a} xs) (tailList {a} xs)) {r} + !mkCons : all a. a -> list a -> list a = mkCons + ~zipWith : + all a b c. + (\arep -> list arep) c -> (a -> b -> c) -> list a -> list b -> list c + = /\a b c -> + \(`$dMkNil` : (\arep -> list arep) c) (f : a -> b -> c) -> + let + !f : a -> b -> c = f + in + letrec + ~go : list a -> list b -> list c + = \(xs : list a) -> + let + !xs : list a = xs + in + \(ys : list b) -> + let + !ys : list b = ys + in + caseList' + {a} + {list c} + `$dMkNil` + (\(x : a) -> + let + !x : a = x + in + \(xs' : list a) -> + let + !xs' : list a = xs' + in + caseList' + {b} + {list c} + `$dMkNil` + (\(y : b) -> + let + !y : b = y + in + \(ys' : list b) -> + let + !ys' : list b = ys' + in + mkCons {c} (f x y) (go xs' ys')) + ys) + xs + in + \(eta : list a) (eta : list b) -> go eta eta in -letrec - !go : list integer -> list integer -> list integer - = \(xs : list integer) (ys : list integer) -> - caseList' - {integer} - {list integer} - [] - (\(x : integer) (xs' : list integer) -> - caseList' - {integer} - {list integer} - [] - (\(y : integer) (ys' : list integer) -> - mkCons {integer} (addInteger x y) (go xs' ys')) - ys) - xs -in -\(xs : list integer) -> go xs xs \ No newline at end of file +\(xs : list integer) -> + let + !xs : list integer = xs + in + zipWith + {integer} + {integer} + {integer} + `$fMkNilInteger` + (`+` {integer} `$fAdditiveSemigroupInteger`) + xs + xs \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.uplc.golden index 3a84c0a43e4..cc0ee8ec242 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.uplc.golden @@ -1,18 +1,105 @@ (program 1.1.0 - ((\go xs -> go xs xs) - ((\s -> s s) - (\s xs ys -> - (\cse -> - cse - (\x xs' -> - cse - (\y ys' -> force mkCons (addInteger x y) (s s xs' ys')) - ys) - xs) - (\f xs -> - force - (force (force chooseList) - xs - (delay []) - (delay (f (force headList xs) (force tailList xs))))))))) \ No newline at end of file + ((\fix1 + xs -> + (\xs -> + force + (force + (force + ((\zipWith -> + force zipWith) + (delay + (delay + (delay + (delay + (\`$dMkNil` + f -> + (\f -> + (\mkCons -> + (\caseList' -> + (\tup -> + (\go -> + (\go eta eta -> + force go eta eta) + (go (delay (\x -> x)))) + (force tup (\arg_0 -> arg_0))) + (delay + (\f -> + f + (force + (force fix1) + (\go + arg -> + delay + (\xs -> + (\xs + ys -> + (\ys -> + force + (force + caseList') + `$dMkNil` + (\x -> + (\x + xs' -> + (\xs' -> + force + (force + caseList') + `$dMkNil` + (\y -> + (\y + ys' -> + (\ys' -> + force + mkCons + (f + x + y) + (force + (go + (delay + (\x -> + x))) + xs' + ys')) + ys') + y) + ys) + xs') + x) + xs) + ys) + xs)))))) + (delay + (delay + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f + (force headList + xs) + (force tailList + xs)))))))) + mkCons) + f)))))))) + ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) + (force ((\`+` -> force `+`) (delay (delay (\v -> v)))) + ((\addInteger -> + (\addInteger -> + (\`$fAdditiveSemigroupInteger` -> + force `$fAdditiveSemigroupInteger`) + (delay (force addInteger))) + (delay (\x -> (\x y -> (\y -> addInteger x y) y) x))) + addInteger)) + xs + xs) + xs) + (delay + (delay + (\f -> + force (delay (\s -> s s)) + (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index 09248316cbf..782c9633c39 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -1,6 +1,9 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} +{-# OPTIONS_GHC -fplugin-opt PlutusTx.Plugin:max-cse-iterations=0 #-} +{-# OPTIONS_GHC -fplugin-opt PlutusTx.Plugin:max-simplifier-iterations-pir=0 #-} +{-# OPTIONS_GHC -fplugin-opt PlutusTx.Plugin:max-simplifier-iterations-uplc=0 #-} module BuiltinList.Budget.Spec where From 115f5d07c9838b41d155bc992e6d96616d99aaa4 Mon Sep 17 00:00:00 2001 From: zeme Date: Tue, 3 Jun 2025 14:55:24 +0200 Subject: [PATCH 25/30] wip --- .../BuiltinList/Budget/9.6/(++).eval.golden | 6 +- .../BuiltinList/Budget/9.6/(++).uplc.golden | 117 ++---- .../BuiltinList/Budget/9.6/(<|).eval.golden | 6 +- .../BuiltinList/Budget/9.6/(<|).uplc.golden | 9 +- .../BuiltinList/Budget/9.6/all.eval.golden | 6 +- .../BuiltinList/Budget/9.6/all.uplc.golden | 148 ++------ .../BuiltinList/Budget/9.6/and.eval.golden | 6 +- .../BuiltinList/Budget/9.6/and.uplc.golden | 113 ++---- .../BuiltinList/Budget/9.6/any.eval.golden | 6 +- .../BuiltinList/Budget/9.6/any.uplc.golden | 148 ++------ .../BuiltinList/Budget/9.6/append.eval.golden | 6 +- .../BuiltinList/Budget/9.6/append.uplc.golden | 120 +------ .../BuiltinList/Budget/9.6/concat.eval.golden | 6 +- .../BuiltinList/Budget/9.6/concat.uplc.golden | 157 +++----- .../Budget/9.6/concatMap.eval.golden | 6 +- .../Budget/9.6/concatMap.uplc.golden | 283 ++++----------- .../BuiltinList/Budget/9.6/cons.eval.golden | 6 +- .../BuiltinList/Budget/9.6/cons.uplc.golden | 9 +- .../BuiltinList/Budget/9.6/drop.eval.golden | 6 +- .../BuiltinList/Budget/9.6/drop.uplc.golden | 124 ++----- .../Budget/9.6/dropWhile.eval.golden | 6 +- .../Budget/9.6/dropWhile.uplc.golden | 123 ++----- .../BuiltinList/Budget/9.6/elem.eval.golden | 6 +- .../BuiltinList/Budget/9.6/elem.uplc.golden | 141 ++------ .../BuiltinList/Budget/9.6/elemBy.eval.golden | 6 +- .../BuiltinList/Budget/9.6/elemBy.uplc.golden | 123 ++----- .../BuiltinList/Budget/9.6/empty.eval.golden | 6 +- .../BuiltinList/Budget/9.6/empty.uplc.golden | 8 +- .../BuiltinList/Budget/9.6/filter.eval.golden | 6 +- .../BuiltinList/Budget/9.6/filter.uplc.golden | 131 ++----- .../BuiltinList/Budget/9.6/find.eval.golden | 6 +- .../BuiltinList/Budget/9.6/find.uplc.golden | 167 ++------- .../Budget/9.6/findIndexJust.eval.golden | 6 +- .../Budget/9.6/findIndexJust.uplc.golden | 156 ++------ .../Budget/9.6/findIndexNothing.eval.golden | 6 +- .../Budget/9.6/findIndexNothing.uplc.golden | 156 ++------ .../Budget/9.6/findIndices.eval.golden | 6 +- .../Budget/9.6/findIndices.uplc.golden | 148 ++------ .../BuiltinList/Budget/9.6/foldl.eval.golden | 6 +- .../BuiltinList/Budget/9.6/foldl.uplc.golden | 96 ++--- .../BuiltinList/Budget/9.6/foldr.eval.golden | 6 +- .../BuiltinList/Budget/9.6/foldr.uplc.golden | 93 +---- .../Budget/9.6/headEmpty.uplc.golden | 91 +---- .../BuiltinList/Budget/9.6/headOk.eval.golden | 6 +- .../BuiltinList/Budget/9.6/headOk.uplc.golden | 95 +---- .../BuiltinList/Budget/9.6/index.eval.golden | 6 +- .../BuiltinList/Budget/9.6/index.uplc.golden | 149 +------- .../Budget/9.6/indexNegative.uplc.golden | 149 +------- .../Budget/9.6/indexTooLarge.uplc.golden | 149 +------- .../Budget/9.6/lastEmpty.uplc.golden | 133 ++----- .../BuiltinList/Budget/9.6/lastOk.eval.golden | 6 +- .../BuiltinList/Budget/9.6/lastOk.uplc.golden | 122 ++----- .../BuiltinList/Budget/9.6/length.eval.golden | 6 +- .../BuiltinList/Budget/9.6/length.uplc.golden | 64 +--- .../Budget/9.6/listToMaybeJust.eval.golden | 6 +- .../Budget/9.6/listToMaybeJust.uplc.golden | 40 +-- .../Budget/9.6/listToMaybeNothing.eval.golden | 6 +- .../Budget/9.6/listToMaybeNothing.uplc.golden | 35 +- .../BuiltinList/Budget/9.6/map.eval.golden | 6 +- .../BuiltinList/Budget/9.6/map.uplc.golden | 97 +---- .../Budget/9.6/mapMaybe.eval.golden | 6 +- .../Budget/9.6/mapMaybe.uplc.golden | 199 ++--------- .../Budget/9.6/notElem.eval.golden | 6 +- .../Budget/9.6/notElem.uplc.golden | 165 ++------- .../BuiltinList/Budget/9.6/nub.eval.golden | 6 +- .../BuiltinList/Budget/9.6/nub.uplc.golden | 338 +++++------------- .../BuiltinList/Budget/9.6/nubBy.eval.golden | 6 +- .../BuiltinList/Budget/9.6/nubBy.uplc.golden | 240 ++++--------- .../BuiltinList/Budget/9.6/null.eval.golden | 6 +- .../BuiltinList/Budget/9.6/null.uplc.golden | 30 +- .../BuiltinList/Budget/9.6/or.eval.golden | 6 +- .../BuiltinList/Budget/9.6/or.uplc.golden | 114 ++---- .../Budget/9.6/replicate.eval.golden | 6 +- .../Budget/9.6/replicate.uplc.golden | 105 +----- .../Budget/9.6/revAppend.eval.golden | 6 +- .../Budget/9.6/revAppend.uplc.golden | 70 ++-- .../Budget/9.6/reverse.eval.golden | 6 +- .../Budget/9.6/reverse.uplc.golden | 86 ++--- .../Budget/9.6/singleton.eval.golden | 6 +- .../Budget/9.6/singleton.uplc.golden | 12 +- .../Budget/9.6/tailEmpty.uplc.golden | 91 +---- .../BuiltinList/Budget/9.6/tailOk.eval.golden | 6 +- .../BuiltinList/Budget/9.6/tailOk.uplc.golden | 95 +---- .../BuiltinList/Budget/9.6/take.eval.golden | 6 +- .../BuiltinList/Budget/9.6/take.uplc.golden | 132 ++----- .../Budget/9.6/unconsJust.eval.golden | 6 +- .../Budget/9.6/unconsJust.uplc.golden | 57 +-- .../Budget/9.6/unconsNothing.eval.golden | 6 +- .../Budget/9.6/unconsNothing.uplc.golden | 51 +-- .../Budget/9.6/uniqueElementJust.eval.golden | 6 +- .../Budget/9.6/uniqueElementJust.uplc.golden | 180 ++-------- .../9.6/uniqueElementNothing.eval.golden | 6 +- .../9.6/uniqueElementNothing.uplc.golden | 47 +-- .../Budget/9.6/zipWith.eval.golden | 6 +- .../Budget/9.6/zipWith.uplc.golden | 131 ++----- .../test/BuiltinList/Budget/Spec.hs | 1 - 96 files changed, 1257 insertions(+), 4851 deletions(-) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden index d13081a0da9..57639865071 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden @@ -1,5 +1,5 @@ -cpu: 15994784 -mem: 77412 -size: 162 +cpu: 10746784 +mem: 44612 +size: 83 (con (list integer) [1,2,3,4,5,6,7,8,9,10,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).uplc.golden index 6a9ee885e8e..b92b22a7ff2 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).uplc.golden @@ -1,99 +1,22 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - ((\`++` -> - force `++`) - (delay - (delay - (\l -> - (\l - r -> - (\r -> - force - (force - ((\foldr -> - force foldr) - (delay - (delay - (delay - (\f -> - (\f - acc -> - (\acc -> - (\caseList' -> - (\tup -> - (\go -> - (\go -> - force go) - (go - (delay - (\x -> - x)))) - (force tup - (\arg_0 -> - arg_0))) - (delay - (\f -> - f - (force - (force - fix1) - (\go - arg -> - delay - (force - (force - caseList') - acc - (\x -> - (\x - xs -> - (\xs -> - f - x - (force - (go - (delay - (\x -> - x))) - xs)) - xs) - x))))))) - (delay - (delay - (\z - f - xs -> - force - (force - (force - chooseList) - xs - (delay - z) - (delay - (f - (force - headList - xs) - (force - tailList - xs)))))))) - acc) - f)))))) - (force ((\mkCons -> mkCons) mkCons)) - r - l) - r) - l)))) - xs - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay xs) + (delay + ((\xs -> + force mkCons + (force headList xs) + (force (go (delay (\x -> x))) xs)) + (force tailList xs)))))) + (delay (\x -> x))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden index 6e75b247019..ba51fd9d80e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden @@ -1,5 +1,5 @@ -cpu: 392462 -mem: 2132 -size: 20 +cpu: 216462 +mem: 1032 +size: 9 (con (list integer) [42,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).uplc.golden index aaccbae3117..5d97b79876d 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).uplc.golden @@ -1,8 +1 @@ -(program - 1.1.0 - (\xs -> - (\xs -> - force ((\`<|` -> force `<|`) (delay ((\mkCons -> mkCons) mkCons))) - 42 - xs) - xs)) \ No newline at end of file +(program 1.1.0 (\xs -> force mkCons 42 xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.eval.golden index 9aab1e5bba3..d720bac4f0f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.eval.golden @@ -1,5 +1,5 @@ -cpu: 26311700 -mem: 136010 -size: 241 +cpu: 15879700 +mem: 70810 +size: 124 (constr 0 (constr 1) (constr 0)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.uplc.golden index d0a86c4a784..fa8fdb3c973 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.uplc.golden @@ -1,121 +1,33 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - (\lessThanInteger -> - (\ifThenElse -> - force - (delay - (\True - False - Bool_match -> - (\greaterThanEqualsInteger -> - (\caseList' -> - (\all -> - force - (force - (force - (delay - (\Tuple2 Tuple2_match -> Tuple2)) - (delay - (delay - (\arg_0 arg_1 -> - constr 0 [arg_0, arg_1]))) - (delay - (delay - (\x -> - delay - (\case_Tuple2 -> - case - x - [case_Tuple2])))))) - (force (force all) - (\v -> - force greaterThanEqualsInteger - v - ((\v -> force v) (delay 8))) - xs) - (force (force all) - (\v -> - force greaterThanEqualsInteger - v - ((\v -> force v) (delay 0))) - xs)) + (\xs -> + (\greaterThanEqualsInteger -> + (\cse -> + constr 0 + [ (cse (\v -> greaterThanEqualsInteger v 8) xs) + , (cse (\v -> greaterThanEqualsInteger v 0) xs) ]) + (\p -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay (constr 0 [])) (delay - (delay - (\p -> - (\p -> - (\tup -> - (\go -> - (\go -> force go) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force - caseList') - True - (\x -> - (\x - xs -> - (\xs -> - force - (force - (Bool_match - (p - x)) - (delay - (force - (go - (delay - (\x -> - x))) - xs)) - (delay - False))) - xs) - x))))))) - p)))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList xs)))))))) - (delay - (\x -> - (\x y -> - (\y -> - force ifThenElse - (lessThanInteger x y) - False - True) - y) - x)))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True case_False -> - case x [case_True, case_False]))) - ifThenElse) - lessThanInteger) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + ((\xs -> + force + (case + (p (force headList xs)) + [ (delay + (force (go (delay (\x -> x))) + xs)) + , (delay (constr 1 [])) ])) + (force tailList xs)))))) + (delay (\x -> x))))) + (\x y -> + force ifThenElse (lessThanInteger x y) (constr 1 []) (constr 0 [])))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden index 88e4ca25e92..59e7396cde5 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden @@ -1,5 +1,5 @@ -cpu: 4667812 -mem: 24794 -size: 176 +cpu: 2267812 +mem: 9794 +size: 91 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.uplc.golden index 7046ab03f98..46488ebefaa 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.uplc.golden @@ -1,90 +1,27 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (delay - (\True - False - Bool_match -> - (\and -> - force and) - (delay - (force - ((\all -> - force all) - (delay - (delay - (\p -> - (\p -> - (\caseList' -> - (\tup -> - (\go -> - (\go -> force go) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force - caseList') - True - (\x -> - (\x - xs -> - (\xs -> - force - (force - (Bool_match - (p - x)) - (delay - (force - (go - (delay - (\x -> - x))) - xs)) - (delay - False))) - xs) - x))))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList - xs) - (force tailList - xs)))))))) - p)))) - (\x -> - (\x -> - force ((\ifThenElse -> ifThenElse) ifThenElse) - x - True - False) - x))))) - (constr 0 []) - (constr 1 []) - (\x -> - delay (\case_True case_False -> case x [case_True, case_False])) - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay (constr 0 [])) + (delay + ((\xs -> + force + (force + (force ifThenElse + (force headList xs) + (delay + (delay + (force (go (delay (\x -> x))) xs))) + (delay (delay (constr 1 [])))))) + (force tailList xs)))))) + (delay (\x -> x))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.eval.golden index 6596a7683c2..2c1623cc884 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.eval.golden @@ -1,5 +1,5 @@ -cpu: 41341722 -mem: 212296 -size: 241 +cpu: 25389722 +mem: 112596 +size: 124 (constr 0 (constr 0) (constr 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.uplc.golden index a574e2647ac..ad074859ce4 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.uplc.golden @@ -1,121 +1,33 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - (\lessThanInteger -> - (\ifThenElse -> - force - (delay - (\True - False - Bool_match -> - (\greaterThanEqualsInteger -> - (\caseList' -> - (\any -> - force - (force - (force - (delay - (\Tuple2 Tuple2_match -> Tuple2)) - (delay - (delay - (\arg_0 arg_1 -> - constr 0 [arg_0, arg_1]))) - (delay - (delay - (\x -> - delay - (\case_Tuple2 -> - case - x - [case_Tuple2])))))) - (force (force any) - (\v -> - force greaterThanEqualsInteger - v - ((\v -> force v) (delay 8))) - xs) - (force (force any) - (\v -> - force greaterThanEqualsInteger - v - ((\v -> force v) (delay 12))) - xs)) + (\xs -> + (\greaterThanEqualsInteger -> + (\cse -> + constr 0 + [ (cse (\v -> greaterThanEqualsInteger v 8) xs) + , (cse (\v -> greaterThanEqualsInteger v 12) xs) ]) + (\p -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) (delay - (delay - (\p -> - (\p -> - (\tup -> - (\go -> - (\go -> force go) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force - caseList') - False - (\x -> - (\x - xs -> - (\xs -> - force - (force - (Bool_match - (p - x)) - (delay - True) - (delay - (force - (go - (delay - (\x -> - x))) - xs)))) - xs) - x))))))) - p)))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList xs)))))))) - (delay - (\x -> - (\x y -> - (\y -> - force ifThenElse - (lessThanInteger x y) - False - True) - y) - x)))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True case_False -> - case x [case_True, case_False]))) - ifThenElse) - lessThanInteger) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + ((\xs -> + force + (case + (p (force headList xs)) + [ (delay (constr 0 [])) + , (delay + (force (go (delay (\x -> x))) + xs)) ])) + (force tailList xs)))))) + (delay (\x -> x))))) + (\x y -> + force ifThenElse (lessThanInteger x y) (constr 1 []) (constr 0 [])))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden index 34e4493ca8b..57639865071 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden @@ -1,5 +1,5 @@ -cpu: 16074784 -mem: 77912 -size: 167 +cpu: 10746784 +mem: 44612 +size: 83 (con (list integer) [1,2,3,4,5,6,7,8,9,10,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.uplc.golden index e1852e0968e..b92b22a7ff2 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.uplc.golden @@ -1,104 +1,22 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - ((\append -> - force append) - (delay - ((\`++` -> - force `++`) - (delay + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay xs) (delay - (\l -> - (\l - r -> - (\r -> - force - (force - ((\foldr -> - force foldr) - (delay - (delay - (delay - (\f -> - (\f - acc -> - (\acc -> - (\caseList' -> - (\tup -> - (\go -> - (\go -> - force - go) - (go - (delay - (\x -> - x)))) - (force - tup - (\arg_0 -> - arg_0))) - (delay - (\f -> - f - (force - (force - fix1) - (\go - arg -> - delay - (force - (force - caseList') - acc - (\x -> - (\x - xs -> - (\xs -> - f - x - (force - (go - (delay - (\x -> - x))) - xs)) - xs) - x))))))) - (delay - (delay - (\z - f - xs -> - force - (force - (force - chooseList) - xs - (delay - z) - (delay - (f - (force - headList - xs) - (force - tailList - xs)))))))) - acc) - f)))))) - (force ((\mkCons -> mkCons) mkCons)) - r - l) - r) - l)))))) - xs - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + ((\xs -> + force mkCons + (force headList xs) + (force (go (delay (\x -> x))) xs)) + (force tailList xs)))))) + (delay (\x -> x))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden index b3c14b0e80f..4f048966d71 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden @@ -1,5 +1,5 @@ -cpu: 12811372 -mem: 65500 -size: 216 +cpu: 8715372 +mem: 39900 +size: 157 (con (list integer) [1,2,3,4]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden index bd51b7d79c4..d9bd353f343 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.uplc.golden @@ -1,116 +1,45 @@ (program 1.1.0 - ((\fix1 - xss -> - (\xss -> - force - ((\concat -> - force concat) - (delay - (delay - (\`$dMkNil` -> - (\acc -> - (\mkCons -> - (\caseList' -> - (\foldr -> - (\tup -> - (\go -> - (\go -> force go) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force caseList') - acc - (\x -> - (\x - xs -> - (\xs -> - (\r -> - force - (force - (force - foldr)) - (force - mkCons) - r - x) - (force - (go - (delay - (\x -> - x))) - xs)) - xs) - x))))))) - (delay - (delay - (delay - (\f -> - (\f - acc -> - (\acc -> - (\tup -> - (\go -> - (\go -> force go) - (go - (delay - (\x -> x)))) - (force tup - (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force - caseList') - acc - (\x -> - (\x - xs -> - (\xs -> - f - x - (force - (go - (delay - (\x -> - x))) - xs)) - xs) - x))))))) - acc) - f))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList xs)))))))) - mkCons) - `$dMkNil`)))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) - xss) - xss) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xss -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + ((\cse -> + cse + [] + (\x xs -> + (\acc -> + force + ((\f -> + (\s -> + f + (\x -> + f + (\x -> + f (\x -> f (\x -> s s x) x) x) + x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (cse + acc + (\x xs -> + force mkCons + x + (force (go (delay (\x -> x))) + xs)))) + (delay (\x -> x)))) + (force (go (delay (\x -> x))) xs) + x)) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f (force headList xs) (force tailList xs))))))) + (delay (\x -> x))) + xss)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden index 8a5f2a5511b..e5c957c6e94 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden @@ -1,5 +1,5 @@ -cpu: 98528464 -mem: 502312 -size: 352 +cpu: 64688464 +mem: 290812 +size: 237 (con (list integer) [1,1,2,2,3,3,4,4,5,5,6,6,7,7,8,8,9,9,10,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.uplc.golden index 8267b9023ea..506fd482612 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.uplc.golden @@ -1,216 +1,73 @@ (program 1.1.0 - ((\fix1 - xss -> - (\xss -> - (\mkCons -> - (\`$fMkNilInteger` -> - force - (force - ((\concatMap -> - force concatMap) - (delay - (delay - (delay - (\`$dMkNil` -> - (\acc - f -> - (\f -> - (\caseList' -> - (\foldr -> - (\tup -> - (\go -> - (\go -> force go) - (go (delay (\x -> x)))) - (force tup - (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force - caseList') - acc - (\x -> - (\x - xs -> - (\xs -> - (\ys -> - (\l -> - force - (force - (force - foldr)) - (force - mkCons) - ys - l) - (f - x)) - (force - (go - (delay - (\x -> - x))) - xs)) - xs) - x))))))) - (delay - (delay - (delay - (\f -> - (\f - acc -> - (\acc -> - (\tup -> - (\go -> - (\go -> - force - go) - (go - (delay - (\x -> - x)))) - (force - tup - (\arg_0 -> - arg_0))) - (delay - (\f -> - f - (force - (force - fix1) - (\go - arg -> - delay - (force - (force - caseList') - acc - (\x -> - (\x - xs -> - (\xs -> - f - x - (force - (go - (delay - (\x -> - x))) - xs)) - xs) - x))))))) - acc) - f))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList - xs) - (force tailList - xs)))))))) - f) - `$dMkNil`)))))) - (force `$fMkNilInteger`) - (force - ((\subtractInteger -> - (\lessThanEqualsInteger -> - (\ifThenElse -> + (\xss -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + ((\cse -> + cse + [] + (\x xs -> + (\ys -> + (\l -> force - (delay - (\True - False - Bool_match -> - (\replicate -> - force replicate) - (delay - (delay - (\`$dMkNil` - n -> - (\n - x -> - (\x -> - (\tup -> - (\go -> - (\go -> - force go n) - (go - (delay - (\x -> - x)))) - (force tup - (\arg_0 -> - arg_0))) - (delay - (\f -> - f - (force - (force - fix1) - (\go - arg -> - delay - (\n -> - (\n -> - (\b -> - force - (force - (Bool_match - (force - ifThenElse - b - True - False)) - (delay - `$dMkNil`) - (delay - (force - mkCons - x - (force - (go - (delay - (\x -> - x))) - (subtractInteger - n - 1)))))) - (lessThanEqualsInteger - n - 0)) - n)))))) - x) - n))))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True case_False -> - case x [case_True, case_False]))) - ifThenElse) - lessThanEqualsInteger) - subtractInteger) - (force `$fMkNilInteger`) - 2)) - (delay [])) - mkCons - xss) - xss) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + ((\f -> + (\s -> + f + (\x -> + f + (\x -> + f (\x -> f (\x -> s s x) x) x) + x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (cse + ys + (\x xs -> + force mkCons + x + (force (go (delay (\x -> x))) + xs)))) + (delay (\x -> x))) + l) + (force + ((\f -> + (\s -> + f + (\x -> + f + (\x -> + f (\x -> f (\x -> s s x) x) x) + x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\n -> + force + (force ifThenElse + (lessThanEqualsInteger n 0) + (delay []) + (delay + (force mkCons + x + (force + (go (delay (\x -> x))) + (subtractInteger + n + 1))))))) + (delay (\x -> x))) + 2)) + (force (go (delay (\x -> x))) xs))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay + (f (force headList xs) (force tailList xs))))))) + (delay (\x -> x))) + xss)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden index 59b15d35277..4eec5a3badc 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden @@ -1,5 +1,5 @@ -cpu: 392462 -mem: 2132 -size: 20 +cpu: 216462 +mem: 1032 +size: 9 (con (list integer) [0,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.uplc.golden index f610a9ebf43..f4626f1cdc2 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.uplc.golden @@ -1,8 +1 @@ -(program - 1.1.0 - (\xs -> - (\xs -> - force ((\cons -> force cons) (delay ((\mkCons -> mkCons) mkCons))) - 0 - xs) - xs)) \ No newline at end of file +(program 1.1.0 (\xs -> force mkCons 0 xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden index 69c85ba76a0..bd9c475bf9a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden @@ -1,5 +1,5 @@ -cpu: 13258491 -mem: 66502 -size: 193 +cpu: 8410491 +mem: 36202 +size: 115 (con (list integer) [6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden index bfff191cd0d..da557a22073 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.uplc.golden @@ -1,100 +1,28 @@ (program 1.1.0 - ((\fix1 -> - (\subtractInteger -> - (\lessThanEqualsInteger -> - (\ifThenElse -> - (\caseList' -> - force - (delay - (\True - False - Bool_match -> - (\`$fMkNilInteger` -> - (\tup -> - (\drop -> - (\drop xs -> - (\xs -> - force (force drop) - (force `$fMkNilInteger`) - 5 - xs) - xs) - (drop (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\drop - arg -> - delay - (delay - (\`$dMkNil` - n -> - (\n - l -> - (\l -> - (\b -> - force - (force - (Bool_match - (force - ifThenElse - b - True - False)) - (delay l) - (delay - (force - (force - caseList') - `$dMkNil` - (\ds - xs -> - (\xs -> - force - (force - (drop - (delay - (\x -> - x)))) - `$dMkNil` - (subtractInteger - n - 1) - xs) - xs) - l)))) - (lessThanEqualsInteger - n - 0)) - l) - n))))))) - (delay []))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True case_False -> - case x [case_True, case_False]))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList xs)))))))) - ifThenElse) - lessThanEqualsInteger) - subtractInteger) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + ((\drop xs -> force (force drop) [] 5 xs) + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\drop arg -> + delay + (delay + (\`$dMkNil` n l -> + force + (force ifThenElse + (lessThanEqualsInteger n 0) + (delay l) + (delay + (force + (force (force chooseList) + l + (delay `$dMkNil`) + (delay + ((\ds xs -> + force (force (drop (delay (\x -> x)))) + `$dMkNil` + (subtractInteger n 1) + xs) + (force headList l) + (force tailList l)))))))))) + (delay (\x -> x))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden index e921026974a..0c48b6f15cc 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden @@ -1,5 +1,5 @@ -cpu: 13151830 -mem: 69690 -size: 209 +cpu: 6095830 +mem: 25590 +size: 95 (con (list integer) [5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden index b106f42c10a..1b9af8ab54e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.uplc.golden @@ -1,99 +1,28 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (delay - (\True - False - Bool_match -> - force - ((\dropWhile -> - force dropWhile) - (delay - (delay - (\p -> - (\p -> - (\caseList' -> - (\tup -> - (\go -> - (\go eta -> force go eta) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (\xs -> - (\xs -> - force - (force - caseList') - xs - (\x -> - (\x - xs' -> - (\xs' -> - force - (force - (Bool_match - (p - x)) - (delay - (force - (go - (delay - (\x -> - x))) - xs')) - (delay - xs))) - xs') - x) - xs) - xs)))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList - xs)))))))) - p)))) - (\v -> - (\lessThanInteger -> - (\ifThenElse -> - (\lessThanInteger -> force lessThanInteger) - (delay - (\x -> - (\x y -> - (\y -> - (\b -> force ifThenElse b True False) - (lessThanInteger x y)) - y) - x))) - ifThenElse) - lessThanInteger - v - ((\v -> force v) (delay 5))))) - (constr 0 []) - (constr 1 []) - (\x -> - delay (\case_True case_False -> case x [case_True, case_False])) - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay xs) + (delay + ((\xs' -> + force + (force + (force ifThenElse + (lessThanInteger (force headList xs) 5) + (delay + (delay + (force (go (delay (\x -> x))) + xs'))) + (delay (delay xs))))) + (force tailList xs)))))) + (delay (\x -> x))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.eval.golden index 5f220aecc55..bce84c1aa50 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.eval.golden @@ -1,5 +1,5 @@ -cpu: 41356496 -mem: 211596 -size: 236 +cpu: 22876496 +mem: 96096 +size: 107 (constr 0 (constr 0) (constr 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.uplc.golden index 3d4f5c8c4dc..a7446d7ecb5 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.uplc.golden @@ -1,114 +1,31 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - (\caseList' -> - force - (delay - (\True - False - Bool_match -> - (\elem -> - (\equalsInteger -> - (\`$fEqInteger` -> - force - (force - (force - (delay (\Tuple2 Tuple2_match -> Tuple2)) - (delay - (delay - (\arg_0 arg_1 -> - constr 0 [arg_0, arg_1]))) - (delay - (delay - (\x -> - delay - (\case_Tuple2 -> - case x [case_Tuple2])))))) - (force (force elem) (force `$fEqInteger`) 8 xs) - (force (force elem) - (force `$fEqInteger`) - 12 - xs)) - (delay (force equalsInteger))) - (delay - (\x -> - (\x y -> - (\y -> - (\b -> - force - ((\ifThenElse -> ifThenElse) - ifThenElse) - b - True - False) - ((\equalsInteger -> equalsInteger) - equalsInteger - x - y)) - y) - x))) - (delay - (delay - (\`$dEq` - a -> - (\a -> - (\tup -> - (\go -> - (\go -> force go) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force caseList') - False - (\x -> - (\x - xs -> - (\xs -> - force - (force - (Bool_match - (`$dEq` - a - x)) - (delay - True) - (delay - (force - (go - (delay - (\x -> - x))) - xs)))) - xs) - x))))))) - a))))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True case_False -> case x [case_True, case_False]))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f (force headList xs) (force tailList xs)))))))) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xs -> + (\cse -> constr 0 [(cse 8 xs), (cse 12 xs)]) + (\a -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + ((\xs -> + force + (force + (force ifThenElse + (equalsInteger + a + (force headList xs)) + (delay (delay (constr 0 []))) + (delay + (delay + (force (go (delay (\x -> x))) + xs)))))) + (force tailList xs)))))) + (delay (\x -> x)))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden index 49d3c7d5659..b9ef254cf9e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden @@ -1,5 +1,5 @@ -cpu: 22342024 -mem: 113812 -size: 198 +cpu: 12822024 +mem: 54312 +size: 95 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.uplc.golden index a64f6bd0daa..357c71c629b 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.uplc.golden @@ -1,97 +1,30 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (delay - (\True - False - Bool_match -> - force - ((\elemBy -> - force elemBy) - (delay - (delay - (\eq -> - (\eq - y -> - (\y -> - (\caseList' -> - (\tup -> - (\go -> - (\go -> force go) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force caseList') - False - (\x -> - (\x - xs -> - (\xs -> - force - (force - (Bool_match - (eq - x - y)) - (delay - True) - (delay - (force - (go - (delay - (\x -> - x))) - xs)))) - xs) - x))))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList - xs)))))))) - y) - eq)))) - ((\lessThanEqualsInteger -> - (\ifThenElse -> - (\lessThanEqualsInteger -> - force lessThanEqualsInteger) - (delay - (\x -> - (\x y -> - (\y -> - (\b -> force ifThenElse b True False) - (lessThanEqualsInteger x y)) - y) - x))) - ifThenElse) - lessThanEqualsInteger))) - (constr 0 []) - (constr 1 []) - (\x -> - delay (\case_True case_False -> case x [case_True, case_False])) - 0 - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + ((\xs -> + force + (force + (force ifThenElse + (lessThanEqualsInteger + (force headList xs) + 0) + (delay (delay (constr 0 []))) + (delay + (delay + (force (go (delay (\x -> x))) + xs)))))) + (force tailList xs)))))) + (delay (\x -> x))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden index 4792048209b..906f70b6c08 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden @@ -1,5 +1,5 @@ -cpu: 384100 -mem: 2500 -size: 24 +cpu: 64100 +mem: 500 +size: 4 (con (list integer) []) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.uplc.golden index 395a8da9f59..c2725f32aa6 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.uplc.golden @@ -1,7 +1 @@ -(program - 1.1.0 - (\ds -> - force - ((\empty -> force empty) - (delay ((\mkNil -> force mkNil) (delay (delay (\v -> v)))))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])))) \ No newline at end of file +(program 1.1.0 (\ds -> [])) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden index 979cc415dd9..1cb6d45cab2 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden @@ -1,5 +1,5 @@ -cpu: 25324094 -mem: 121582 -size: 218 +cpu: 16588094 +mem: 66982 +size: 110 (con (list integer) [2,4,6,8,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.uplc.golden index 4643be45682..3e74357867c 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.uplc.golden @@ -1,107 +1,28 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (delay - (\True - False - Bool_match -> - force - ((\filter -> - force filter) - (delay - (delay - (\`$dMkNil` -> - (\acc - p -> - (\p -> - (\mkCons -> - (\caseList' -> - (\tup -> - (\go -> - (\go -> force go) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force - caseList') - acc - (\x -> - (\x - xs -> - (\xs -> - (\xs -> - force - (force - (Bool_match - (p - x)) - (delay - (force - mkCons - x - xs)) - (delay - xs))) - (force - (go - (delay - (\x -> - x))) - xs)) - xs) - x))))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList - xs) - (force tailList - xs)))))))) - mkCons) - p) - `$dMkNil`)))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) - ((\modInteger -> - (\ifThenElse -> - (\equalsInteger -> - (\even -> force even) - (delay - (\n -> - (\n -> - (\x -> - (\b -> - force ifThenElse b True False) - (equalsInteger x 0)) - (modInteger n 2)) - n))) - equalsInteger) - ifThenElse) - modInteger))) - (constr 0 []) - (constr 1 []) - (\x -> - delay (\case_True case_False -> case x [case_True, case_False])) - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay []) + (delay + ((\x xs -> + (\xs -> + force + (force + (force ifThenElse + (equalsInteger (modInteger x 2) 0) + (delay (delay (force mkCons x xs))) + (delay (delay xs))))) + (force (go (delay (\x -> x))) xs)) + (force headList xs) + (force tailList xs)))))) + (delay (\x -> x))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.eval.golden index aaed420f5f8..a4ecac644a1 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.eval.golden @@ -1,5 +1,5 @@ -cpu: 42221722 -mem: 217796 -size: 268 +cpu: 26269722 +mem: 118096 +size: 128 (constr 0 (constr 0 (con integer 8)) (constr 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.uplc.golden index 5c2e5607723..aff11190216 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.uplc.golden @@ -1,141 +1,34 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - (\lessThanInteger -> - (\ifThenElse -> - force - (delay - (\True - False - Bool_match -> - (\greaterThanEqualsInteger -> - (\caseList' -> - force - (delay - (\Just - Nothing - Maybe_match -> - (\find -> - force - (force - (force - (delay - (\Tuple2 Tuple2_match -> - Tuple2)) - (delay - (delay - (\arg_0 arg_1 -> - constr 0 - [arg_0, arg_1]))) - (delay - (delay - (\x -> - delay - (\case_Tuple2 -> - case - x - [ case_Tuple2 ])))))) - (force (force find) - (\v -> - force greaterThanEqualsInteger - v - ((\v -> force v) (delay 8))) - xs) - (force (force find) - (\v -> - force greaterThanEqualsInteger - v - ((\v -> force v) (delay 12))) - xs)) - (delay - (delay - (\p -> - (\p -> - (\tup -> - (\go -> - (\go -> force go) - (go - (delay - (\x -> x)))) - (force tup - (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force - caseList') - (force - Nothing) - (\x -> - (\x - xs -> - (\xs -> - force - (force - (Bool_match - (p - x)) - (delay - (force - Just - x)) - (delay - (force - (go - (delay - (\x -> - x))) - xs)))) - xs) - x))))))) - p))))) - (delay (\arg_0 -> constr 0 [arg_0])) + (\xs -> + (\greaterThanEqualsInteger -> + (\cse -> + constr 0 + [ (cse (\v -> greaterThanEqualsInteger v 8) xs) + , (cse (\v -> greaterThanEqualsInteger v 12) xs) ]) + (\p -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs (delay (constr 1 [])) (delay - (\x -> - delay - (\case_Just case_Nothing -> - case x [case_Just, case_Nothing])))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList xs)))))))) - (delay - (\x -> - (\x y -> - (\y -> - force ifThenElse - (lessThanInteger x y) - False - True) - y) - x)))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True case_False -> - case x [case_True, case_False]))) - ifThenElse) - lessThanInteger) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + ((\x xs -> + force + (case + (p x) + [ (delay (constr 0 [x])) + , (delay + (force (go (delay (\x -> x))) + xs)) ])) + (force headList xs) + (force tailList xs)))))) + (delay (\x -> x))))) + (\x y -> + force ifThenElse (lessThanInteger x y) (constr 1 []) (constr 0 [])))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden index 1303bbe252a..eccb9d68d89 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden @@ -1,5 +1,5 @@ -cpu: 12920480 -mem: 68698 -size: 262 +cpu: 5592480 +mem: 22898 +size: 105 (constr 0 (con integer 3)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.uplc.golden index 8fb1bfc4c42..ce0a37f00de 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.uplc.golden @@ -1,130 +1,30 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (delay - (\True - False - Bool_match -> - force - (force - (delay - (\Just - Nothing - Maybe_match -> - (\findIndex -> - force findIndex) - (delay - (delay - (\f -> - (\f -> - (\caseList' -> - (\addInteger -> - (\tup -> - (\go -> - (\go -> force go 0) - (go (delay (\x -> x)))) - (force tup - (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (\i -> - (\i -> - force - (force - caseList') - (force - Nothing) - (\x -> - (\x - xs -> - (\xs -> - force - (force - (Bool_match - (f - x)) - (delay - (force - Just - i)) - (delay - (force - (go - (delay - (\x -> - x))) - (addInteger - i - 1) - xs)))) - xs) - x)) - i)))))) - addInteger) - (delay - (delay - (\z f xs -> - force - (force - (force chooseList) - xs - (delay z) - (delay - (f - (force headList - xs) - (force tailList - xs)))))))) - f))))) - (delay (\arg_0 -> constr 0 [arg_0])) - (delay (constr 1 [])) - (delay - (\x -> - delay - (\case_Just case_Nothing -> - case x [case_Just, case_Nothing])))) - (\v -> - (\`==` -> - (\ifThenElse -> - (\equalsInteger -> - (\equalsInteger -> - (\`$fEqInteger` -> - (\v -> force v) - (delay - (force (force `==`) - (force `$fEqInteger`)))) - (delay (force equalsInteger))) - (delay - (\x -> - (\x y -> - (\y -> - (\b -> - force ifThenElse b True False) - (equalsInteger x y)) - y) - x))) - equalsInteger) - ifThenElse) - (delay (delay (\v -> v))) - v - ((\v -> force v) (delay 4))))) - (constr 0 []) - (constr 1 []) - (\x -> - delay (\case_True case_False -> case x [case_True, case_False])) - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\i xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + ((\xs -> + force + (force + (force ifThenElse + (equalsInteger (force headList xs) 4) + (delay (delay (constr 0 [i]))) + (delay + (delay + (force (go (delay (\x -> x))) + (addInteger i 1) + xs)))))) + (force tailList xs)))))) + (delay (\x -> x))) + 0 + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden index 0f598c161c3..4a9170dd9fa 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden @@ -1,5 +1,5 @@ -cpu: 31679064 -mem: 165332 -size: 262 +cpu: 15087064 +mem: 61632 +size: 105 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.uplc.golden index e8d19fa4e92..514fe355b04 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.uplc.golden @@ -1,130 +1,30 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (delay - (\True - False - Bool_match -> - force - (force - (delay - (\Just - Nothing - Maybe_match -> - (\findIndex -> - force findIndex) - (delay - (delay - (\f -> - (\f -> - (\caseList' -> - (\addInteger -> - (\tup -> - (\go -> - (\go -> force go 0) - (go (delay (\x -> x)))) - (force tup - (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (\i -> - (\i -> - force - (force - caseList') - (force - Nothing) - (\x -> - (\x - xs -> - (\xs -> - force - (force - (Bool_match - (f - x)) - (delay - (force - Just - i)) - (delay - (force - (go - (delay - (\x -> - x))) - (addInteger - i - 1) - xs)))) - xs) - x)) - i)))))) - addInteger) - (delay - (delay - (\z f xs -> - force - (force - (force chooseList) - xs - (delay z) - (delay - (f - (force headList - xs) - (force tailList - xs)))))))) - f))))) - (delay (\arg_0 -> constr 0 [arg_0])) - (delay (constr 1 [])) - (delay - (\x -> - delay - (\case_Just case_Nothing -> - case x [case_Just, case_Nothing])))) - (\v -> - (\`==` -> - (\ifThenElse -> - (\equalsInteger -> - (\equalsInteger -> - (\`$fEqInteger` -> - (\v -> force v) - (delay - (force (force `==`) - (force `$fEqInteger`)))) - (delay (force equalsInteger))) - (delay - (\x -> - (\x y -> - (\y -> - (\b -> - force ifThenElse b True False) - (equalsInteger x y)) - y) - x))) - equalsInteger) - ifThenElse) - (delay (delay (\v -> v))) - v - ((\v -> force v) (delay 99))))) - (constr 0 []) - (constr 1 []) - (\x -> - delay (\case_True case_False -> case x [case_True, case_False])) - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\i xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + ((\xs -> + force + (force + (force ifThenElse + (equalsInteger (force headList xs) 99) + (delay (delay (constr 0 [i]))) + (delay + (delay + (force (go (delay (\x -> x))) + (addInteger i 1) + xs)))))) + (force tailList xs)))))) + (delay (\x -> x))) + 0 + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden index 39a825dea34..b09c26dccf1 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden @@ -1,5 +1,5 @@ -cpu: 31632174 -mem: 154702 -size: 243 +cpu: 18768174 +mem: 74302 +size: 119 (con (list integer) [0,2,4,6,8]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.uplc.golden index 738e6b909d3..a24ef8885db 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.uplc.golden @@ -1,119 +1,33 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (delay - (\True - False - Bool_match -> - force - ((\findIndices -> - force findIndices) - (delay - (delay - (\p -> - (\p -> - (\mkCons -> - (\caseList' -> - (\addInteger -> - (\tup -> - (\go -> - (\go -> force go 0) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (\i -> - (\i -> - force - (force - caseList') - [] - (\x -> - (\x - xs -> - (\xs -> - (\indices -> - force - (force - (Bool_match - (p - x)) - (delay - (force - mkCons - i - indices)) - (delay - indices))) - (force - (go - (delay - (\x -> - x))) - (addInteger - i - 1) - xs)) - xs) - x)) - i)))))) - addInteger) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList - xs)))))))) - mkCons) - p)))) - ((\modInteger -> - (\ifThenElse -> - (\equalsInteger -> - (\even -> - (\odd -> force odd) - (delay - (\n -> - (\n -> - force - (force (Bool_match (force even n)) - (delay False) - (delay True))) - n))) - (delay - (\n -> - (\n -> - (\x -> - (\b -> - force ifThenElse b True False) - (equalsInteger x 0)) - (modInteger n 2)) - n))) - equalsInteger) - ifThenElse) - modInteger))) - (constr 0 []) - (constr 1 []) - (\x -> - delay (\case_True case_False -> case x [case_True, case_False])) - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\i xs -> + force + (force (force chooseList) + xs + (delay []) + (delay + ((\x xs -> + (\indices -> + force + (force + (force ifThenElse + (equalsInteger (modInteger x 2) 0) + (delay (delay indices)) + (delay + (delay + (force mkCons i indices)))))) + (force (go (delay (\x -> x))) + (addInteger i 1) + xs)) + (force headList xs) + (force tailList xs)))))) + (delay (\x -> x))) + 0 + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden index 107e5657664..69a4b2809ae 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden @@ -1,5 +1,5 @@ -cpu: 19108694 -mem: 95412 -size: 179 +cpu: 11780694 +mem: 49612 +size: 90 (con integer 3628800) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden index 70c3cdd0d1a..9eb114cf73e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.uplc.golden @@ -1,78 +1,24 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (force - ((\foldl -> - force foldl) - (delay - (delay + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\acc xs -> + force + (force (force chooseList) + xs + (delay acc) (delay - (\f -> - (\f -> - (\caseList' -> - (\tup -> - (\go -> - (\go eta -> force go eta) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (\acc -> - (\acc -> - force - (force caseList') - acc - (\x -> - (\x - xs -> - (\xs -> - force - (go - (delay - (\x -> - x))) - (f - acc - x) - xs) - xs) - x)) - acc)))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList - xs)))))))) - f)))))) - (force ((\`*` -> force `*`) (delay (delay (\v -> v)))) - ((\multiplyInteger -> - (\multiplyInteger -> - (\`$fMultiplicativeSemigroupInteger` -> - force `$fMultiplicativeSemigroupInteger`) - (delay (force multiplyInteger))) - (delay (\x -> (\x y -> (\y -> multiplyInteger x y) y) x))) - multiplyInteger)) - 1 - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + ((\x xs -> + force (go (delay (\x -> x))) + (multiplyInteger acc x) + xs) + (force headList xs) + (force tailList xs)))))) + (delay (\x -> x))) + 1 + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden index bba173fd542..411dbd777d6 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden @@ -1,5 +1,5 @@ -cpu: 18203244 -mem: 89112 -size: 174 +cpu: 10875244 +mem: 43312 +size: 82 (con integer 55) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.uplc.golden index 1d7dd967a92..940a1646b23 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.uplc.golden @@ -1,77 +1,22 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (force - ((\foldr -> - force foldr) - (delay - (delay + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay 0) (delay - (\f -> - (\f - acc -> - (\acc -> - (\caseList' -> - (\tup -> - (\go -> - (\go -> force go) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force caseList') - acc - (\x -> - (\x - xs -> - (\xs -> - f - x - (force - (go - (delay - (\x -> - x))) - xs)) - xs) - x))))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList - xs)))))))) - acc) - f)))))) - (force ((\`+` -> force `+`) (delay (delay (\v -> v)))) - ((\addInteger -> - (\addInteger -> - (\`$fAdditiveSemigroupInteger` -> - force `$fAdditiveSemigroupInteger`) - (delay (force addInteger))) - (delay (\x -> (\x y -> (\y -> addInteger x y) y) x))) - addInteger)) - 0 - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + ((\xs -> + addInteger + (force headList xs) + (force (go (delay (\x -> x))) xs)) + (force tailList xs)))))) + (delay (\x -> x))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.uplc.golden index 663629ecaed..793b96b43d4 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headEmpty.uplc.golden @@ -2,89 +2,8 @@ 1.1.0 (\ds -> force - ((\head -> - force head) - (delay - (delay - (force - (delay - (\Unit - Unit_match -> - force - (force - ((\caseList -> - force caseList) - (delay - (delay - (delay - (\nilCase -> - (\nilCase - consCase -> - (\consCase - l -> - (\l -> - force - (force - ((\caseList' -> - caseList') - (delay - (delay - (\z - f - xs -> - force - (force - (force - chooseList) - xs - (delay - z) - (delay - (f - (force - headList - xs) - (force - tailList - xs))))))))) - nilCase - (\x -> - (\x xs -> - (\xs ds -> - consCase x xs) - xs) - x) - l - Unit) - l) - consCase) - nilCase)))))) - (\ds -> - force - ((\unitval -> - (\trace -> - (\error -> - (\traceError -> force traceError) - (delay - (delay - (\str -> - (\str -> - (\x -> - force error unitval) - (force trace - str - Unit)) - str)))) - (delay (\thunk -> error))) - trace) - ()) - ((\headEmptyBuiltinListError -> - force headEmptyBuiltinListError) - (delay "PT23"))))) - (constr 0 []) - (\x -> delay (\case_Unit -> case x [case_Unit])) - (\x -> (\x ds -> x) x))))) - (force - ((\mkNil -> (\empty -> force empty) (delay (force mkNil))) - (delay (delay (\v -> v)))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay []))))) \ No newline at end of file + (force (force chooseList) + [] + (delay (\ds -> (\x -> error) (force trace "PT23" (constr 0 [])))) + (delay ((\x xs ds -> x) (force headList []) (force tailList [])))) + (constr 0 []))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden index b8a7fce99d3..80fd21ad390 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden @@ -1,5 +1,5 @@ -cpu: 1977907 -mem: 10696 -size: 152 +cpu: 761907 +mem: 3096 +size: 39 (con integer 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.uplc.golden index 1a0d4edaa2a..8a8d6b52439 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.uplc.golden @@ -1,92 +1,9 @@ (program 1.1.0 (\xs -> - (\xs -> - force - ((\head -> - force head) - (delay - (delay - (force - (delay - (\Unit - Unit_match -> - force - (force - ((\caseList -> - force caseList) - (delay - (delay - (delay - (\nilCase -> - (\nilCase - consCase -> - (\consCase - l -> - (\l -> - force - (force - ((\caseList' -> - caseList') - (delay - (delay - (\z - f - xs -> - force - (force - (force - chooseList) - xs - (delay - z) - (delay - (f - (force - headList - xs) - (force - tailList - xs))))))))) - nilCase - (\x -> - (\x xs -> - (\xs ds -> - consCase - x - xs) - xs) - x) - l - Unit) - l) - consCase) - nilCase)))))) - (\ds -> - force - ((\unitval -> - (\trace -> - (\error -> - (\traceError -> force traceError) - (delay - (delay - (\str -> - (\str -> - (\x -> - force error - unitval) - (force trace - str - Unit)) - str)))) - (delay (\thunk -> error))) - trace) - ()) - ((\headEmptyBuiltinListError -> - force headEmptyBuiltinListError) - (delay "PT23"))))) - (constr 0 []) - (\x -> delay (\case_Unit -> case x [case_Unit])) - (\x -> (\x ds -> x) x))))) - xs) - xs)) \ No newline at end of file + force + (force (force chooseList) + xs + (delay (\ds -> (\x -> error) (force trace "PT23" (constr 0 [])))) + (delay ((\x xs ds -> x) (force headList xs) (force tailList xs)))) + (constr 0 []))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden index e4db0f2b557..afd1cf3dfa2 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden @@ -1,5 +1,5 @@ -cpu: 2945742 -mem: 15202 -size: 196 +cpu: 1441742 +mem: 5802 +size: 72 (con integer 6) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden index a545d303924..866c5fb0c76 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.uplc.golden @@ -1,135 +1,22 @@ (program 1.1.0 (\xs -> - (\xs -> - force - ((\`!!` -> - force `!!`) + force + ((\traceError -> + force ifThenElse + (lessThanInteger 5 0) + (delay (traceError "PT21")) (delay - (delay - (\xs -> - (\xs - i -> - (\i -> - (\b -> - force - ((\unitval -> - (\trace -> - (\error -> - force - (delay - (\Unit - Unit_match -> - (\traceError -> - force - (force - (delay - (\True - False - Bool_match -> - Bool_match - (force - ((\ifThenElse -> - ifThenElse) - ifThenElse) - b - True - False))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True - case_False -> - case - x - [ case_True - , case_False ]))) - (delay - (force - (force - traceError) - ((\builtinListNegativeIndexError -> - force - builtinListNegativeIndexError) - (delay - "PT21")))) - (delay - ((\l -> - force - (force - ((\caseList' -> - caseList') - (delay - (delay - (\z - f - xs -> - force - (force - (force - chooseList) - xs - (delay - z) - (delay - (f - (force - headList - xs) - (force - tailList - xs))))))))) - (\_ann -> - force - (force - traceError) - ((\builtinListIndexTooLargeError -> - force - builtinListIndexTooLargeError) - (delay - "PT22"))) - (\x -> - (\x - xs - ds - _ann -> - x) - x) - l - Unit - Unit) - (force - ((\drop -> - drop) - dropList) - i - xs)))) - (delay - (delay - (\str -> - (\str -> - (\x -> - force error - unitval) - (force trace - str - Unit)) - str))))) - (constr 0 []) - (\x -> - delay - (\case_Unit -> - case x [case_Unit]))) - (delay (\thunk -> error))) - trace) - ())) - ((\lessThanInteger -> lessThanInteger) - lessThanInteger - i - 0)) - i) - xs)))) - xs - 5) - xs)) \ No newline at end of file + ((\l -> + force + (force (force chooseList) + l + (delay (\_ann -> traceError "PT22")) + (delay + ((\x xs ds _ann -> x) + (force headList l) + (force tailList l)))) + (constr 0 []) + (constr 0 [])) + (force dropList 5 xs)))) + (\str -> (\x -> error) (force trace str (constr 0 [])))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden index b5f18a18e88..751f886b406 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexNegative.uplc.golden @@ -1,135 +1,24 @@ (program 1.1.0 (\xs -> - (\xs -> + (\i -> force - ((\`!!` -> - force `!!`) - (delay + ((\traceError -> + force ifThenElse + (lessThanInteger i 0) + (delay (traceError "PT21")) (delay - (\xs -> - (\xs - i -> - (\i -> - (\b -> - force - ((\unitval -> - (\trace -> - (\error -> - force - (delay - (\Unit - Unit_match -> - (\traceError -> - force - (force - (delay - (\True - False - Bool_match -> - Bool_match - (force - ((\ifThenElse -> - ifThenElse) - ifThenElse) - b - True - False))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True - case_False -> - case - x - [ case_True - , case_False ]))) - (delay - (force - (force - traceError) - ((\builtinListNegativeIndexError -> - force - builtinListNegativeIndexError) - (delay - "PT21")))) - (delay - ((\l -> - force - (force - ((\caseList' -> - caseList') - (delay - (delay - (\z - f - xs -> - force - (force - (force - chooseList) - xs - (delay - z) - (delay - (f - (force - headList - xs) - (force - tailList - xs))))))))) - (\_ann -> - force - (force - traceError) - ((\builtinListIndexTooLargeError -> - force - builtinListIndexTooLargeError) - (delay - "PT22"))) - (\x -> - (\x - xs - ds - _ann -> - x) - x) - l - Unit - Unit) - (force - ((\drop -> - drop) - dropList) - i - xs)))) - (delay - (delay - (\str -> - (\str -> - (\x -> - force error - unitval) - (force trace - str - Unit)) - str))))) - (constr 0 []) - (\x -> - delay - (\case_Unit -> - case x [case_Unit]))) - (delay (\thunk -> error))) - trace) - ())) - ((\lessThanInteger -> lessThanInteger) - lessThanInteger - i - 0)) - i) - xs)))) - xs - ((\integerNegate -> integerNegate) (\x -> subtractInteger 0 x) 1)) - xs)) \ No newline at end of file + ((\l -> + force + (force (force chooseList) + l + (delay (\_ann -> traceError "PT22")) + (delay + ((\x xs ds _ann -> x) + (force headList l) + (force tailList l)))) + (constr 0 []) + (constr 0 [])) + (force dropList i xs)))) + (\str -> (\x -> error) (force trace str (constr 0 []))))) + (subtractInteger 0 1))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden index 969b4dae2b5..d6793d58743 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/indexTooLarge.uplc.golden @@ -1,135 +1,22 @@ (program 1.1.0 (\xs -> - (\xs -> - force - ((\`!!` -> - force `!!`) + force + ((\traceError -> + force ifThenElse + (lessThanInteger 10 0) + (delay (traceError "PT21")) (delay - (delay - (\xs -> - (\xs - i -> - (\i -> - (\b -> - force - ((\unitval -> - (\trace -> - (\error -> - force - (delay - (\Unit - Unit_match -> - (\traceError -> - force - (force - (delay - (\True - False - Bool_match -> - Bool_match - (force - ((\ifThenElse -> - ifThenElse) - ifThenElse) - b - True - False))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True - case_False -> - case - x - [ case_True - , case_False ]))) - (delay - (force - (force - traceError) - ((\builtinListNegativeIndexError -> - force - builtinListNegativeIndexError) - (delay - "PT21")))) - (delay - ((\l -> - force - (force - ((\caseList' -> - caseList') - (delay - (delay - (\z - f - xs -> - force - (force - (force - chooseList) - xs - (delay - z) - (delay - (f - (force - headList - xs) - (force - tailList - xs))))))))) - (\_ann -> - force - (force - traceError) - ((\builtinListIndexTooLargeError -> - force - builtinListIndexTooLargeError) - (delay - "PT22"))) - (\x -> - (\x - xs - ds - _ann -> - x) - x) - l - Unit - Unit) - (force - ((\drop -> - drop) - dropList) - i - xs)))) - (delay - (delay - (\str -> - (\str -> - (\x -> - force error - unitval) - (force trace - str - Unit)) - str))))) - (constr 0 []) - (\x -> - delay - (\case_Unit -> - case x [case_Unit]))) - (delay (\thunk -> error))) - trace) - ())) - ((\lessThanInteger -> lessThanInteger) - lessThanInteger - i - 0)) - i) - xs)))) - xs - 10) - xs)) \ No newline at end of file + ((\l -> + force + (force (force chooseList) + l + (delay (\_ann -> traceError "PT22")) + (delay + ((\x xs ds _ann -> x) + (force headList l) + (force tailList l)))) + (constr 0 []) + (constr 0 [])) + (force dropList 10 xs)))) + (\str -> (\x -> error) (force trace str (constr 0 [])))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden index 9a0fad96a0b..8132ce9d202 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastEmpty.uplc.golden @@ -1,110 +1,29 @@ (program 1.1.0 - ((\fix1 -> - force - (delay - (\Unit - Unit_match -> - (\traceError -> - (\lastEmptyBuiltinListError -> - (\caseList' -> - (\caseList -> - (\empty -> - (\`$fMkNilInteger` -> - (\tup -> - (\last -> - (\last ds -> - force (force last) - (force (force empty) - (force `$fMkNilInteger`))) - (last (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\last - arg -> - delay - (delay - (force - (force - (force caseList)) - (\ds -> - force - (force traceError) - (force - lastEmptyBuiltinListError)) - (\x -> - (\x - xs -> - (\xs -> - force - (force - caseList') - x - (\ds - ds -> - force - (force - (last - (delay - (\x -> - x)))) - xs) - xs) - xs) - x)))))))) - (delay [])) - (delay - ((\mkNil -> force mkNil) - (delay (delay (\v -> v)))))) - (delay - (delay - (delay - (\nilCase -> - (\nilCase consCase -> - (\consCase l -> - (\l -> - force (force caseList') - nilCase - (\x -> - (\x xs -> - (\xs ds -> consCase x xs) - xs) - x) - l - Unit) - l) - consCase) - nilCase))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList xs)))))))) - (delay "PT25")) + ((\caseList' -> + (\last ds -> force (force last) []) + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\last arg -> + delay (delay - (delay - (\str -> - (\str -> - (\x -> - force - ((\error -> error) (delay (\thunk -> error))) - ((\unitval -> unitval) ())) - (force ((\trace -> trace) trace) str Unit)) - str))))) - (constr 0 []) - (\x -> delay (\case_Unit -> case x [case_Unit]))) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\l -> + caseList' + (\ds -> + (\x -> error) (force trace "PT25" (constr 0 []))) + (\x xs ds -> + caseList' + x + (\ds ds -> + force (force (last (delay (\x -> x)))) xs) + xs) + l + (constr 0 [])))) + (delay (\x -> x)))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden index e8fe43350d0..f894403069d 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden @@ -1,5 +1,5 @@ -cpu: 28175427 -mem: 141856 -size: 223 +cpu: 19055427 +mem: 84856 +size: 119 (con integer 10) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden index 5c3bdbf0016..ea05f13d767 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.uplc.golden @@ -1,99 +1,29 @@ (program 1.1.0 - ((\fix1 -> - force - (delay - (\Unit - Unit_match -> - (\traceError -> - (\lastEmptyBuiltinListError -> - (\caseList' -> - (\caseList -> - (\tup -> - (\last -> - (\last xs -> (\xs -> force (force last) xs) xs) - (last (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\last - arg -> - delay - (delay - (force - (force (force caseList)) - (\ds -> - force - (force traceError) - (force - lastEmptyBuiltinListError)) - (\x -> - (\x - xs -> - (\xs -> - force - (force caseList') - x - (\ds - ds -> - force - (force - (last - (delay - (\x -> - x)))) - xs) - xs) - xs) - x)))))))) - (delay - (delay - (delay - (\nilCase -> - (\nilCase consCase -> - (\consCase l -> - (\l -> - force (force caseList') - nilCase - (\x -> - (\x xs -> - (\xs ds -> consCase x xs) - xs) - x) - l - Unit) - l) - consCase) - nilCase))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList xs)))))))) - (delay "PT25")) + ((\caseList' -> + (\last xs -> force (force last) xs) + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\last arg -> + delay (delay - (delay - (\str -> - (\str -> - (\x -> - force - ((\error -> error) (delay (\thunk -> error))) - ((\unitval -> unitval) ())) - (force ((\trace -> trace) trace) str Unit)) - str))))) - (constr 0 []) - (\x -> delay (\case_Unit -> case x [case_Unit]))) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\l -> + caseList' + (\ds -> + (\x -> error) (force trace "PT25" (constr 0 []))) + (\x xs ds -> + caseList' + x + (\ds ds -> + force (force (last (delay (\x -> x)))) xs) + xs) + l + (constr 0 [])))) + (delay (\x -> x)))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden index 0aa1922b1c3..3c15082a487 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden @@ -1,5 +1,5 @@ -cpu: 15739244 -mem: 73712 -size: 128 +cpu: 11355244 +mem: 46312 +size: 85 (con integer 10) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.uplc.golden index 5cb666693bf..188963e1150 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.uplc.golden @@ -1,49 +1,21 @@ (program 1.1.0 - ((\fix1 xs -> - (\xs -> - force - ((\length -> force length) - (delay - (delay - ((\caseList' -> - (\addInteger -> - (\tup -> - (\go -> (\go -> force go) (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force (force fix1) - (\go arg -> - delay - (force (force caseList') - 0 - (\x xs -> - (\xs -> - (\y -> addInteger 1 y) - (force - (go - (delay - (\x -> x))) - xs)) - xs))))))) - addInteger) + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay 0) (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList xs))))))))))) - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + ((\x xs -> + addInteger 1 (force (go (delay (\x -> x))) xs)) + (force headList xs) + (force tailList xs)))))) + (delay (\x -> x))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden index e256823f282..c51ab8f5ceb 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden @@ -1,5 +1,5 @@ -cpu: 1481907 -mem: 7596 -size: 83 +cpu: 681907 +mem: 2596 +size: 25 (constr 0 (con integer 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.uplc.golden index d2c935ac931..6e71d21bd03 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.uplc.golden @@ -1,37 +1,9 @@ (program 1.1.0 (\xs -> - (\xs -> - force - (force - (delay - (\Just Nothing Maybe_match -> - (\listToMaybe -> force listToMaybe) - (delay - (delay - (force - (force - ((\caseList' -> caseList') - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList - xs))))))))) - (force Nothing) - (\x -> (\x ds -> force Just x) x)))))) - (delay (\arg_0 -> constr 0 [arg_0])) - (delay (constr 1 [])) - (delay - (\x -> - delay - (\case_Just case_Nothing -> - case x [case_Just, case_Nothing])))) - xs) - xs)) \ No newline at end of file + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + ((\ds -> constr 0 [(force headList xs)]) (force tailList xs)))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden index 033a1106036..6eec30a642f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden @@ -1,5 +1,5 @@ -cpu: 1253094 -mem: 7132 -size: 100 +cpu: 357094 +mem: 1532 +size: 25 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.uplc.golden index fe4672ddd54..65216008d85 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.uplc.golden @@ -2,37 +2,8 @@ 1.1.0 (\ds -> force - (force - (delay - (\Just Nothing Maybe_match -> - (\listToMaybe -> force listToMaybe) - (delay - (delay - (force - (force - ((\caseList' -> caseList') - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList - xs))))))))) - (force Nothing) - (\x -> (\x ds -> force Just x) x)))))) - (delay (\arg_0 -> constr 0 [arg_0])) + (force (force chooseList) + [] (delay (constr 1 [])) (delay - (\x -> - delay - (\case_Just case_Nothing -> - case x [case_Just, case_Nothing])))) - (force - ((\mkNil -> (\empty -> force empty) (delay (force mkNil))) - (delay (delay (\v -> v)))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay []))))) \ No newline at end of file + ((\ds -> constr 0 [(force headList [])]) (force tailList [])))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.eval.golden index 590009edd5e..6043cf47790 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.eval.golden @@ -1,5 +1,5 @@ -cpu: 25102864 -mem: 128032 -size: 191 +cpu: 12350864 +mem: 48332 +size: 84 (con (list integer) [2,3,4,5,6,7,8,9,10,11]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden index 7f5be9f7c48..324e6833e47 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.uplc.golden @@ -1,81 +1,20 @@ (program 1.1.0 - ((\fix1 -> - force - (force - ((\map -> - force map) - (delay - (delay - (delay - (\`$dMkNil` - f -> - (\f -> - (\mkCons -> - (\caseList' -> - (\tup -> - (\go -> - (\go -> force go) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force caseList') - `$dMkNil` - (\x -> - (\x - xs -> - (\xs -> - force - mkCons - (f x) - (force - (go - (delay - (\x -> - x))) - xs)) - xs) - x))))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList - xs)))))))) - mkCons) - f)))))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) - (\v -> - (\`+` -> - (\addInteger -> - (\addInteger -> - (\`$fAdditiveSemigroupInteger` -> - (\v -> force v) - (delay - (force (force `+`) - (force `$fAdditiveSemigroupInteger`)))) - (delay (force addInteger))) - (delay (\x -> (\x y -> (\y -> addInteger x y) y) x))) - addInteger) - (delay (delay (\v -> v))) - v - ((\v -> force v) (delay 1)))) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay []) + (delay + ((\xs -> + force mkCons + (addInteger (force headList xs) 1) + (force (go (delay (\x -> x))) xs)) + (force tailList xs)))))) + (delay (\x -> x))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden index 9ecb3535d37..a01ca7f20f8 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden @@ -1,5 +1,5 @@ -cpu: 37164094 -mem: 195582 -size: 287 +cpu: 16908094 +mem: 68982 +size: 122 (con (list integer) [1,3,5,7,9]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.uplc.golden index 4194a574fba..9cb4012c613 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.uplc.golden @@ -1,163 +1,40 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (delay - (\Just - Nothing - Maybe_match -> - force - (force - ((\mapMaybe -> - force mapMaybe) - (delay - (delay - (delay - (\`$dMkNil` - f -> - (\f -> - (\mkCons -> - (\caseList' -> - (\tup -> - (\go -> - (\go -> force go) - (go (delay (\x -> x)))) - (force tup - (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force - caseList') - `$dMkNil` - (\x -> - (\x - xs -> - (\xs -> - force - (force - (force - Maybe_match - (f - x)) - (\y -> - delay - (force - mkCons - y - (force - (go - (delay - (\x -> - x))) - xs))) - (delay - (force - (go - (delay - (\x -> - x))) - xs)))) - xs) - x))))))) - (delay - (delay - (\z f xs -> - force - (force - (force chooseList) - xs - (delay z) - (delay - (f - (force - headList - xs) - (force - tailList - xs)))))))) - mkCons) - f)))))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) - (\x -> - (\x -> - force - (force - (force - (delay - (\True - False - Bool_match -> - Bool_match - ((\modInteger -> - (\ifThenElse -> - (\equalsInteger -> - (\even -> - (\odd -> - force odd) - (delay - (\n -> - (\n -> - force - (force - (Bool_match - (force - even - n)) - (delay - False) - (delay - True))) - n))) - (delay - (\n -> - (\n -> - (\x -> - (\b -> - force - ifThenElse - b - True - False) - (equalsInteger - x - 0)) - (modInteger - n - 2)) - n))) - equalsInteger) - ifThenElse) - modInteger - x))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True case_False -> - case x [case_True, case_False]))) - (delay (force Just x)) - (delay (force Nothing)))) - x))) - (delay (\arg_0 -> constr 0 [arg_0])) - (delay (constr 1 [])) - (delay - (\x -> - delay - (\case_Just case_Nothing -> - case x [case_Just, case_Nothing]))) - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay []) + (delay + ((\xs -> + force + (case + ((\x -> + force + (force + (force ifThenElse + (equalsInteger + (modInteger x 2) + 0) + (delay (delay (constr 1 []))) + (delay + (delay (constr 0 [x])))))) + (force headList xs)) + [ (\y -> + delay + (force mkCons + y + (force (go (delay (\x -> x))) + xs))) + , (delay + (force (go (delay (\x -> x))) xs)) ])) + (force tailList xs)))))) + (delay (\x -> x))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden index a177893b8cb..d9cb74f8b16 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden @@ -1,5 +1,5 @@ -cpu: 23178984 -mem: 118512 -size: 240 +cpu: 12970984 +mem: 54712 +size: 101 (constr 0) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.uplc.golden index d8cee9f0c2f..c899f12f0c9 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.uplc.golden @@ -1,136 +1,33 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (delay - (\True - False - Bool_match -> - force - ((\notElem -> - force notElem) - (delay - (delay - (\`$dEq` - a -> - (\a - eta -> - (\x -> - (\g -> - force - (force (Bool_match (g x)) - (delay False) - (delay True))) - ((\g -> - force g) - (delay - (force - ((\elem -> - force elem) - (delay - (delay - (\`$dEq` - a -> - (\a -> - (\caseList' -> - (\tup -> - (\go -> - (\go -> - force - go) - (go - (delay - (\x -> - x)))) - (force - tup - (\arg_0 -> - arg_0))) - (delay - (\f -> - f - (force - (force - fix1) - (\go - arg -> - delay - (force - (force - caseList') - False - (\x -> - (\x - xs -> - (\xs -> - force - (force - (Bool_match - (`$dEq` - a - x)) - (delay - True) - (delay - (force - (go - (delay - (\x -> - x))) - xs)))) - xs) - x))))))) - (delay - (delay - (\z - f - xs -> - force - (force - (force - chooseList) - xs - (delay - z) - (delay - (f - (force - headList - xs) - (force - tailList - xs)))))))) - a)))) - `$dEq` - a)))) - eta) - a)))) - ((\ifThenElse -> - (\equalsInteger -> - (\equalsInteger -> - (\`$fEqInteger` -> force `$fEqInteger`) - (delay (force equalsInteger))) - (delay - (\x -> - (\x y -> - (\y -> - (\b -> force ifThenElse b True False) - (equalsInteger x y)) - y) - x))) - equalsInteger) - ifThenElse))) - (constr 0 []) - (constr 1 []) - (\x -> - delay (\case_True case_False -> case x [case_True, case_False])) - 42 - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xs -> + force + (case + (force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + ((\xs -> + force + (force + (force ifThenElse + (equalsInteger + 42 + (force headList xs)) + (delay (delay (constr 0 []))) + (delay + (delay + (force (go (delay (\x -> x))) + xs)))))) + (force tailList xs)))))) + (delay (\x -> x))) + xs) + [(delay (constr 1 [])), (delay (constr 0 []))]))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden index 425cbbca95d..578b5127098 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden @@ -1,5 +1,5 @@ -cpu: 279527998 -mem: 1415424 -size: 446 +cpu: 182519998 +mem: 809124 +size: 266 (con (list integer) [1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden index 981d112c087..a5873a4dd45 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.uplc.golden @@ -1,258 +1,90 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - (\mkCons -> - (\caseList' -> - force - (delay - (\True - False - Bool_match -> - force - ((\nub -> - force nub) - (delay - (delay - (\`$dEq` - `$dMkNil` -> - force - ((\nubBy -> - force nubBy) - (delay - (delay - (\`$dMkNil` -> - (\x - eq -> - (\eq -> - (\elemBy -> - (\tup -> - (\go -> - (\go eta -> - (\y -> - force - go - y - x) - eta) - (go - (delay - (\x -> - x)))) - (force tup - (\arg_0 -> - arg_0))) + (\xs -> + (\caseList' -> + (\eta -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go + arg -> + delay + (\l + xs -> + caseList' + [] + (\y + ys -> + force + (case + (force + ((\f -> + (\s -> + f + (\x -> + f + (\x -> + f + (\x -> + f (\x -> s s x) x) + x) + x)) + (\s -> f (\x -> s s x))) + (\go + arg -> + delay + (caseList' + (constr 1 []) + (\x + xs -> + force + (force + (force + ifThenElse + (equalsInteger x y) + (delay (delay - (\f -> - f - (force - (force - fix1) - (\go - arg -> - delay - (\l -> - (\l - xs -> - (\xs -> - force - (force - caseList') - `$dMkNil` - (\y -> - (\y - ys -> - (\ys -> - force - (force - (Bool_match - (force - (force - elemBy) - eq - y - xs)) - (delay - (force - (go - (delay - (\x -> - x))) - ys - xs)) - (delay - (force - mkCons - y - (force - (go - (delay - (\x -> - x))) - ys - (force - mkCons - y - xs)))))) - ys) - y) - l) - xs) - l)))))) + (constr 0 + []))) (delay (delay - (\eq -> - (\eq - y -> - (\y -> - (\tup -> - (\go -> - (\go -> - force - go) - (go - (delay - (\x -> - x)))) - (force - tup - (\arg_0 -> - arg_0))) - (delay - (\f -> - f - (force - (force - fix1) - (\go - arg -> - delay - (force - (force - caseList') - False - (\x -> - (\x - xs -> - (\xs -> - force - (force - (Bool_match - (eq - x - y)) - (delay - True) - (delay - (force - (go - (delay - (\x -> - x))) - xs)))) - xs) - x))))))) - y) - eq)))) - eq) - `$dMkNil`)))) - `$dMkNil` - `$dEq`)))) - ((\ifThenElse -> - (\equalsInteger -> - (\equalsInteger -> - (\`$fEqInteger` -> force `$fEqInteger`) - (delay (force equalsInteger))) - (delay - (\x -> - (\x y -> - (\y -> - (\b -> - force ifThenElse b True False) - (equalsInteger x y)) - y) - x))) - equalsInteger) - ifThenElse))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True case_False -> - case x [case_True, case_False])) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) - (force - ((\foldr -> - (\`++` -> - (\append -> force append) (delay (force `++`))) - (delay - (delay - (\l -> - (\l r -> - (\r -> - force (force (force foldr)) - (force mkCons) - r - l) - r) - l)))) - (delay - (delay - (delay - (\f -> - (\f - acc -> - (\acc -> - (\tup -> - (\go -> - (\go -> force go) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force caseList') - acc - (\x -> - (\x - xs -> - (\xs -> - f - x - (force - (go - (delay - (\x -> - x))) - xs)) - xs) - x))))))) - acc) - f))))) - xs - xs)) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList xs)))))))) - mkCons) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (force + (go + (delay + (\x -> + x))) + xs)))))))) + (delay (\x -> x))) + xs) + [ (delay + (force (go (delay (\x -> x))) ys xs)) + , (delay + ((\cse -> + cse + (force (go (delay (\x -> x))) + ys + (cse xs))) + (force mkCons y))) ])) + l)) + (delay (\x -> x))) + eta + []) + (force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (caseList' + xs + (\x xs -> + force mkCons x (force (go (delay (\x -> x))) xs)))) + (delay (\x -> x))) + xs)) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden index 9617aa85d1b..d6cdfe158dd 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden @@ -1,5 +1,5 @@ -cpu: 44700119 -mem: 236770 -size: 326 +cpu: 26348119 +mem: 122070 +size: 199 (con (list integer) [1]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden index 5918acc020d..40b19b3d8f7 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.uplc.golden @@ -1,181 +1,71 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (delay - (\True - False - Bool_match -> - force - ((\nubBy -> - force nubBy) - (delay - (delay - (\`$dMkNil` -> - (\x - eq -> - (\eq -> - (\mkCons -> - (\caseList' -> - (\elemBy -> - (\tup -> - (\go -> - (\go eta -> - (\y -> force go y x) - eta) - (go (delay (\x -> x)))) - (force tup - (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (\l -> - (\l - xs -> - (\xs -> - force - (force - caseList') - `$dMkNil` - (\y -> - (\y - ys -> - (\ys -> - force - (force - (Bool_match - (force - (force - elemBy) - eq - y - xs)) - (delay - (force - (go - (delay - (\x -> - x))) - ys - xs)) - (delay - (force - mkCons - y - (force - (go - (delay - (\x -> - x))) - ys - (force - mkCons - y - xs)))))) - ys) - y) - l) - xs) - l)))))) - (delay - (delay - (\eq -> - (\eq - y -> - (\y -> - (\tup -> - (\go -> - (\go -> - force go) - (go - (delay - (\x -> - x)))) - (force tup - (\arg_0 -> - arg_0))) - (delay - (\f -> - f - (force - (force - fix1) - (\go - arg -> - delay - (force - (force - caseList') - False - (\x -> - (\x - xs -> - (\xs -> - force - (force - (Bool_match - (eq - x - y)) - (delay - True) - (delay - (force - (go - (delay - (\x -> - x))) - xs)))) - xs) - x))))))) + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\l xs -> + (\cse -> + cse + [] + (\y ys -> + force + (case + (force + ((\f -> + (\s -> + f + (\x -> + f + (\x -> + f + (\x -> f (\x -> s s x) x) + x) + x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (cse + (constr 1 []) + (\x xs -> + force + (force + (force ifThenElse + (lessThanEqualsInteger + x y) - eq)))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) (delay - (f - (force headList - xs) - (force tailList + (delay + (constr 0 []))) + (delay + (delay + (force + (go + (delay + (\x -> + x))) xs)))))))) - mkCons) - eq) - `$dMkNil`)))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) - ((\lessThanEqualsInteger -> - (\ifThenElse -> - (\lessThanEqualsInteger -> - force lessThanEqualsInteger) + (delay (\x -> x))) + xs) + [ (delay (force (go (delay (\x -> x))) ys xs)) + , (delay + ((\cse -> + cse + (force (go (delay (\x -> x))) + ys + (cse xs))) + (force mkCons y))) ])) + l) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) (delay - (\x -> - (\x y -> - (\y -> - (\b -> force ifThenElse b True False) - (lessThanEqualsInteger x y)) - y) - x))) - ifThenElse) - lessThanEqualsInteger))) - (constr 0 []) - (constr 1 []) - (\x -> - delay (\case_True case_False -> case x [case_True, case_False])) - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (f (force headList xs) (force tailList xs))))))) + (delay (\x -> x))) + xs + [])) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden index 95980926e9c..01e48473efb 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden @@ -1,5 +1,5 @@ -cpu: 1030582 -mem: 5633 -size: 62 +cpu: 374582 +mem: 1533 +size: 14 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.uplc.golden index c96b8eda181..05a9d295460 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.uplc.golden @@ -1,31 +1,3 @@ (program 1.1.0 - (\xs -> - (\xs -> - force - (force - (delay - (\True False Bool_match -> - (\null -> force null) - (delay - ((\null -> force null) - (delay - (delay - (\l -> - (\l -> - (\b -> - force - ((\ifThenElse -> ifThenElse) - ifThenElse) - b - True - False) - (force ((\null -> null) nullList) l)) - l))))))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True case_False -> case x [case_True, case_False]))) - xs) - xs)) \ No newline at end of file + (\xs -> force ifThenElse (force nullList xs) (constr 0 []) (constr 1 []))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden index 2b5491f5e73..9f8d7fe2679 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden @@ -1,5 +1,5 @@ -cpu: 2837956 -mem: 15597 -size: 176 +cpu: 1189956 +mem: 5297 +size: 91 (constr 0) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.uplc.golden index f0891e31df7..3e448871e90 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.uplc.golden @@ -1,90 +1,28 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (delay - (\True - False - Bool_match -> - (\or -> - force or) - (delay - (force - ((\any -> - force any) - (delay - (delay - (\p -> - (\p -> - (\caseList' -> - (\tup -> - (\go -> - (\go -> force go) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (force - (force - caseList') - False - (\x -> - (\x - xs -> - (\xs -> - force - (force - (Bool_match - (p - x)) - (delay - True) - (delay - (force - (go - (delay - (\x -> - x))) - xs)))) - xs) - x))))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList - xs) - (force tailList - xs)))))))) - p)))) - (\x -> - (\x -> - force ((\ifThenElse -> ifThenElse) ifThenElse) - x - True - False) - x))))) - (constr 0 []) - (constr 1 []) - (\x -> - delay (\case_True case_False -> case x [case_True, case_False])) - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs -> + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + ((\xs -> + force + (force + (force ifThenElse + (force headList xs) + (delay (delay (constr 0 []))) + (delay + (delay + (force (go (delay (\x -> x))) + xs)))))) + (force tailList xs)))))) + (delay (\x -> x))) + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden index 30afabd4bc6..e62031ccd9d 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden @@ -1,5 +1,5 @@ -cpu: 15246546 -mem: 76662 -size: 162 +cpu: 9694546 +mem: 41962 +size: 81 (con (list integer) [0,0,0,0,0,0,0,0,0,0]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.uplc.golden index 8223fbd1617..1a6bf510bd4 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.uplc.golden @@ -1,88 +1,21 @@ (program 1.1.0 - ((\fix1 - ds -> - force - ((\replicate -> - force replicate) - (delay - (delay - (\`$dMkNil` - n -> - (\n - x -> - (\x -> - (\subtractInteger -> - (\mkCons -> - (\lessThanEqualsInteger -> - (\ifThenElse -> - force - (delay - (\True - False - Bool_match -> - (\tup -> - (\go -> - (\go -> force go n) - (go (delay (\x -> x)))) - (force tup - (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (\n -> - (\n -> - (\b -> - force - (force - (Bool_match - (force - ifThenElse - b - True - False)) - (delay - `$dMkNil`) - (delay - (force - mkCons - x - (force - (go - (delay - (\x -> - x))) - (subtractInteger - n - 1)))))) - (lessThanEqualsInteger - n - 0)) - n))))))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True case_False -> - case - x - [case_True, case_False]))) - ifThenElse) - lessThanEqualsInteger) - mkCons) - subtractInteger) - x) - n)))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) - 10 - 0) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\ds -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\n -> + force + (force ifThenElse + (lessThanEqualsInteger n 0) + (delay []) + (delay + (force mkCons + 0 + (force (go (delay (\x -> x))) + (subtractInteger n 1))))))) + (delay (\x -> x))) + 10)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden index b67588a7bf9..62ae47ba0f1 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden @@ -1,5 +1,5 @@ -cpu: 17962784 -mem: 89712 -size: 139 +cpu: 12154784 +mem: 53412 +size: 97 (con (list integer) [10,9,8,7,6,5,4,3,2,1,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.uplc.golden index afa37ead415..c65dfe8fa3e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.uplc.golden @@ -1,52 +1,22 @@ (program 1.1.0 - ((\fix1 -> - (\mkCons -> - (\caseList' -> - (\tup -> - (\revAppend -> - (\revAppend xs -> (\xs -> force (force revAppend) xs xs) xs) - (revAppend (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force (force fix1) - (\revAppend arg -> - delay - (delay - (\l -> - (\l r -> - (\r -> - force (force caseList') - r - (\x -> - (\x xs -> - (\xs -> - force - (force - (revAppend - (delay - (\x -> x)))) - xs - (force mkCons x r)) - xs) - x) - l) - r) - l))))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f (force headList xs) (force tailList xs)))))))) - mkCons) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + ((\revAppend xs -> force (force revAppend) xs xs) + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\revAppend arg -> + delay + (delay + (\l r -> + force + (force (force chooseList) + l + (delay r) + (delay + ((\x xs -> + force (force (revAppend (delay (\x -> x)))) + xs + (force mkCons x r)) + (force headList l) + (force tailList l))))))) + (delay (\x -> x))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden index e2ab77168e2..da272af74fc 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden @@ -1,5 +1,5 @@ -cpu: 18298784 -mem: 91812 -size: 160 +cpu: 12154784 +mem: 53412 +size: 97 (con (list integer) [10,9,8,7,6,5,4,3,2,1]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.uplc.golden index ab2501f2e27..b5453975712 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.uplc.golden @@ -1,68 +1,22 @@ (program 1.1.0 - ((\fix1 -> - (\mkCons -> - (\caseList' -> - (\`$fMkNilInteger` -> - (\tup -> - (\revAppend -> - (\revAppend xs -> - (\xs -> - force - ((\reverse -> force reverse) - (delay - (delay - (\`$dMkNil` xs -> - (\xs -> - force (force revAppend) - xs - `$dMkNil`) - xs)))) - (force `$fMkNilInteger`) - xs) - xs) - (revAppend (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force (force fix1) - (\revAppend arg -> - delay - (delay - (\l -> - (\l r -> - (\r -> - force (force caseList') - r - (\x -> - (\x xs -> - (\xs -> - force - (force - (revAppend - (delay - (\x -> x)))) - xs - (force mkCons x r)) - xs) - x) - l) - r) - l))))))) - (delay [])) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f (force headList xs) (force tailList xs)))))))) - mkCons) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + ((\revAppend xs -> force (force revAppend) xs []) + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\revAppend arg -> + delay + (delay + (\l r -> + force + (force (force chooseList) + l + (delay r) + (delay + ((\x xs -> + force (force (revAppend (delay (\x -> x)))) + xs + (force mkCons x r)) + (force headList l) + (force tailList l))))))) + (delay (\x -> x))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden index 94f06afbd59..ca9e33cc851 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden @@ -1,5 +1,5 @@ -cpu: 600462 -mem: 3432 -size: 33 +cpu: 216462 +mem: 1032 +size: 9 (con (list integer) [42]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden index 9d1ae6095dd..fb912294641 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.uplc.golden @@ -1,11 +1 @@ -(program - 1.1.0 - (\ds -> - force - ((\singleton -> force singleton) - (delay - (delay - (\`$dMkNil` x -> - (\x -> force ((\mkCons -> mkCons) mkCons) x `$dMkNil`) x)))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) - 42)) \ No newline at end of file +(program 1.1.0 (\ds -> force mkCons 42 [])) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.uplc.golden index b956778bcc4..bf34b9f1680 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailEmpty.uplc.golden @@ -2,89 +2,8 @@ 1.1.0 (\ds -> force - ((\tail -> - force tail) - (delay - (delay - (force - (delay - (\Unit - Unit_match -> - force - (force - ((\caseList -> - force caseList) - (delay - (delay - (delay - (\nilCase -> - (\nilCase - consCase -> - (\consCase - l -> - (\l -> - force - (force - ((\caseList' -> - caseList') - (delay - (delay - (\z - f - xs -> - force - (force - (force - chooseList) - xs - (delay - z) - (delay - (f - (force - headList - xs) - (force - tailList - xs))))))))) - nilCase - (\x -> - (\x xs -> - (\xs ds -> - consCase x xs) - xs) - x) - l - Unit) - l) - consCase) - nilCase)))))) - (\ds -> - force - ((\unitval -> - (\trace -> - (\error -> - (\traceError -> force traceError) - (delay - (delay - (\str -> - (\str -> - (\x -> - force error unitval) - (force trace - str - Unit)) - str)))) - (delay (\thunk -> error))) - trace) - ()) - ((\lastEmptyBuiltinListError -> - force lastEmptyBuiltinListError) - (delay "PT25"))))) - (constr 0 []) - (\x -> delay (\case_Unit -> case x [case_Unit])) - (\ds xs -> xs))))) - (force - ((\mkNil -> (\empty -> force empty) (delay (force mkNil))) - (delay (delay (\v -> v)))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay []))))) \ No newline at end of file + (force (force chooseList) + [] + (delay (\ds -> (\x -> error) (force trace "PT25" (constr 0 [])))) + (delay ((\x xs ds -> xs) (force headList []) (force tailList [])))) + (constr 0 []))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden index c19f0f15561..86aa7f56508 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden @@ -1,5 +1,5 @@ -cpu: 1929907 -mem: 10396 -size: 149 +cpu: 761907 +mem: 3096 +size: 39 (con (list integer) [2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.uplc.golden index d519a628e50..266a36fc6ba 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.uplc.golden @@ -1,92 +1,9 @@ (program 1.1.0 (\xs -> - (\xs -> - force - ((\tail -> - force tail) - (delay - (delay - (force - (delay - (\Unit - Unit_match -> - force - (force - ((\caseList -> - force caseList) - (delay - (delay - (delay - (\nilCase -> - (\nilCase - consCase -> - (\consCase - l -> - (\l -> - force - (force - ((\caseList' -> - caseList') - (delay - (delay - (\z - f - xs -> - force - (force - (force - chooseList) - xs - (delay - z) - (delay - (f - (force - headList - xs) - (force - tailList - xs))))))))) - nilCase - (\x -> - (\x xs -> - (\xs ds -> - consCase - x - xs) - xs) - x) - l - Unit) - l) - consCase) - nilCase)))))) - (\ds -> - force - ((\unitval -> - (\trace -> - (\error -> - (\traceError -> force traceError) - (delay - (delay - (\str -> - (\str -> - (\x -> - force error - unitval) - (force trace - str - Unit)) - str)))) - (delay (\thunk -> error))) - trace) - ()) - ((\lastEmptyBuiltinListError -> - force lastEmptyBuiltinListError) - (delay "PT25"))))) - (constr 0 []) - (\x -> delay (\case_Unit -> case x [case_Unit])) - (\ds xs -> xs))))) - xs) - xs)) \ No newline at end of file + force + (force (force chooseList) + xs + (delay (\ds -> (\x -> error) (force trace "PT25" (constr 0 [])))) + (delay ((\x xs ds -> xs) (force headList xs) (force tailList xs)))) + (constr 0 []))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden index 99c0cf52688..9659a137189 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden @@ -1,5 +1,5 @@ -cpu: 14308301 -mem: 70962 -size: 204 +cpu: 8932301 +mem: 37362 +size: 117 (con (list integer) [1,2,3,4,5]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.uplc.golden index 3edaab18f33..aca01e7a065 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.uplc.golden @@ -1,108 +1,30 @@ (program 1.1.0 - ((\fix1 -> - (\subtractInteger -> - (\mkCons -> - (\lessThanEqualsInteger -> - (\ifThenElse -> - (\caseList' -> - force - (delay - (\True - False - Bool_match -> - (\`$fMkNilInteger` -> - (\tup -> - (\take -> - (\take xs -> - (\xs -> - force (force take) - (force `$fMkNilInteger`) - 5 - xs) - xs) - (take (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f + ((\take xs -> force (force take) [] 5 xs) + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\take arg -> + delay + (delay + (\`$dMkNil` n l -> + force + (force ifThenElse + (lessThanEqualsInteger n 0) + (delay `$dMkNil`) + (delay + (force + (force (force chooseList) + l + (delay `$dMkNil`) + (delay + ((\xs -> + force mkCons + (force headList l) (force - (force fix1) - (\take - arg -> - delay - (delay - (\`$dMkNil` - n -> - (\n - l -> - (\l -> - (\b -> - force - (force - (Bool_match - (force - ifThenElse - b - True - False)) - (delay - `$dMkNil`) - (delay - (force - (force - caseList') - `$dMkNil` - (\x -> - (\x - xs -> - (\xs -> - force - mkCons - x - (force - (force - (take - (delay - (\x -> - x)))) - `$dMkNil` - (subtractInteger - n - 1) - xs)) - xs) - x) - l)))) - (lessThanEqualsInteger - n - 0)) - l) - n))))))) - (delay []))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True case_False -> - case x [case_True, case_False]))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList xs)))))))) - ifThenElse) - lessThanEqualsInteger) - mkCons) - subtractInteger) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (force (take (delay (\x -> x)))) + `$dMkNil` + (subtractInteger n 1) + xs)) + (force tailList l)))))))))) + (delay (\x -> x))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden index f9c66c25a9b..710ffb00b0f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden @@ -1,5 +1,5 @@ -cpu: 1849907 -mem: 9896 -size: 113 +cpu: 665907 +mem: 2496 +size: 24 (constr 0 (constr 0 (con integer 1) (con (list integer) [2,3,4,5,6,7,8,9,10]))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.uplc.golden index 0fb3fd76117..a4563742bf5 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.uplc.golden @@ -1,53 +1,10 @@ (program 1.1.0 (\xs -> - (\xs -> - force - (force - (delay - (\Just Nothing Maybe_match -> - force - (delay - (\Tuple2 Tuple2_match -> - (\uncons -> force uncons) - (delay - (delay - (force - (force - ((\caseList' -> caseList') - (delay - (delay - (\z f xs -> - force - (force - (force chooseList) - xs - (delay z) - (delay - (f - (force headList - xs) - (force tailList - xs))))))))) - (force Nothing) - (\h -> - (\h t -> - (\t -> - force Just - (force (force Tuple2) h t)) - t) - h)))))) - (delay (delay (\arg_0 arg_1 -> constr 0 [arg_0, arg_1]))) - (delay - (delay - (\x -> - delay (\case_Tuple2 -> case x [case_Tuple2])))))) - (delay (\arg_0 -> constr 0 [arg_0])) - (delay (constr 1 [])) - (delay - (\x -> - delay - (\case_Just case_Nothing -> - case x [case_Just, case_Nothing])))) - xs) - xs)) \ No newline at end of file + force + (force (force chooseList) + xs + (delay (constr 1 [])) + (delay + (constr 0 + [(constr 0 [(force headList xs), (force tailList xs)])]))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden index 2e801f04470..6597dd039a7 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden @@ -1,5 +1,5 @@ -cpu: 1381094 -mem: 7932 -size: 130 +cpu: 357094 +mem: 1532 +size: 24 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.uplc.golden index 6020571bc48..1facba8acf0 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.uplc.golden @@ -2,52 +2,9 @@ 1.1.0 (\ds -> force - (force - (delay - (\Just Nothing Maybe_match -> - force - (delay - (\Tuple2 Tuple2_match -> - (\uncons -> force uncons) - (delay - (delay - (force - (force - ((\caseList' -> caseList') - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList - xs) - (force tailList - xs))))))))) - (force Nothing) - (\h -> - (\h t -> - (\t -> - force Just - (force (force Tuple2) h t)) - t) - h)))))) - (delay (delay (\arg_0 arg_1 -> constr 0 [arg_0, arg_1]))) - (delay - (delay - (\x -> - delay (\case_Tuple2 -> case x [case_Tuple2])))))) - (delay (\arg_0 -> constr 0 [arg_0])) + (force (force chooseList) + [] (delay (constr 1 [])) (delay - (\x -> - delay - (\case_Just case_Nothing -> - case x [case_Just, case_Nothing])))) - (force - ((\mkNil -> (\empty -> force empty) (delay (force mkNil))) - (delay (delay (\v -> v)))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay []))))) \ No newline at end of file + (constr 0 + [(constr 0 [(force headList []), (force tailList [])])]))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden index 007da693932..3c4f62cfc59 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden @@ -1,5 +1,5 @@ -cpu: 6358050 -mem: 32962 -size: 259 +cpu: 3878050 +mem: 17462 +size: 146 (constr 0 (con integer 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden index b4dfc0bf4c5..5d6504bd0ff 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.uplc.golden @@ -1,147 +1,37 @@ (program 1.1.0 - ((\fix1 -> - (\caseList' -> - (\subtractInteger -> - (\mkCons -> - (\lessThanEqualsInteger -> - (\ifThenElse -> - force - (delay - (\True - False - Bool_match -> - (\`$fMkNilInteger` -> - (\tup -> - (\take -> - (\take - xs -> - (\xs -> - force - (force - (delay - (\Just - Nothing - Maybe_match -> - (\uniqueElement -> - force uniqueElement) - (delay - (delay - (force - (force - caseList') - (force - Nothing) - (\x -> - (\x -> - force - (force - caseList') - (force - Just - x) - (\ds - ds -> - force - Nothing)) - x)))))) - (delay - (\arg_0 -> - constr 0 [arg_0])) - (delay (constr 1 [])) - (delay - (\x -> - delay - (\case_Just - case_Nothing -> - case - x - [ case_Just - , case_Nothing ])))) - (force (force take) - (force `$fMkNilInteger`) - 1 - xs)) - xs) - (take (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\take - arg -> - delay - (delay - (\`$dMkNil` - n -> - (\n - l -> - (\l -> - (\b -> - force - (force - (Bool_match - (force - ifThenElse - b - True - False)) - (delay - `$dMkNil`) - (delay - (force - (force - caseList') - `$dMkNil` - (\x -> - (\x - xs -> - (\xs -> - force - mkCons - x - (force - (force - (take - (delay - (\x -> - x)))) - `$dMkNil` - (subtractInteger - n - 1) - xs)) - xs) - x) - l)))) - (lessThanEqualsInteger - n - 0)) - l) - n))))))) - (delay []))) - (constr 0 []) - (constr 1 []) - (\x -> - delay - (\case_True case_False -> - case x [case_True, case_False]))) - ifThenElse) - lessThanEqualsInteger) - mkCons) - subtractInteger) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay (f (force headList xs) (force tailList xs)))))))) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + ((\caseList' -> + (\take xs -> + caseList' + (constr 1 []) + (\x -> caseList' (constr 0 [x]) (\ds ds -> constr 1 [])) + (force (force take) [] 1 xs)) + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\take arg -> + delay + (delay + (\`$dMkNil` n l -> + force + (force ifThenElse + (lessThanEqualsInteger n 0) + (delay `$dMkNil`) + (delay + (caseList' + `$dMkNil` + (\x xs -> + force mkCons + x + (force (force (take (delay (\x -> x)))) + `$dMkNil` + (subtractInteger n 1) + xs)) + l)))))) + (delay (\x -> x)))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden index d453e46980e..01ce14fd5fd 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden @@ -1,5 +1,5 @@ -cpu: 1253094 -mem: 7132 -size: 108 +cpu: 549094 +mem: 2732 +size: 45 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.uplc.golden index c3122437b79..5915b2d2824 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.uplc.golden @@ -1,41 +1,12 @@ (program 1.1.0 (\ds -> - force - (force - (delay - (\Just Nothing Maybe_match -> - (\uniqueElement -> force uniqueElement) - (delay - (delay - ((\caseList' -> - force (force caseList') - (force Nothing) - (\x -> - (\x -> - force (force caseList') - (force Just x) - (\ds ds -> force Nothing)) - x)) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList xs) - (force tailList xs)))))))))))) - (delay (\arg_0 -> constr 0 [arg_0])) - (delay (constr 1 [])) - (delay - (\x -> - delay - (\case_Just case_Nothing -> - case x [case_Just, case_Nothing])))) - (force - ((\mkNil -> (\empty -> force empty) (delay (force mkNil))) - (delay (delay (\v -> v)))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay []))))) \ No newline at end of file + (\cse -> + cse (constr 1 []) (\x -> cse (constr 0 [x]) (\ds ds -> constr 1 []))) + (\z f xs -> + force + (force (force chooseList) + xs + (delay z) + (delay (f (force headList xs) (force tailList xs))))) + [])) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden index 5a3a300d075..82e897cf1c7 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden @@ -1,5 +1,5 @@ -cpu: 31584934 -mem: 150892 -size: 222 +cpu: 22448934 +mem: 93792 +size: 110 (con (list integer) [2,4,6,8,10,12,14,16,18,20]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.uplc.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.uplc.golden index cc0ee8ec242..f49e5963301 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.uplc.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.uplc.golden @@ -1,105 +1,30 @@ (program 1.1.0 - ((\fix1 - xs -> - (\xs -> - force - (force - (force - ((\zipWith -> - force zipWith) - (delay - (delay - (delay - (delay - (\`$dMkNil` - f -> - (\f -> - (\mkCons -> - (\caseList' -> - (\tup -> - (\go -> - (\go eta eta -> - force go eta eta) - (go (delay (\x -> x)))) - (force tup (\arg_0 -> arg_0))) - (delay - (\f -> - f - (force - (force fix1) - (\go - arg -> - delay - (\xs -> - (\xs - ys -> - (\ys -> - force - (force - caseList') - `$dMkNil` - (\x -> - (\x - xs' -> - (\xs' -> - force - (force - caseList') - `$dMkNil` - (\y -> - (\y - ys' -> - (\ys' -> - force - mkCons - (f - x - y) - (force - (go - (delay - (\x -> - x))) - xs' - ys')) - ys') - y) - ys) - xs') - x) - xs) - ys) - xs)))))) - (delay - (delay - (\z f xs -> - force - (force (force chooseList) - xs - (delay z) - (delay - (f - (force headList - xs) - (force tailList - xs)))))))) - mkCons) - f)))))))) - ((\`$fMkNilInteger` -> force `$fMkNilInteger`) (delay [])) - (force ((\`+` -> force `+`) (delay (delay (\v -> v)))) - ((\addInteger -> - (\addInteger -> - (\`$fAdditiveSemigroupInteger` -> - force `$fAdditiveSemigroupInteger`) - (delay (force addInteger))) - (delay (\x -> (\x y -> (\y -> addInteger x y) y) x))) - addInteger)) - xs - xs) - xs) - (delay - (delay - (\f -> - force (delay (\s -> s s)) - (\s -> f (\x -> force (delay (\s -> s s)) s x))))))) \ No newline at end of file + (\xs -> + force + ((\f -> + (\s -> f (\x -> f (\x -> f (\x -> f (\x -> s s x) x) x) x)) + (\s -> f (\x -> s s x))) + (\go arg -> + delay + (\xs ys -> + (\cse -> + cse + (\x xs' -> + cse + (\y ys' -> + force mkCons + (addInteger x y) + (force (go (delay (\x -> x))) xs' ys')) + ys) + xs) + (\f xs -> + force + (force (force chooseList) + xs + (delay []) + (delay + (f (force headList xs) (force tailList xs))))))) + (delay (\x -> x))) + xs + xs)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index 782c9633c39..cfa41790e3b 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -1,7 +1,6 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} -{-# OPTIONS_GHC -fplugin-opt PlutusTx.Plugin:max-cse-iterations=0 #-} {-# OPTIONS_GHC -fplugin-opt PlutusTx.Plugin:max-simplifier-iterations-pir=0 #-} {-# OPTIONS_GHC -fplugin-opt PlutusTx.Plugin:max-simplifier-iterations-uplc=0 #-} From b0a844ed3b8bb538bf3a3ddf6ac0599bfd092208 Mon Sep 17 00:00:00 2001 From: zeme Date: Mon, 26 May 2025 16:56:04 +0200 Subject: [PATCH 26/30] donw --- plutus-tx/src/PlutusTx/List.hs | 12 ------------ 1 file changed, 12 deletions(-) diff --git a/plutus-tx/src/PlutusTx/List.hs b/plutus-tx/src/PlutusTx/List.hs index 2ba3ff8d045..c21f90767d9 100644 --- a/plutus-tx/src/PlutusTx/List.hs +++ b/plutus-tx/src/PlutusTx/List.hs @@ -248,18 +248,6 @@ findIndex f = go 0 -} infixl 9 !! -(!!) :: forall a. [a] -> Integer -> a -_ !! n0 | n0 < 0 = traceError negativeIndexError -xs0 !! n0 = go n0 xs0 - where - go :: Integer -> [a] -> a - go _ [] = traceError indexTooLargeError - go n (x : xs) = - if Builtins.equalsInteger n 0 - then x - else go (Builtins.subtractInteger n 1) xs -{-# INLINEABLE (!!) #-} - {-| Cons each element of the first list to the second one in reverse order (i.e. the last element of the first list is the head of the result). From 3850c7e567d06b665a13b3590a9d5b38d0f272a8 Mon Sep 17 00:00:00 2001 From: zeme Date: Tue, 3 Jun 2025 16:55:30 +0200 Subject: [PATCH 27/30] wip --- .../changelog.d/20250527_092743_lorenzo.calegari_list_api.md | 2 -- 1 file changed, 2 deletions(-) diff --git a/plutus-tx/changelog.d/20250527_092743_lorenzo.calegari_list_api.md b/plutus-tx/changelog.d/20250527_092743_lorenzo.calegari_list_api.md index 59689c596a0..80986929992 100644 --- a/plutus-tx/changelog.d/20250527_092743_lorenzo.calegari_list_api.md +++ b/plutus-tx/changelog.d/20250527_092743_lorenzo.calegari_list_api.md @@ -2,8 +2,6 @@ - Added over 30 new functions to `PlutusTx.BuiltinList` -- Added new function `mapMaybe` to `PlutusTx.List` - - Added new errors codes: - `PT23` -> `PlutusTx.BuiltinList.head: empty list` - `PT24` -> `PlutusTx.BuiltinList.tail: empty list` From 6c1ec8e8f15252ebba0181359ee6e0cbcc536c95 Mon Sep 17 00:00:00 2001 From: zeme Date: Tue, 3 Jun 2025 17:01:45 +0200 Subject: [PATCH 28/30] wip --- .../test/BuiltinList/Budget/9.6/(++).eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/(<|).eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/all.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/and.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/any.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/append.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/concat.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/concatMap.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/cons.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/drop.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/dropWhile.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/elem.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/elemBy.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/empty.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/filter.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/find.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/findIndexJust.eval.golden | 6 +++--- .../BuiltinList/Budget/9.6/findIndexNothing.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/findIndices.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/foldl.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/foldr.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/headOk.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/index.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/lastOk.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/length.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden | 6 +++--- .../BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/map.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/mapMaybe.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/notElem.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/nub.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/nubBy.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/null.eval.golden | 6 +++--- plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/replicate.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/revAppend.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/reverse.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/singleton.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/tailOk.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/take.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/unconsJust.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/unconsNothing.eval.golden | 6 +++--- .../BuiltinList/Budget/9.6/uniqueElementJust.eval.golden | 6 +++--- .../BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden | 6 +++--- .../test/BuiltinList/Budget/9.6/zipWith.eval.golden | 6 +++--- 45 files changed, 135 insertions(+), 135 deletions(-) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden index 57639865071..427bb334a13 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(++).eval.golden @@ -1,5 +1,5 @@ -cpu: 10746784 -mem: 44612 -size: 83 +CPU: 10_746_784 +Memory: 44_612 +Size: 83 (con (list integer) [1,2,3,4,5,6,7,8,9,10,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden index ba51fd9d80e..6060f599045 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/(<|).eval.golden @@ -1,5 +1,5 @@ -cpu: 216462 -mem: 1032 -size: 9 +CPU: 216_462 +Memory: 1_032 +Size: 9 (con (list integer) [42,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.eval.golden index 1144b4b16c2..08e0f559563 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/all.eval.golden @@ -1,5 +1,5 @@ -CPU: 14_535_700 -Memory: 62_410 -Size: 86 +CPU: 15_879_700 +Memory: 70_810 +Size: 124 (constr 0 (constr 1) (constr 0)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden index 59e7396cde5..4e857a872c3 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/and.eval.golden @@ -1,5 +1,5 @@ -cpu: 2267812 -mem: 9794 -size: 91 +CPU: 2_267_812 +Memory: 9_794 +Size: 91 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.eval.golden index 4ad1de25836..62c554f810c 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/any.eval.golden @@ -1,5 +1,5 @@ -CPU: 23_293_722 -Memory: 99_496 -Size: 86 +CPU: 25_389_722 +Memory: 112_596 +Size: 124 (constr 0 (constr 0) (constr 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden index 57639865071..427bb334a13 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/append.eval.golden @@ -1,5 +1,5 @@ -cpu: 10746784 -mem: 44612 -size: 83 +CPU: 10_746_784 +Memory: 44_612 +Size: 83 (con (list integer) [1,2,3,4,5,6,7,8,9,10,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden index 4f048966d71..78a8c8db592 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concat.eval.golden @@ -1,5 +1,5 @@ -cpu: 8715372 -mem: 39900 -size: 157 +CPU: 8_715_372 +Memory: 39_900 +Size: 157 (con (list integer) [1,2,3,4]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden index e5c957c6e94..fbc00729b2a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/concatMap.eval.golden @@ -1,5 +1,5 @@ -cpu: 64688464 -mem: 290812 -size: 237 +CPU: 64_688_464 +Memory: 290_812 +Size: 237 (con (list integer) [1,1,2,2,3,3,4,4,5,5,6,6,7,7,8,8,9,9,10,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden index 4eec5a3badc..cea08d35413 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/cons.eval.golden @@ -1,5 +1,5 @@ -cpu: 216462 -mem: 1032 -size: 9 +CPU: 216_462 +Memory: 1_032 +Size: 9 (con (list integer) [0,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden index bd9c475bf9a..d4b180e9815 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/drop.eval.golden @@ -1,5 +1,5 @@ -cpu: 8410491 -mem: 36202 -size: 115 +CPU: 8_410_491 +Memory: 36_202 +Size: 115 (con (list integer) [6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden index 0c48b6f15cc..0fcbe541260 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/dropWhile.eval.golden @@ -1,5 +1,5 @@ -cpu: 6095830 -mem: 25590 -size: 95 +CPU: 6_095_830 +Memory: 25_590 +Size: 95 (con (list integer) [5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.eval.golden index 32259614c3d..dd97143ae91 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elem.eval.golden @@ -1,5 +1,5 @@ -CPU: 22_604_496 -Memory: 94_396 -Size: 93 +CPU: 22_876_496 +Memory: 96_096 +Size: 107 (constr 0 (constr 0) (constr 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden index b9ef254cf9e..1315ba3e6a8 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/elemBy.eval.golden @@ -1,5 +1,5 @@ -cpu: 12822024 -mem: 54312 -size: 95 +CPU: 12_822_024 +Memory: 54_312 +Size: 95 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden index 906f70b6c08..8ca5c9aa046 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/empty.eval.golden @@ -1,5 +1,5 @@ -cpu: 64100 -mem: 500 -size: 4 +CPU: 64_100 +Memory: 500 +Size: 4 (con (list integer) []) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden index 1cb6d45cab2..fd821a0419a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/filter.eval.golden @@ -1,5 +1,5 @@ -cpu: 16588094 -mem: 66982 -size: 110 +CPU: 16_588_094 +Memory: 66_982 +Size: 110 (con (list integer) [2,4,6,8,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.eval.golden index f3f098262d2..5e47e40ff45 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/find.eval.golden @@ -1,5 +1,5 @@ -CPU: 23_309_722 -Memory: 99_596 -Size: 87 +CPU: 26_269_722 +Memory: 118_096 +Size: 128 (constr 0 (constr 0 (con integer 8)) (constr 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden index eccb9d68d89..a380634298f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexJust.eval.golden @@ -1,5 +1,5 @@ -cpu: 5592480 -mem: 22898 -size: 105 +CPU: 5_592_480 +Memory: 22_898 +Size: 105 (constr 0 (con integer 3)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden index 4a9170dd9fa..2046c2e9632 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndexNothing.eval.golden @@ -1,5 +1,5 @@ -cpu: 15087064 -mem: 61632 -size: 105 +CPU: 15_087_064 +Memory: 61_632 +Size: 105 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden index b09c26dccf1..cb88d8c947c 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/findIndices.eval.golden @@ -1,5 +1,5 @@ -cpu: 18768174 -mem: 74302 -size: 119 +CPU: 18_768_174 +Memory: 74_302 +Size: 119 (con (list integer) [0,2,4,6,8]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden index 69a4b2809ae..f462ea1c5cd 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldl.eval.golden @@ -1,5 +1,5 @@ -cpu: 11780694 -mem: 49612 -size: 90 +CPU: 11_780_694 +Memory: 49_612 +Size: 90 (con integer 3628800) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden index 411dbd777d6..0cab9611ad4 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/foldr.eval.golden @@ -1,5 +1,5 @@ -cpu: 10875244 -mem: 43312 -size: 82 +CPU: 10_875_244 +Memory: 43_312 +Size: 82 (con integer 55) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden index 80fd21ad390..cf4b291e7af 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/headOk.eval.golden @@ -1,5 +1,5 @@ -cpu: 761907 -mem: 3096 -size: 39 +CPU: 761_907 +Memory: 3_096 +Size: 39 (con integer 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden index 7486123d160..53f20b85ddc 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/index.eval.golden @@ -1,5 +1,5 @@ -CPU: 1_064_403 -Memory: 4_200 -Size: 50 +CPU: 1_441_742 +Memory: 5_802 +Size: 72 (con integer 6) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden index f894403069d..a1641a7591d 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/lastOk.eval.golden @@ -1,5 +1,5 @@ -cpu: 19055427 -mem: 84856 -size: 119 +CPU: 19_055_427 +Memory: 84_856 +Size: 119 (con integer 10) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden index 3c15082a487..3fcc54a9707 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/length.eval.golden @@ -1,5 +1,5 @@ -cpu: 11355244 -mem: 46312 -size: 85 +CPU: 11_355_244 +Memory: 46_312 +Size: 85 (con integer 10) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden index c51ab8f5ceb..e541b71c7e9 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeJust.eval.golden @@ -1,5 +1,5 @@ -cpu: 681907 -mem: 2596 -size: 25 +CPU: 681_907 +Memory: 2_596 +Size: 25 (constr 0 (con integer 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden index 6eec30a642f..b2507bd8d37 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/listToMaybeNothing.eval.golden @@ -1,5 +1,5 @@ -cpu: 357094 -mem: 1532 -size: 25 +CPU: 357_094 +Memory: 1_532 +Size: 25 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.eval.golden index 1464bd5e840..996efd5b628 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/map.eval.golden @@ -1,5 +1,5 @@ -CPU: 10_606_864 -Memory: 37_432 -Size: 43 +CPU: 12_350_864 +Memory: 48_332 +Size: 84 (con (list integer) [2,3,4,5,6,7,8,9,10,11]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden index a01ca7f20f8..7988d00d8b3 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/mapMaybe.eval.golden @@ -1,5 +1,5 @@ -cpu: 16908094 -mem: 68982 -size: 122 +CPU: 16_908_094 +Memory: 68_982 +Size: 122 (con (list integer) [1,3,5,7,9]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden index d9cb74f8b16..3d5b583b61f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/notElem.eval.golden @@ -1,5 +1,5 @@ -cpu: 12970984 -mem: 54712 -size: 101 +CPU: 12_970_984 +Memory: 54_712 +Size: 101 (constr 0) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden index 578b5127098..e472fbdf562 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nub.eval.golden @@ -1,5 +1,5 @@ -cpu: 182519998 -mem: 809124 -size: 266 +CPU: 182_519_998 +Memory: 809_124 +Size: 266 (con (list integer) [1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden index d6cdfe158dd..e7d27c4448f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/nubBy.eval.golden @@ -1,5 +1,5 @@ -cpu: 26348119 -mem: 122070 -size: 199 +CPU: 26_348_119 +Memory: 122_070 +Size: 199 (con (list integer) [1]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden index 01e48473efb..4642c612e16 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/null.eval.golden @@ -1,5 +1,5 @@ -cpu: 374582 -mem: 1533 -size: 14 +CPU: 374_582 +Memory: 1_533 +Size: 14 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden index 9f8d7fe2679..e8a17a1b2bb 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/or.eval.golden @@ -1,5 +1,5 @@ -cpu: 1189956 -mem: 5297 -size: 91 +CPU: 1_189_956 +Memory: 5_297 +Size: 91 (constr 0) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden index e62031ccd9d..2e3381d19eb 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/replicate.eval.golden @@ -1,5 +1,5 @@ -cpu: 9694546 -mem: 41962 -size: 81 +CPU: 9_694_546 +Memory: 41_962 +Size: 81 (con (list integer) [0,0,0,0,0,0,0,0,0,0]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden index 62ae47ba0f1..1a1f130221a 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/revAppend.eval.golden @@ -1,5 +1,5 @@ -cpu: 12154784 -mem: 53412 -size: 97 +CPU: 12_154_784 +Memory: 53_412 +Size: 97 (con (list integer) [10,9,8,7,6,5,4,3,2,1,1,2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden index da272af74fc..7883b7d312f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/reverse.eval.golden @@ -1,5 +1,5 @@ -cpu: 12154784 -mem: 53412 -size: 97 +CPU: 12_154_784 +Memory: 53_412 +Size: 97 (con (list integer) [10,9,8,7,6,5,4,3,2,1]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden index ca9e33cc851..4b04811ad7f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/singleton.eval.golden @@ -1,5 +1,5 @@ -cpu: 216462 -mem: 1032 -size: 9 +CPU: 216_462 +Memory: 1_032 +Size: 9 (con (list integer) [42]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden index 86aa7f56508..ac86fb7b830 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/tailOk.eval.golden @@ -1,5 +1,5 @@ -cpu: 761907 -mem: 3096 -size: 39 +CPU: 761_907 +Memory: 3_096 +Size: 39 (con (list integer) [2,3,4,5,6,7,8,9,10]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden index 9659a137189..6df5a6aa7ed 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/take.eval.golden @@ -1,5 +1,5 @@ -cpu: 8932301 -mem: 37362 -size: 117 +CPU: 8_932_301 +Memory: 37_362 +Size: 117 (con (list integer) [1,2,3,4,5]) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden index 710ffb00b0f..d30012947d8 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsJust.eval.golden @@ -1,5 +1,5 @@ -cpu: 665907 -mem: 2496 -size: 24 +CPU: 665_907 +Memory: 2_496 +Size: 24 (constr 0 (constr 0 (con integer 1) (con (list integer) [2,3,4,5,6,7,8,9,10]))) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden index 6597dd039a7..4d8baaa977d 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/unconsNothing.eval.golden @@ -1,5 +1,5 @@ -cpu: 357094 -mem: 1532 -size: 24 +CPU: 357_094 +Memory: 1_532 +Size: 24 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden index 3c4f62cfc59..8f40cc3c8d7 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementJust.eval.golden @@ -1,5 +1,5 @@ -cpu: 3878050 -mem: 17462 -size: 146 +CPU: 3_878_050 +Memory: 17_462 +Size: 146 (constr 0 (con integer 1)) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden index 01ce14fd5fd..c06234da40f 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/uniqueElementNothing.eval.golden @@ -1,5 +1,5 @@ -cpu: 549094 -mem: 2732 -size: 45 +CPU: 549_094 +Memory: 2_732 +Size: 45 (constr 1) \ No newline at end of file diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden index 82e897cf1c7..bdaf868a2a6 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden +++ b/plutus-tx-plugin/test/BuiltinList/Budget/9.6/zipWith.eval.golden @@ -1,5 +1,5 @@ -cpu: 22448934 -mem: 93792 -size: 110 +CPU: 22_448_934 +Memory: 93_792 +Size: 110 (con (list integer) [2,4,6,8,10,12,14,16,18,20]) \ No newline at end of file From 041b746814f69bcf689636f64b179bb4af6a5e7c Mon Sep 17 00:00:00 2001 From: zeme Date: Wed, 4 Jun 2025 13:02:46 +0200 Subject: [PATCH 29/30] wip --- .../test/BuiltinList/Budget/Spec.hs | 20 ------------------- 1 file changed, 20 deletions(-) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index cfa41790e3b..f299b56546e 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -241,23 +241,3 @@ concat = $$(compile [||\xss -> L.concat xss||]) concatMap :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) concatMap = $$(compile [||\xss -> L.concatMap (L.replicate 2) xss||]) - -splitAt - :: CompiledCode - (L.BuiltinList Integer -> BuiltinPair (L.BuiltinList Integer) (L.BuiltinList Integer)) -splitAt = undefined -- \$$(compile [|| \xs -> L.splitAt 2 xs ||]) - -partition :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -partition = undefined -- \$$(compile [|| L.partition ||]) - -sort :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -sort = undefined -- \$$(compile [|| \xs -> L.sort xs ||]) - -sortBy :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList Integer) -sortBy = undefined -- \$$(compile [|| \xs -> L.sortBy (<=) xs ||]) - -unzip :: CompiledCode (L.BuiltinList (BuiltinPair a b) -> L.BuiltinList Integer) -unzip = undefined -- \$$(compile [|| \xs -> L.unzip xs ||]) - -zip :: CompiledCode (L.BuiltinList Integer -> L.BuiltinList (BuiltinPair Integer Integer)) -zip = undefined -- \$$(compile [|| \xs -> L.zip xs xs ||]) From 2451661f36b94d3e96f4235490b0927117a5078b Mon Sep 17 00:00:00 2001 From: zeme Date: Wed, 4 Jun 2025 14:43:34 +0200 Subject: [PATCH 30/30] wip --- plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs index f299b56546e..efb205754bc 100644 --- a/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs +++ b/plutus-tx-plugin/test/BuiltinList/Budget/Spec.hs @@ -13,7 +13,6 @@ import PlutusTx.Code (CompiledCode, unsafeApplyCode) import PlutusTx.Lift (liftCodeDef) import PlutusTx.Test (goldenBundle) import PlutusTx.TH (compile) -import Prelude (undefined) import System.FilePath (()) import Test.Tasty.Extras (TestNested, testNested, testNestedGhc)