From bcd04598a6b7667275a069c5e923f9e30afeaf8f Mon Sep 17 00:00:00 2001 From: Ari Fordsham Date: Thu, 1 Sep 2022 19:25:36 +0300 Subject: [PATCH] Fix transcribed to Plutarch --- Plutarch/CPS/Optics/Lens.hs | 3 +- Plutarch/CPS/Optics/Optic.hs | 2 +- Plutarch/CPS/Optics/Optional.hs | 4 +- Plutarch/CPS/Optics/Prism.hs | 3 +- Plutarch/CPS/Optics/Traversal.hs | 15 +++---- Plutarch/CPS/Profunctor.hs | 3 +- Plutarch/Cont.hs | 15 +++++++ Plutarch/Optics/Fix.hs | 57 ++++++++++++++++---------- Plutarch/Optics/PEither.hs | 14 +++---- Plutarch/Optics/PList.hs | 69 ++++++++++++-------------------- plutarch-core.cabal | 6 +-- 11 files changed, 102 insertions(+), 89 deletions(-) create mode 100644 Plutarch/Cont.hs diff --git a/Plutarch/CPS/Optics/Lens.hs b/Plutarch/CPS/Optics/Lens.hs index 0017aa8..96ab270 100644 --- a/Plutarch/CPS/Optics/Lens.hs +++ b/Plutarch/CPS/Optics/Lens.hs @@ -2,7 +2,8 @@ module Plutarch.CPS.Optics.Lens where -import Control.Monad.Cont +import Control.Monad +import Control.Monad.Trans.Cont import Plutarch.CPS.Optics.Iso import Plutarch.CPS.Optics.Optic import Plutarch.CPS.Profunctor diff --git a/Plutarch/CPS/Optics/Optic.hs b/Plutarch/CPS/Optics/Optic.hs index f368546..bab5219 100644 --- a/Plutarch/CPS/Optics/Optic.hs +++ b/Plutarch/CPS/Optics/Optic.hs @@ -1,6 +1,6 @@ module Plutarch.CPS.Optics.Optic where -import Control.Monad.Cont +import Control.Monad.Trans.Cont type COptic r p s t a b = p a (Cont r b) -> p s (Cont r t) diff --git a/Plutarch/CPS/Optics/Optional.hs b/Plutarch/CPS/Optics/Optional.hs index b944a30..7edab44 100644 --- a/Plutarch/CPS/Optics/Optional.hs +++ b/Plutarch/CPS/Optics/Optional.hs @@ -7,7 +7,9 @@ import Plutarch.CPS.Optics.Optic import Plutarch.CPS.Optics.Prism import Control.Arrow -import Control.Monad.Cont +import Control.Monad + +import Control.Monad.Trans.Cont import Plutarch.CPS.Optics.Iso import Plutarch.CPS.Profunctor diff --git a/Plutarch/CPS/Optics/Prism.hs b/Plutarch/CPS/Optics/Prism.hs index bbed2c8..4f8dfaf 100644 --- a/Plutarch/CPS/Optics/Prism.hs +++ b/Plutarch/CPS/Optics/Prism.hs @@ -2,7 +2,8 @@ module Plutarch.CPS.Optics.Prism where -import Control.Monad.Cont +import Control.Monad +import Control.Monad.Trans.Cont import Plutarch.CPS.Optics.Iso import Plutarch.CPS.Optics.Optic import Plutarch.CPS.Profunctor diff --git a/Plutarch/CPS/Optics/Traversal.hs b/Plutarch/CPS/Optics/Traversal.hs index 3240e85..ea1ce85 100644 --- a/Plutarch/CPS/Optics/Traversal.hs +++ b/Plutarch/CPS/Optics/Traversal.hs @@ -5,13 +5,10 @@ module Plutarch.CPS.Optics.Traversal( CTraversal', ctraverse, ctraverseOf, - ConcreteTraversal(ConcreteTraversal, unConcreteTraversal), - FunList, - single, - traversal, + ctraversal, ) where -import Control.Monad.Cont +import Control.Monad.Trans.Cont import Plutarch.CPS.Optics.Optic import Plutarch.CPS.Optics.Optional import Plutarch.CPS.Profunctor @@ -52,7 +49,7 @@ instance Applicative (FunList a b) where fuse :: FunList b b t -> Cont r t fuse = either return (\(a, c) -> ($ a) <$> fuse c) . unFunList -newtype ConcreteTraversal r s t a b = ConcreteTraversal {unConcreteTraversal :: s -> Cont r (FunList a b t)} - -traversal :: (s -> Cont r (FunList a b t)) -> CTraversal r s t a b -traversal h = cdimap h fuse . ctraverse +ctraversal :: + (forall f. Applicative f => (a -> f b) -> (s -> Cont r (f t))) -> + CTraversal r s t a b +ctraversal h = cdimap (h single) fuse . ctraverse diff --git a/Plutarch/CPS/Profunctor.hs b/Plutarch/CPS/Profunctor.hs index bacd7ae..bd773f9 100644 --- a/Plutarch/CPS/Profunctor.hs +++ b/Plutarch/CPS/Profunctor.hs @@ -3,7 +3,8 @@ module Plutarch.CPS.Profunctor where import Control.Applicative -import Control.Monad.Cont +import Control.Monad +import Control.Monad.Trans.Cont import Data.Tuple newtype CStar r f a b = CStar {runCStar :: a -> Cont r (f b)} diff --git a/Plutarch/Cont.hs b/Plutarch/Cont.hs new file mode 100644 index 0000000..938aa4a --- /dev/null +++ b/Plutarch/Cont.hs @@ -0,0 +1,15 @@ +module Plutarch.Cont(pmatchCont) where + +import Control.Monad.Trans.Cont + +import Plutarch.Core + +pmatchCont :: + ( + EConstructable edsl a, + IsEType edsl r + ) => + (EConcrete edsl a -> Cont (Term edsl r) b) -> + Term edsl a -> + Cont (Term edsl r) b +pmatchCont cnt t = cont \c -> ematch t \con -> runCont (cnt con) c \ No newline at end of file diff --git a/Plutarch/Optics/Fix.hs b/Plutarch/Optics/Fix.hs index de9fed2..cd7dc45 100644 --- a/Plutarch/Optics/Fix.hs +++ b/Plutarch/Optics/Fix.hs @@ -1,28 +1,43 @@ +{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE PartialTypeSignatures #-} -{-# OPTIONS_GHC -Wno-unused-top-binds #-} -module Plutarch.Optics.Fix(fixt) where -import Data.Fix -import Control.Lens +module Plutarch.Optics.Fix(pfix) where -import Data.Functor.Base import Data.Function +import Data.Profunctor -fixt :: - (Applicative f) => - (forall ra rb. (ra -> f rb) -> a ra -> f (b rb)) -> - Fix a -> - f (Fix b) -fixt f = fmap Fix . (fix (f . dimap unFix (fmap Fix))) . unFix +import Control.Monad.Trans.Cont -list' :: Traversal (Fix (ListF a)) (Fix (ListF b)) a b -list' f = fixt (listf f) +import Plutarch.Core +import Plutarch.Cont -listf :: - (Applicative f) => - (a -> f b) -> - (ra -> f rb) -> - ListF a ra -> - f (ListF b rb) -listf _ _ Nil = pure Nil -listf f r (Cons a b) = Cons <$> f a <*> r b +-- | Not a 'Plutarch.CPS.Optics.Traversal.CTraversal', but can be used to construct one. +pfix :: + ( + EConstructable edsl (EFix a), + EConstructable edsl (a (EFix a)), + EConstructable edsl (EFix b), + EConstructable edsl (b (EFix b)), + EConstructable edsl r, + Applicative f + ) => + ( + forall ra rb. + ( + EConstructable edsl (a ra), + EConstructable edsl (b rb) + ) => + (Term edsl ra -> Cont (Term edsl r) (f (Term edsl rb ))) -> + Term edsl (a ra ) -> Cont (Term edsl r) (f (Term edsl (b rb ))) + ) -> + Term edsl (EFix a) -> Cont (Term edsl r) (f (Term edsl (EFix b))) +pfix f = + pmatchCont \(EFix a) -> + fmap (econ . EFix) + <$> fix + (f . + dimap + (\fa -> ematch fa \(EFix a') -> a') + (fmap (fmap (econ . EFix))) + ) + a \ No newline at end of file diff --git a/Plutarch/Optics/PEither.hs b/Plutarch/Optics/PEither.hs index 5726c88..2512abc 100644 --- a/Plutarch/Optics/PEither.hs +++ b/Plutarch/Optics/PEither.hs @@ -4,8 +4,8 @@ module Plutarch.Optics.PEither where import Plutarch.CPS.Optics.Prism -import Control.Monad.Cont import Plutarch.Core +import Plutarch.Cont _PLeft :: (ESOP edsl, IsEType edsl a, IsEType edsl a', IsEType edsl b, IsEType edsl r) => @@ -18,9 +18,9 @@ _PLeft :: _PLeft = cprism (return . pleft) - ( \te -> cont \f -> ematch te \case - ELeft a -> f . Right $ a - ERight b -> f . Left $ pright b + (pmatchCont \case + ELeft a -> return $ Right a + ERight b -> return $ Left (pright b) ) _PRight :: @@ -34,7 +34,7 @@ _PRight :: _PRight = cprism (return . pright) - ( \te -> cont \f -> ematch te \case - ELeft a -> f . Left $ pleft a - ERight b -> f . Right $ b + (pmatchCont \case + ELeft a -> return $ Left (pleft a) + ERight b -> return $ Right b ) diff --git a/Plutarch/Optics/PList.hs b/Plutarch/Optics/PList.hs index 13be5ee..5a7a9e1 100644 --- a/Plutarch/Optics/PList.hs +++ b/Plutarch/Optics/PList.hs @@ -1,58 +1,21 @@ module Plutarch.Optics.PList where -import Control.Applicative -import Control.Monad.Cont +import Control.Monad.Trans.Cont import Plutarch.CPS.Optics.Traversal import Plutarch.Core +import Plutarch.Cont import Plutarch.PList - -plist'' :: - ( ESOP edsl - , IsEType edsl a - , IsEType edsl b - , IsEType edsl r - , IsEType edsl (EFix (PListF a)) - , EConstructable edsl (EFix (PListF a)) - , IsEType edsl (EFix (PListF b)) - , EConstructable edsl (EFix (PListF b)) - ) => - Term edsl (EFix (PListF a)) -> - Cont - (Term edsl r) - (FunList (Term edsl a) (Term edsl b) (Term edsl (EFix (PListF b)))) -plist'' fl = cont \f -> - ematch fl \(EFix l) -> ematch l \case - PNil -> f . pure . econ . EFix . econ $ PNil - PCons x xs -> - runCont - (plist'' xs) - (f . liftA2 (\x' -> econ . EFix . econ . PCons x') (single x)) - -plist' :: - ( ESOP edsl - , IsEType edsl a - , IsEType edsl b - , IsEType edsl r - , IsEType edsl (EFix (PListF a)) - , EConstructable edsl (EFix (PListF a)) - , IsEType edsl (EFix (PListF b)) - , EConstructable edsl (EFix (PListF b)) - ) => - Term edsl (PList a) -> - Cont - (Term edsl r) - (FunList (Term edsl a) (Term edsl b) (Term edsl (PList b))) -plist' fl = fmap (econ . PList) <$> plist'' (ematch fl unPList) +import Plutarch.Optics.Fix +import Control.Applicative plist :: ( ESOP edsl , IsEType edsl a , IsEType edsl b , IsEType edsl r - , IsEType edsl (EFix (PListF a)) , EConstructable edsl (EFix (PListF a)) - , IsEType edsl (EFix (PListF b)) , EConstructable edsl (EFix (PListF b)) + , EConstructable edsl r ) => CTraversal (Term edsl r) @@ -60,5 +23,25 @@ plist :: (Term edsl (PList b)) (Term edsl a) (Term edsl b) -plist = traversal plist' +plist = + ctraversal + \f -> pmatchCont (\(PList as) -> fmap (econ . PList) <$> plist' f as) +plist' :: + ( + EConstructable edsl (EFix (PListF a)), + EConstructable edsl (PListF a (EFix (PListF a))), + EConstructable edsl (EFix (PListF b)), + EConstructable edsl r, + EConstructable edsl (PListF b (EFix (PListF b))), + Applicative f + ) => + (Term edsl a -> f (Term edsl b)) -> + Term edsl (EFix (PListF a)) -> + Cont (Term edsl r) (f (Term edsl (EFix (PListF b)))) +plist' f = + pfix + (\r -> pmatchCont \case + PNil -> return $ pure (econ PNil) + PCons a as -> fmap econ . liftA2 PCons (f a) <$> r as + ) \ No newline at end of file diff --git a/plutarch-core.cabal b/plutarch-core.cabal index 93eadb4..0175aa0 100644 --- a/plutarch-core.cabal +++ b/plutarch-core.cabal @@ -117,8 +117,6 @@ library build-depends: , base - , data-fix , generics-sop - , lens - , mtl - , recursion-schemes + , transformers + , profunctors \ No newline at end of file