Skip to content

Commit

Permalink
Fix warnings and add some more standard language extensions to hydra-…
Browse files Browse the repository at this point in the history
…plutus.cabal
  • Loading branch information
ch1bo committed Jun 14, 2021
1 parent f324de4 commit 1226e81
Show file tree
Hide file tree
Showing 6 changed files with 7 additions and 26 deletions.
26 changes: 5 additions & 21 deletions hydra-plutus/exe/hydra-pab/Main.hs
@@ -1,48 +1,32 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wno-orphans #-}

module Main where

import Cardano.Prelude

import Control.Monad (void)
import Control.Monad.Freer (Eff, Member, interpret, type (~>))
import Control.Monad.Freer.Error (Error)
import Control.Monad.Freer.Extras.Log (LogMsg)
import Control.Monad.IO.Class (MonadIO (..))
import Data.Aeson (
FromJSON (..),
Options (..),
ToJSON (..),
defaultOptions,
genericParseJSON,
genericToJSON,
)
import Data.Text.Prettyprint.Doc (Pretty (..), viaShow)
import GHC.Generics (Generic)
import Hydra.Contract.OffChain as OffChain
import Hydra.Contract.OnChain as OnChain
import Ledger (MonetaryPolicy, pubKeyHash, TxOut, TxOutRef, TxOutTx)
import Plutus.Contract (Contract, BlockchainActions, ContractError, Empty, logInfo)
import Ledger (MonetaryPolicy, TxOut, TxOutRef, TxOutTx, pubKeyHash)
import Plutus.Contract (BlockchainActions, Contract, ContractError, Empty, logInfo)
import Plutus.Contract.Test (walletPubKey)
import Plutus.PAB.Effects.Contract (ContractEffect (..))
import Plutus.PAB.Effects.Contract.Builtin (Builtin, SomeBuiltin (..), type (.\\), endpointsToSchemas)
import Plutus.PAB.Effects.Contract.Builtin (Builtin, SomeBuiltin (..), endpointsToSchemas, type (.\\))
import qualified Plutus.PAB.Effects.Contract.Builtin as Builtin
import Plutus.PAB.Monitoring.PABLogMsg (PABMultiAgentMsg)
import Plutus.PAB.Simulator (SimulatorEffectHandlers)
import qualified Plutus.PAB.Simulator as Simulator
import Plutus.PAB.Types (PABError (..))
import qualified Plutus.PAB.Webserver.Server as PAB.Server
import Schema (FormSchema (..), ToSchema (..))
import Wallet.Emulator.Types (Wallet (..))
import Schema (ToSchema(..), FormSchema(..))

main :: IO ()
main = void $
Expand Down
2 changes: 2 additions & 0 deletions hydra-plutus/hydra-plutus.cabal
Expand Up @@ -32,6 +32,7 @@ common project-config
ConstraintKinds
DataKinds
DefaultSignatures
DeriveAnyClass
DeriveDataTypeable
DeriveFoldable
DeriveFunctor
Expand Down Expand Up @@ -59,6 +60,7 @@ common project-config
ScopedTypeVariables
StandaloneDeriving
TupleSections
TypeApplications
TypeFamilies
TypeOperators
TypeSynonymInstances
Expand Down
1 change: 0 additions & 1 deletion hydra-plutus/src/Hydra/Contract/OffChain.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -fno-specialize #-}

module Hydra.Contract.OffChain where
Expand Down
2 changes: 0 additions & 2 deletions hydra-plutus/src/Hydra/Contract/OnChain.hs
@@ -1,7 +1,5 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -fno-specialize #-}

module Hydra.Contract.OnChain where
Expand Down
1 change: 0 additions & 1 deletion hydra-plutus/test/Hydra/ContractTest.hs
@@ -1,4 +1,3 @@
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -fplugin-opt PlutusTx.Plugin:defer-errors #-}

module Hydra.ContractTest where
Expand Down
1 change: 0 additions & 1 deletion hydra-plutus/test/Hydra/Test/Utils.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TypeApplications #-}

module Hydra.Test.Utils where

Expand Down

0 comments on commit 1226e81

Please sign in to comment.