Skip to content

Commit

Permalink
Update lts (#243)
Browse files Browse the repository at this point in the history
* dependencies resolved, had to remove bloodhound

* project compiles, tests don't

* stylish hlint

* remove empty orphans module

* upgrade to 15.10

* update tintin

* tintin git

* update stylish command

* ignore stack lock

* weeder

* fix weeder file
  • Loading branch information
martyall authored Jul 28, 2020
1 parent b4252a7 commit 733352c
Show file tree
Hide file tree
Showing 49 changed files with 332 additions and 492 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
.stack-work/
stack.yaml.lock
*.cabal
*~
.ci-bins/
Expand Down
2 changes: 1 addition & 1 deletion .travis.yml
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ jobs:
if: branch = master
script:
- echo "test formatting"
- travis_wait 120 stack --skip-ghc-check install hlint-2.1.26 stylish-haskell-0.9.4.3 weeder-1.0.8
- travis_wait 120 stack --skip-ghc-check install hlint-2.2.11 stylish-haskell-0.10.0.0 weeder-1.0.8
- make stylish && git diff-index --quiet HEAD
- make hlint
- make weeder
Expand Down
36 changes: 22 additions & 14 deletions .weeder.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -15,25 +15,28 @@
- module:
- Proto.Types
- Proto.Types_Fields
- Proto.Vendored.Google.Protobuf.Timestamp
- Proto.Vendored.Google.Protobuf.Timestamp_Fields
- Proto.Vendored.Tendermint.Tendermint.Crypto.Merkle.Merkle
- Proto.Vendored.Tendermint.Tendermint.Crypto.Merkle.Merkle_Fields
- Proto.Vendored.Tendermint.Tendermint.Libs.Common.Types
- Proto.Vendored.Tendermint.Tendermint.Libs.Common.Types_Fields
- Proto.Google.Protobuf.Timestamp
- Proto.Google.Protobuf.Timestamp_Fields
- Proto.Tendermint.Tendermint.Crypto.Merkle.Merkle
- Proto.Tendermint.Tendermint.Crypto.Merkle.Merkle_Fields
- Proto.Tendermint.Tendermint.Libs.Common.Types
- Proto.Tendermint.Tendermint.Libs.Common.Types_Fields
- message:
- name: Module not compiled
- module:
- Proto.Types
- Proto.Types_Fields
- Proto.Vendored.Gogo.Protobuf.Gogoproto.Gogo
- Proto.Vendored.Gogo.Protobuf.Gogoproto.Gogo_Fields
- Proto.Vendored.Google.Protobuf.Timestamp
- Proto.Vendored.Google.Protobuf.Timestamp_Fields
- Proto.Vendored.Tendermint.Tendermint.Crypto.Merkle.Merkle
- Proto.Vendored.Tendermint.Tendermint.Crypto.Merkle.Merkle_Fields
- Proto.Vendored.Tendermint.Tendermint.Libs.Common.Types
- Proto.Vendored.Tendermint.Tendermint.Libs.Common.Types_Fields
- Proto.Gogo.Protobuf.Gogoproto.Gogo
- Proto.Gogo.Protobuf.Gogoproto.Gogo_Fields
- Proto.Google.Protobuf.Timestamp
- Proto.Google.Protobuf.Timestamp_Fields
- Proto.Tendermint.Tendermint.Crypto.Merkle.Merkle
- Proto.Tendermint.Tendermint.Crypto.Merkle.Merkle_Fields
- Proto.Tendermint.Tendermint.Libs.Common.Types
- Proto.Tendermint.Tendermint.Libs.Common.Types_Fields
- Proto.Google.Protobuf.Descriptor
- Proto.Google.Protobuf.Descriptor_Fields

- message:
- name: Redundant build-depends entry
- depends: proto-lens-runtime
Expand Down Expand Up @@ -61,10 +64,15 @@
- name: Module not compiled
- module:
- Proto.Google.Api.Annotations
- Proto.Google.Api.Annotations_Fields
- Proto.Google.Api.Http
- Proto.Google.Api.Http_Fields
- Proto.Google.Protobuf.Empty
- Proto.Google.Protobuf.Empty_Fields
- Proto.Iavl.Api
- Proto.Iavl.Api_Fields
- Proto.Google.Protobuf.Descriptor
- Proto.Google.Protobuf.Descriptor_Fields
- message:
- name: Redundant build-depends entry
- depends: proto-lens-runtime
Expand Down
1 change: 1 addition & 0 deletions Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ stylish: ## Run stylish-haskell over all haskell projects
./hs-abci-test-utils \
./hs-abci-server \
./hs-iavl-client \
-not -path "*/.stack-work/*" \
-name "*.hs" | xargs stack exec stylish-haskell -- -c ./.stylish_haskell.yaml -i

###################
Expand Down
2 changes: 0 additions & 2 deletions hs-abci-docs/nameservice/interact/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,10 +2,8 @@ module Main where

import Control.Concurrent.Async (forConcurrently_)
import Control.Monad (forever, replicateM)
import Data.Maybe (maybe)
import Interact
import System.Environment (lookupEnv)
import Text.Read (read)

main :: IO ()
main = do
Expand Down
3 changes: 0 additions & 3 deletions hs-abci-docs/nameservice/package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -43,16 +43,13 @@ library:
- aeson
- aeson-casing
- base >= 4.7 && < 5
- bloodhound
- bytestring
- errors
- hs-abci-extra
- hs-abci-server
- hs-abci-sdk
- hs-abci-types
- http-client
- katip
- katip-elasticsearch
- lens
- polysemy
- polysemy-plugin
Expand Down
18 changes: 5 additions & 13 deletions hs-abci-docs/nameservice/src/Nameservice/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,18 +15,14 @@ import Control.Lens (makeLenses, (&),
import Data.IORef (IORef, newIORef)
import Data.Maybe (fromMaybe)
import Data.String.Conversions (cs)
import qualified Database.V5.Bloodhound as BH
import qualified Katip as K
import qualified Katip.Scribes.ElasticSearch as ES
import qualified Network.HTTP.Client as Client
import System.Environment
import System.IO (stdout)
import qualified Tendermint.SDK.BaseApp as BaseApp
import Tendermint.SDK.BaseApp.Logger.Katip as KL
import qualified Tendermint.SDK.BaseApp.Metrics.Prometheus as P
import Tendermint.SDK.BaseApp.Store.IAVLStore (GrpcConfig (..),
initIAVLVersions)
import Text.Read (read)


data AppConfig = AppConfig
Expand Down Expand Up @@ -87,12 +83,14 @@ makeLogLevel = do
| otherwise = Nothing


data KatipConfig = ES {host :: String, port :: String} | Console
data KatipConfig =
ES String String -- host, port
| Console

makeLoggingConfig :: IO KatipConfig
makeLoggingConfig = do
mEsConfig <- runMaybeT $
ES <$> (MaybeT $ lookupEnv "ES_HOST") <*> (MaybeT $ lookupEnv "ES_PORT")
ES <$> MaybeT (lookupEnv "ES_HOST") <*> MaybeT (lookupEnv "ES_PORT")
pure $ fromMaybe Console mEsConfig

-- makes a log environment for console logs / ES logs
Expand All @@ -105,10 +103,4 @@ makeKatipScribe kcfg LogLevel{..} le = case kcfg of
Console -> do
handleScribe <- K.mkHandleScribe K.ColorIfTerminal stdout (K.permitItem severity) verbosity
K.registerScribe "stdout" handleScribe K.defaultScribeSettings le
ES {host, port} -> do
mgr <- Client.newManager Client.defaultManagerSettings
let serverAddress = "http://" <> host <> ":" <> port
bloodhoundEnv = BH.mkBHEnv (BH.Server $ cs serverAddress) mgr
esScribe <- ES.mkEsScribe ES.defaultEsScribeCfgV5 bloodhoundEnv (BH.IndexName "nameservice")
(BH.MappingName "application-logs") (K.permitItem severity) verbosity
K.registerScribe "es" esScribe K.defaultScribeSettings le
ES _ _ -> error "ES Logging is not available due to dependency issues with Bloodhound ES client"
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module SimpleStorage.Modules.SimpleStorage.Message
)where

import Control.Lens (from, iso, view, (&),
(.~), (^.), _Wrapped')
(.~), (^.))
import Control.Lens.Wrapped (Wrapped (..))
import Data.Bifunctor (bimap)
import Data.Int (Int32)
Expand Down
2 changes: 0 additions & 2 deletions hs-abci-sdk/package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,6 @@ library:
- mtl
- polysemy
- polysemy-plugin
- polysemy-zoo
- prometheus
- proto-lens
- proto-lens-runtime
Expand Down Expand Up @@ -194,7 +193,6 @@ tests:
- memory
- polysemy
- polysemy-plugin
- polysemy-zoo
- prometheus
- secp256k1-haskell
- servant
Expand Down
8 changes: 4 additions & 4 deletions hs-abci-sdk/src/Tendermint/SDK/Application/Module.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ type family DependencyEffs (ms :: [Component]) :: EffectRow where
DependencyEffs (Module _ _ _ _ es deps ': rest) = es :& DependencyEffs rest
DependencyEffs _ = TypeError ('Text "DependencyEffs is a partial function defined only on partially applied Modules")

data Module (name :: Symbol) (check :: *) (deliver :: *) (query :: *) (es :: EffectRow) (deps :: [Component]) (r :: EffectRow) = Module
data Module (name :: Symbol) (check :: Type) (deliver :: Type) (query :: Type) (es :: EffectRow) (deps :: [Component]) (r :: EffectRow) = Module
{ moduleTxChecker :: T.RouteTx check r
, moduleTxDeliverer :: T.RouteTx deliver r
, moduleQuerier :: Q.RouteQ query r
Expand All @@ -61,9 +61,9 @@ data Application check deliver query r s = Application
}

class ToApplication ms r where
type ApplicationC ms :: *
type ApplicationD ms :: *
type ApplicationQ ms :: *
type ApplicationC ms :: Type
type ApplicationD ms :: Type
type ApplicationQ ms :: Type

toApplication :: ModuleList ms r -> Application (ApplicationC ms) (ApplicationD ms) (ApplicationQ ms) r r

Expand Down
7 changes: 3 additions & 4 deletions hs-abci-sdk/src/Tendermint/SDK/BaseApp/Query/Router.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ module Tendermint.SDK.BaseApp.Query.Router
) where

import Control.Monad (join)
import Data.Kind (Type)
import Data.Proxy
import Data.String.Conversions (cs)
import Data.Text (Text)
Expand All @@ -29,9 +30,7 @@ import qualified Tendermint.SDK.BaseApp.Router as R
import Tendermint.SDK.BaseApp.Store (ReadStore, Scope (..))
import Tendermint.SDK.Codec (HasCodec (..))
import Tendermint.SDK.Types.Effects ((:&))
import Web.HttpApiData (FromHttpApiData (..),
parseUrlPieceMaybe)

import Web.HttpApiData (parseUrlPieceMaybe)

--------------------------------------------------------------------------------

Expand All @@ -40,7 +39,7 @@ import Web.HttpApiData (FromHttpApiData (..),
-- | Servant combinators are recognized.
class HasQueryRouter layout r where
-- | A routeQ handler.
type RouteQ layout r :: *
type RouteQ layout r :: Type
-- | Transform a routeQ handler into a 'Router'.
routeQ
:: Proxy layout
Expand Down
5 changes: 3 additions & 2 deletions hs-abci-sdk/src/Tendermint/SDK/BaseApp/Query/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ import Control.Lens (from, lens, to, (^.))
import Data.ByteArray.Base64String (Base64String,
fromBytes, toBytes)
import Data.Int (Int64)
import Data.Kind (Type)
import Data.Text (Text, breakOn, uncons)
import Data.Word (Word64)
import Network.ABCI.Types.Messages.FieldTypes (Proof, WrappedVal (..))
Expand All @@ -29,9 +30,9 @@ import Tendermint.SDK.BaseApp.Router.Types (HasPath (..))
import Tendermint.SDK.BaseApp.Store (RawKey (..))
import Tendermint.SDK.Types.Address (Address)

data Leaf (a :: *)
data Leaf (a :: Type)

data QA (a :: *)
data QA (a :: Type)

--------------------------------------------------------------------------------

Expand Down
3 changes: 2 additions & 1 deletion hs-abci-sdk/src/Tendermint/SDK/BaseApp/Store/Array.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ module Tendermint.SDK.BaseApp.Store.Array
import Control.Lens (iso, (^.))
import qualified Data.ByteArray.HexString as Hex
import qualified Data.ByteString as BS
import Data.Kind (Type)
import Data.Maybe (fromMaybe)
import Data.String.Conversions (cs)
import Data.Word (Word64)
Expand All @@ -34,7 +35,7 @@ import Tendermint.SDK.Codec (HasCodec (..))
-- | A 'Array a' is an appendable list whose elements can be accessed
-- | by their index. You can also delete from the list, in which case accessing
-- | that index will result in a `Nothing`.
data Array (a :: *) = Array
data Array (a :: Type) = Array
{ arrayStore :: S.Store (Array a) }

-- | Represents an index into a list
Expand Down
3 changes: 2 additions & 1 deletion hs-abci-sdk/src/Tendermint/SDK/BaseApp/Store/List.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ import Control.Lens (from, iso, to, view,
(^.))
import Control.Monad (when)
import qualified Data.ByteArray.HexString as Hex
import Data.Kind (Type)
import Data.String.Conversions (cs)
import Data.Word (Word64)
import Polysemy (Members, Sem)
Expand All @@ -31,7 +32,7 @@ import qualified Tendermint.SDK.BaseApp.Store.Map as M
import qualified Tendermint.SDK.BaseApp.Store.RawStore as S
import Tendermint.SDK.Codec (HasCodec (..))

data List (a :: *) = List
data List (a :: Type) = List
{ listStore :: S.Store (List a)
}

Expand Down
3 changes: 2 additions & 1 deletion hs-abci-sdk/src/Tendermint/SDK/BaseApp/Store/Map.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,14 +11,15 @@ module Tendermint.SDK.BaseApp.Store.Map
) where

import Control.Lens ((^.))
import Data.Kind (Type)
import Polysemy (Member, Members, Sem)
import Polysemy.Error (Error)
import Prelude hiding (lookup)
import Tendermint.SDK.BaseApp.Errors (AppError)
import qualified Tendermint.SDK.BaseApp.Store.RawStore as S
import Tendermint.SDK.Codec (HasCodec (..))

data Map (k :: *) (v :: *) = Map
data Map (k :: Type) (v :: Type) = Map
{ mapStore :: S.Store (Map k v)
}

Expand Down
4 changes: 1 addition & 3 deletions hs-abci-sdk/src/Tendermint/SDK/BaseApp/Store/MemoryStore.hs
Original file line number Diff line number Diff line change
Expand Up @@ -122,9 +122,7 @@ evalCommitBlock db DBVersions{..} = do
(\case
CommitBlock -> liftIO $ do
mv <- getVersion db
writeIORef committed $ case mv of
Nothing -> Genesis
Just v -> Version v
writeIORef committed $ maybe Genesis Version mv
root <- getRootHash db
pure . Base64.fromBytes $ root
)
Expand Down
3 changes: 2 additions & 1 deletion hs-abci-sdk/src/Tendermint/SDK/BaseApp/Store/RawStore.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@ module Tendermint.SDK.BaseApp.Store.RawStore
import Control.Lens (Iso', iso, (^.))
import Data.ByteArray.Base64String (Base64String)
import qualified Data.ByteString as BS
import Data.Kind (Type)
import Data.Proxy
import Data.String.Conversions (cs)
import Data.Text
Expand Down Expand Up @@ -75,7 +76,7 @@ instance RawKey () where
rawKey = iso (const "") (const ())

class RawKey k => IsKey k ns where
type Value k ns :: *
type Value k ns :: Type
prefix :: Proxy k -> Proxy ns -> BS.ByteString

default prefix :: Proxy k -> Proxy ns -> BS.ByteString
Expand Down
2 changes: 1 addition & 1 deletion hs-abci-sdk/src/Tendermint/SDK/BaseApp/Store/TH.hs
Original file line number Diff line number Diff line change
Expand Up @@ -101,7 +101,7 @@ mkIsKeyInstance
-> Q Dec
mkIsKeyInstance namespaceName keyTypeName t =
instanceD (pure []) (conT ''IsKey `appT` conT keyTypeName `appT` conT namespaceName)
[tySynInstD ''Value $ tySynEqn [conT keyTypeName, conT namespaceName] t]
[tySynInstD $ tySynEqn Nothing (conT ''Value `appT` conT keyTypeName `appT` conT namespaceName) t]



Expand Down
3 changes: 2 additions & 1 deletion hs-abci-sdk/src/Tendermint/SDK/BaseApp/Store/Var.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module Tendermint.SDK.BaseApp.Store.Var
) where

import Control.Lens ((^.))
import Data.Kind (Type)
import Polysemy (Member, Members, Sem)
import Polysemy.Error (Error)
import Tendermint.SDK.BaseApp.Errors (AppError,
Expand All @@ -17,7 +18,7 @@ import Tendermint.SDK.BaseApp.Errors (AppError,
import qualified Tendermint.SDK.BaseApp.Store.RawStore as S
import Tendermint.SDK.Codec (HasCodec (..))

data Var (a :: *) = Var
data Var (a :: Type) = Var
{ varStore :: S.Store (Var a) }

instance S.IsKey () (Var a) where
Expand Down
5 changes: 3 additions & 2 deletions hs-abci-sdk/src/Tendermint/SDK/BaseApp/Transaction/Checker.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ module Tendermint.SDK.BaseApp.Transaction.Checker
, VoidReturn
) where

import Data.Kind (Type)
import Data.Proxy
import qualified Data.Validation as V
import Polysemy (EffectRow, Member,
Expand All @@ -26,13 +27,13 @@ defaultCheckTxHandler(RoutingTx Tx{txMsg}) =
throwSDKError . MessageValidation . map formatMessageSemanticError $ err
V.Success _ -> pure ()

type family VoidReturn (api :: *) :: * where
type family VoidReturn (api :: Type) :: Type where
VoidReturn (a :<|> b) = VoidReturn a :<|> VoidReturn b
VoidReturn (path :> a) = path :> VoidReturn a
VoidReturn (TypedMessage msg :~> Return a) = TypedMessage msg :~> Return ()

class DefaultCheckTx api (r :: EffectRow) where
type DefaultCheckTxT api r :: *
type DefaultCheckTxT api r :: Type
defaultCheckTx :: Proxy api -> Proxy r -> DefaultCheckTxT api r

instance (DefaultCheckTx a r, DefaultCheckTx b r) => DefaultCheckTx (a :<|> b) r where
Expand Down
Loading

0 comments on commit 733352c

Please sign in to comment.