Skip to content

Commit

Permalink
put instances back
Browse files Browse the repository at this point in the history
  • Loading branch information
echatav committed Sep 30, 2024
1 parent b1b6f07 commit 7a25de1
Showing 1 changed file with 14 additions and 0 deletions.
14 changes: 14 additions & 0 deletions src/ZkFold/Symbolic/Cardano/Types/Value.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@

module ZkFold.Symbolic.Cardano.Types.Value where

import qualified Data.Map as Map
import GHC.Natural (Natural)
import Prelude hiding (Bool, Eq, length, replicate, splitAt, (*), (+))
import qualified Prelude as Haskell
Expand Down Expand Up @@ -35,3 +36,16 @@ deriving instance

instance Symbolic context => Scale Natural (Value n context) where
n `scale` Value v = Value $ fmap (\((pid, aname), q) -> ((pid, aname), n `scale` q)) v

instance (Haskell.Ord (PolicyId context), Haskell.Ord (AssetName context), Symbolic context) => Semigroup (Value n context) where
(<>) (Value va) (Value vb) = Value $ unsafeToVector $ Map.toList $ Map.unionWith (+) (Map.fromList (fromVector va)) (Map.fromList (fromVector vb))

instance (Haskell.Ord (PolicyId context), Haskell.Ord (AssetName context), Symbolic context) => Monoid (Value n context) where
mempty = Value $ unsafeToVector []

instance (Haskell.Ord (PolicyId context), Haskell.Ord (AssetName context), Symbolic context) => AdditiveSemigroup (Value n context) where
(+) = (<>)

instance
(Haskell.Ord (PolicyId context), Haskell.Ord (AssetName context), Symbolic context) => AdditiveMonoid (Value n context) where
zero = mempty

0 comments on commit 7a25de1

Please sign in to comment.