11{-# LANGUAGE AllowAmbiguousTypes #-}
2+ {-# LANGUAGE LiberalTypeSynonyms #-}
23{-# LANGUAGE OverloadedLists #-}
34{-# LANGUAGE UndecidableInstances #-}
45{-# OPTIONS_GHC -Wno-orphans #-}
5-
6- module LambdaBuffers.Runtime.Plutarch (PEither (.. ), PAssetClass , PMap , PChar , PSet , PValue , ptryFromPAsData , PMaybe (.. ), pcon ) where
6+ {-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
7+
8+ module LambdaBuffers.Runtime.Plutarch (
9+ PEither (.. ),
10+ PAssetClass ,
11+ PMap ,
12+ PChar ,
13+ PSet ,
14+ PValue ,
15+ ptryFromPAsData ,
16+ PMaybe (.. ),
17+ pcon ,
18+ PList (.. ),
19+ caseList ,
20+ pcons ,
21+ pnil ,
22+ ) where
723
824import Data.Functor.Const (Const )
925import GHC.Generics (Generic )
1026import GHC.TypeLits qualified as GHC
27+ import LambdaBuffers.Runtime.Plutarch.LamVal (pfromPlutusDataPTryFrom )
1128import LambdaBuffers.Runtime.Plutarch.LamVal qualified as LamVal
1229import Plutarch (
1330 PType ,
@@ -41,6 +58,14 @@ import Plutarch.Reducible (Reduce)
4158import Plutarch.TryFrom (PTryFrom (PTryFromExcess , ptryFrom' ))
4259import Plutarch.Unsafe (punsafeCoerce )
4360
61+ {- | PList because PBuiltinList misses `PAsData` on its constituents which causes type errors when used.
62+ TODO(bladyjoker): Upstream these changes or fix PBuiltinList.
63+ -}
64+ newtype PList (a :: PType ) (s :: S )
65+ = PList (Term s (PBuiltinList (PAsData a )))
66+ deriving stock (Generic )
67+ deriving anyclass (Pl.PShow )
68+
4469-- | PAssetClass missing from Plutarch.
4570type PAssetClass = Plutarch.Api.V1. PTuple Plutarch.Api.V1. PCurrencySymbol Plutarch.Api.V1. PTokenName
4671
@@ -53,6 +78,9 @@ type PValue = Plutarch.Api.V1.PValue 'Plutarch.Api.V1.Sorted 'Plutarch.Api.V1.No
5378-- | Not implemented.
5479data PChar (s :: S ) = PChar
5580
81+ -- | Not implemented.
82+ data PSet (a :: PType ) (s :: S ) = PSet
83+
5684-- | PEither missing from Plutarch.
5785data PEither (a :: PType ) (b :: PType ) (s :: S )
5886 = PLeft (Term s (PAsData a ))
@@ -76,6 +104,7 @@ data PFoo (a :: PType) (s :: S)
76104 (Term s (PAsData (PEither a a )))
77105 (Term s (PAsData PAssetClass ))
78106 (Term s (PAsData (PFoo a )))
107+ (Term s (PAsData (PList a )))
79108 deriving stock (Generic )
80109 deriving anyclass (Pl.PShow )
81110
@@ -136,9 +165,14 @@ instance PlutusType (PEither a b) where
136165 (const perror)
137166 pd
138167
168+ instance PlutusType (PList a ) where
169+ type PInner (PList a ) = (PBuiltinList (PAsData a ))
170+ pcon' (PList x) = x
171+ pmatch' x f = f (PList x)
172+
139173instance PlutusType (PFoo a ) where
140174 type PInner (PFoo a ) = PData
141- pcon' (PFoo i b bs may eit ac foo) =
175+ pcon' (PFoo i b bs may eit ac foo xs ) =
142176 LamVal. listData
143177 [ LamVal. toPlutusData i
144178 , LamVal. toPlutusData b
@@ -147,6 +181,7 @@ instance PlutusType (PFoo a) where
147181 , LamVal. toPlutusData eit
148182 , LamVal. toPlutusData ac
149183 , LamVal. toPlutusData foo
184+ , LamVal. toPlutusData xs
150185 ]
151186 pmatch' pd f =
152187 f
@@ -158,6 +193,7 @@ instance PlutusType (PFoo a) where
158193 (LamVal. pfromPlutusDataPlutusType # pd)
159194 (LamVal. pfromPlutusDataPlutusType # pd)
160195 (LamVal. pfromPlutusDataPlutusType # pd)
196+ (LamVal. pfromPlutusDataPlutusType # pd)
161197 )
162198
163199-- PTryFrom instances.
@@ -241,6 +277,20 @@ instance (PTryFrom PData (PAsData a)) => PTryFrom PData (PAsData (PMaybe a)) whe
241277 , ()
242278 )
243279
280+ instance PTryFrom PData (PAsData a ) => PTryFrom PData (PAsData (PList a )) where
281+ type PTryFromExcess PData (PAsData (PList a )) = Const ()
282+ ptryFrom' pd f =
283+ f
284+ ( LamVal. casePlutusData
285+ (const $ const perror)
286+ ( \ xs -> pcon $ PList $ Pl. pmap # pfromPlutusDataPTryFrom # xs
287+ )
288+ (const perror)
289+ (const perror)
290+ pd
291+ , ()
292+ )
293+
244294instance (PTryFrom PData (PAsData a )) => PTryFrom PData (PFoo a ) where
245295 type PTryFromExcess PData (PFoo a ) = Const ()
246296 ptryFrom' = ptryFromPAsData
@@ -504,7 +554,7 @@ instance PTryFrom PData (PAsData Plutarch.Api.V2.PTxOut) where
504554 , ()
505555 )
506556
507- -- FIXME (bladyjoker): This is used above and it's a hack because something is off with PMaybeData instances.
557+ -- HACK (bladyjoker): This is used above and it's a hack because something is off with PMaybeData instances.
508558maybeToMaybe :: Term s (PAsData (PMaybe a ) :--> PAsData (PMaybeData a ))
509559maybeToMaybe =
510560 phoistAcyclic $
@@ -581,6 +631,7 @@ instance (PTryFrom PData (PAsData a)) => PTryFrom PData (PAsData (PFoo a)) where
581631 (LamVal. pfromPlutusDataPTryFrom # pd)
582632 (LamVal. pfromPlutusDataPTryFrom # pd)
583633 (LamVal. pfromPlutusDataPTryFrom # pd)
634+ (LamVal. pfromPlutusDataPTryFrom # pd)
584635 , ()
585636 )
586637
@@ -598,9 +649,6 @@ instance GHC.TypeError ('GHC.Text "LambdaBuffers Prelude.Char not implemented")
598649instance GHC. TypeError ('GHC.Text " LambdaBuffers Prelude.Char not implemented" ) => PEq PChar where
599650 (#==) _l _r = error " unreachable"
600651
601- -- | Not implemented.
602- data PSet (a :: PType ) (s :: S ) = PSet
603-
604652instance GHC. TypeError ('GHC.Text " LambdaBuffers Prelude.Set not implemented" ) => PlutusType (PSet a ) where
605653 type PInner (PSet a ) = PData
606654 pcon' PSet = error " unreachable"
@@ -626,6 +674,10 @@ instance PIsData (PEither a b) where
626674 pdataImpl = punsafeCoerce
627675 pfromDataImpl = punsafeCoerce
628676
677+ instance PIsData (PList a ) where
678+ pdataImpl = punsafeCoerce
679+ pfromDataImpl = punsafeCoerce
680+
629681instance PEq (PFoo a ) where
630682 (#==) l r = pdata l #== pdata r
631683
@@ -635,5 +687,23 @@ instance PEq (PMaybe a) where
635687instance PEq (PEither a b ) where
636688 (#==) l r = pdata l #== pdata r
637689
690+ instance PEq (PList a ) where
691+ (#==) l r = Pl. plistEquals # Pl. pto l # Pl. pto r
692+
638693pcon :: (PlutusType a , PIsData a ) => a s -> Term s (PAsData a )
639694pcon = pdata . Pl. pcon
695+
696+ {- | PListLike instance was a problem for PList, so this is done instead.
697+
698+ TODO(bladyjoker): Upstream with PList and plan to remove.
699+ -}
700+ caseList :: (PIsData a ) => (Term s a -> Term s (PList a ) -> Term s r ) -> Term s r -> Term s (PList a ) -> Term s r
701+ caseList consCase nilCase ls = pmatch (Pl. pto ls) $ \ case
702+ Pl. PCons x xs -> consCase (Pl. pfromData x) (Pl. pcon $ PList xs)
703+ Pl. PNil -> nilCase
704+
705+ pcons :: PIsData a => Term s (a :--> (PList a :--> PList a ))
706+ pcons = phoistAcyclic $ plam $ \ x xs -> Pl. pcon $ PList (Pl. pcons # Pl. pdata x # Pl. pto xs)
707+
708+ pnil :: Term s (PList a )
709+ pnil = Pl. pcon $ PList $ Pl. pcon Pl. PNil
0 commit comments