{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Plutus.PAB.Run.PSGenerator where
import Cardano.Wallet.Mock.Types (WalletInfo)
import Control.Applicative ((<|>))
import Control.Lens (set, (&))
import Control.Monad.Freer.Extras.Log (LogLevel, LogMessage)
import Data.Proxy (Proxy (Proxy))
import Data.Text qualified as Text
import Data.Typeable (Typeable)
import Language.PureScript.Bridge (BridgePart, Language (Haskell), SumType, argonaut, buildBridge, equal, genericShow,
mkSumType, order)
import Language.PureScript.Bridge.TypeParameters (A, B)
import PSGenerator.Common qualified
import Plutus.Contract.Checkpoint (CheckpointKey, CheckpointStore, CheckpointStoreItem)
import Plutus.Contract.Resumable (Responses)
import Plutus.Contract.StateMachine (InvalidTransition, SMContractError)
import Plutus.Contract.StateMachine.OnChain (State)
import Plutus.PAB.Effects.Contract qualified as Contract
import Plutus.PAB.Effects.Contract.Builtin (Builtin)
import Plutus.PAB.Events.ContractInstanceState (PartiallyDecodedResponse)
import Plutus.PAB.Webserver.API qualified as API
import Plutus.PAB.Webserver.Types (ChainReport, CombinedWSStreamToClient, CombinedWSStreamToServer,
ContractActivationArgs, ContractInstanceClientState, ContractReport,
ContractSignatureResponse, FullReport, InstanceStatusToClient)
import Servant.PureScript (HasBridge, Settings, addTypes, apiModuleName, defaultBridge, defaultSettings,
generateWithSettings, languageBridge)
class HasPSTypes a where
psTypes :: [SumType 'Haskell]
psTypes = []
pabBridge :: BridgePart
pabBridge :: BridgePart
pabBridge =
BridgePart
PSGenerator.Common.aesonBridge BridgePart -> BridgePart -> BridgePart
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
BridgePart
PSGenerator.Common.containersBridge BridgePart -> BridgePart -> BridgePart
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
BridgePart
PSGenerator.Common.languageBridge BridgePart -> BridgePart -> BridgePart
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
BridgePart
PSGenerator.Common.ledgerBridge BridgePart -> BridgePart -> BridgePart
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
BridgePart
PSGenerator.Common.servantBridge BridgePart -> BridgePart -> BridgePart
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
BridgePart
PSGenerator.Common.miscBridge BridgePart -> BridgePart -> BridgePart
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
BridgePart
defaultBridge
data PabBridge
pabBridgeProxy :: Proxy PabBridge
pabBridgeProxy :: Proxy PabBridge
pabBridgeProxy = Proxy PabBridge
forall k (t :: k). Proxy t
Proxy
instance HasBridge PabBridge where
languageBridge :: Proxy PabBridge -> FullBridge
languageBridge Proxy PabBridge
_ = BridgePart -> FullBridge
buildBridge BridgePart
pabBridge
pabTypes :: [SumType 'Haskell]
pabTypes :: [SumType 'Haskell]
pabTypes =
[SumType 'Haskell]
PSGenerator.Common.ledgerTypes [SumType 'Haskell] -> [SumType 'Haskell] -> [SumType 'Haskell]
forall a. Semigroup a => a -> a -> a
<>
[SumType 'Haskell]
PSGenerator.Common.playgroundTypes [SumType 'Haskell] -> [SumType 'Haskell] -> [SumType 'Haskell]
forall a. Semigroup a => a -> a -> a
<>
[SumType 'Haskell]
PSGenerator.Common.walletTypes [SumType 'Haskell] -> [SumType 'Haskell] -> [SumType 'Haskell]
forall a. Semigroup a => a -> a -> a
<>
[ SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic (FullReport A), Typeable (FullReport A),
GDataConstructor (Rep (FullReport A))) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @(FullReport A)
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic ChainReport, Typeable ChainReport,
GDataConstructor (Rep ChainReport)) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @ChainReport
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic (ContractReport A), Typeable (ContractReport A),
GDataConstructor (Rep (ContractReport A))) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @(ContractReport A)
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic (ContractSignatureResponse A),
Typeable (ContractSignatureResponse A),
GDataConstructor (Rep (ContractSignatureResponse A))) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @(ContractSignatureResponse A)
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic (PartiallyDecodedResponse A),
Typeable (PartiallyDecodedResponse A),
GDataConstructor (Rep (PartiallyDecodedResponse A))) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @(PartiallyDecodedResponse A)
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic CheckpointStore, Typeable CheckpointStore,
GDataConstructor (Rep CheckpointStore)) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @CheckpointStore
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
order (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic CheckpointKey, Typeable CheckpointKey,
GDataConstructor (Rep CheckpointKey)) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @CheckpointKey
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic (CheckpointStoreItem A), Typeable (CheckpointStoreItem A),
GDataConstructor (Rep (CheckpointStoreItem A))) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @(CheckpointStoreItem A)
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic (Responses A), Typeable (Responses A),
GDataConstructor (Rep (Responses A))) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @(Responses A)
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic (InvalidTransition A B), Typeable (InvalidTransition A B),
GDataConstructor (Rep (InvalidTransition A B))) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @(InvalidTransition A B)
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic (State A), Typeable (State A),
GDataConstructor (Rep (State A))) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @(State A)
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic SMContractError, Typeable SMContractError,
GDataConstructor (Rep SMContractError)) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @SMContractError
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic (LogMessage A), Typeable (LogMessage A),
GDataConstructor (Rep (LogMessage A))) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @(LogMessage A)
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
order (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic LogLevel, Typeable LogLevel,
GDataConstructor (Rep LogLevel)) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @LogLevel
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
equal (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic (ContractActivationArgs A),
Typeable (ContractActivationArgs A),
GDataConstructor (Rep (ContractActivationArgs A))) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @(ContractActivationArgs A)
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic (ContractInstanceClientState A),
Typeable (ContractInstanceClientState A),
GDataConstructor (Rep (ContractInstanceClientState A))) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @(ContractInstanceClientState A)
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic InstanceStatusToClient, Typeable InstanceStatusToClient,
GDataConstructor (Rep InstanceStatusToClient)) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @InstanceStatusToClient
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic CombinedWSStreamToClient,
Typeable CombinedWSStreamToClient,
GDataConstructor (Rep CombinedWSStreamToClient)) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @CombinedWSStreamToClient
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic CombinedWSStreamToServer,
Typeable CombinedWSStreamToServer,
GDataConstructor (Rep CombinedWSStreamToServer)) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @CombinedWSStreamToServer
, SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
genericShow (SumType 'Haskell -> SumType 'Haskell)
-> (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell
-> SumType 'Haskell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SumType 'Haskell -> SumType 'Haskell
forall (t :: Language). SumType t -> SumType t
argonaut (SumType 'Haskell -> SumType 'Haskell)
-> SumType 'Haskell -> SumType 'Haskell
forall a b. (a -> b) -> a -> b
$ (Generic WalletInfo, Typeable WalletInfo,
GDataConstructor (Rep WalletInfo)) =>
SumType 'Haskell
forall t.
(Generic t, Typeable t, GDataConstructor (Rep t)) =>
SumType 'Haskell
mkSumType @WalletInfo
]
pabSettings :: Settings
pabSettings :: Settings
pabSettings = Settings
defaultSettings
Settings -> (Settings -> Settings) -> Settings
forall a b. a -> (a -> b) -> b
& ASetter Settings Settings Text Text -> Text -> Settings -> Settings
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Settings Settings Text Text
Lens' Settings Text
apiModuleName Text
"Plutus.PAB.Webserver"
Settings -> (Settings -> Settings) -> Settings
forall a b. a -> (a -> b) -> b
& [SumType 'Haskell] -> Settings -> Settings
addTypes [SumType 'Haskell]
pabTypes
generateAPIModule
:: forall a. (Typeable a, HasPSTypes a)
=> Proxy a
-> FilePath
-> IO ()
generateAPIModule :: Proxy a -> FilePath -> IO ()
generateAPIModule Proxy a
_ FilePath
outputDir = do
Settings
-> FilePath -> Proxy PabBridge -> Proxy (API a Text) -> IO ()
forall bridgeSelector api.
(HasForeign (PureScript bridgeSelector) PSType api,
GenerateList PSType (Foreign PSType api),
HasBridge bridgeSelector) =>
Settings -> FilePath -> Proxy bridgeSelector -> Proxy api -> IO ()
generateWithSettings
([SumType 'Haskell] -> Settings -> Settings
addTypes (HasPSTypes a => [SumType 'Haskell]
forall a. HasPSTypes a => [SumType 'Haskell]
psTypes @a) Settings
pabSettings)
FilePath
outputDir
Proxy PabBridge
pabBridgeProxy
( Proxy (API (ContractDef (Builtin a)) Text)
forall k (t :: k). Proxy t
Proxy @(API.API (Contract.ContractDef (Builtin a)) Text.Text)
)