Skip to content

Commit

Permalink
[#876] add metadata validate endpoint
Browse files Browse the repository at this point in the history
  • Loading branch information
jankun4 committed Apr 29, 2024
1 parent 76b8c89 commit 189ef65
Show file tree
Hide file tree
Showing 8 changed files with 149 additions and 13 deletions.
7 changes: 6 additions & 1 deletion govtool/backend/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -72,6 +72,8 @@ import VVA.Config
import VVA.Types (AppEnv (..),
AppError (CriticalError, NotFoundError, ValidationError),
CacheEnv (..))
import Network.HTTP.Client hiding (Proxy, Request)
import Network.HTTP.Client.TLS

proxyAPI :: Proxy (VVAApi :<|> SwaggerAPI)
proxyAPI = Proxy
Expand Down Expand Up @@ -113,6 +115,7 @@ startApp vvaConfig = do
dRepVotingPowerCache <- newCache
dRepListCache <- newCache
networkMetricsCache <- newCache
metadataValidationCache <- newCache
return $ CacheEnv
{ proposalListCache
, getProposalCache
Expand All @@ -124,10 +127,12 @@ startApp vvaConfig = do
, dRepVotingPowerCache
, dRepListCache
, networkMetricsCache
, metadataValidationCache
}
connectionPool <- createPool (connectPostgreSQL (encodeUtf8 (dbSyncConnectionString $ getter vvaConfig))) close 1 1 60
vvaTlsManager <- newManager tlsManagerSettings

let appEnv = AppEnv {vvaConfig=vvaConfig, vvaCache=cacheEnv, vvaConnectionPool=connectionPool}
let appEnv = AppEnv {vvaConfig=vvaConfig, vvaCache=cacheEnv, vvaConnectionPool=connectionPool, vvaTlsManager}
server' <- mkVVAServer appEnv
runSettings settings server'

Expand Down
4 changes: 3 additions & 1 deletion govtool/backend/example-config.json
Original file line number Diff line number Diff line change
Expand Up @@ -9,5 +9,7 @@
"port" : 9999,
"host" : "localhost",
"cachedurationseconds": 20,
"sentrydsn": "https://username:password@senty.host/id"
"sentrydsn": "https://username:password@senty.host/id",
"metadatavalidationhost": "localhost",
"metadatavalidationport": 3001
}
16 changes: 14 additions & 2 deletions govtool/backend/src/VVA/API.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ module VVA.API where
import Control.Exception (throw)
import Control.Monad.Except (throwError)
import Control.Monad.Reader

import Data.Aeson (Result(Error, Success), fromJSON)
import Data.Bool (Bool)
import Data.List (sortOn)
import qualified Data.Map as Map
Expand Down Expand Up @@ -39,8 +39,9 @@ import qualified VVA.Proposal as Proposal
import qualified VVA.Transaction as Transaction
import qualified VVA.Types as Types
import VVA.Types (App, AppEnv (..),
AppError (CriticalError, ValidationError),
AppError (CriticalError, ValidationError, InternalError),
CacheEnv (..))
import qualified VVA.Metadata as Metadata

type VVAApi =
"drep" :> "list"
Expand Down Expand Up @@ -73,6 +74,7 @@ type VVAApi =
:<|> "transaction" :> "status" :> Capture "transactionId" HexText :> Get '[JSON] GetTransactionStatusResponse
:<|> "throw500" :> Get '[JSON] ()
:<|> "network" :> "metrics" :> Get '[JSON] GetNetworkMetricsResponse
:<|> "metadata" :> "validate" :> ReqBody '[JSON] MetadataValidationParams :> Post '[JSON] MetadataValidationResponse

server :: App m => ServerT VVAApi m
server = drepList
Expand All @@ -87,6 +89,7 @@ server = drepList
:<|> getTransactionStatus
:<|> throw500
:<|> getNetworkMetrics
:<|> validateMetadata


mapDRepType :: Types.DRepType -> DRepType
Expand Down Expand Up @@ -390,3 +393,12 @@ getNetworkMetrics = do
, getNetworkMetricsResponseAlwaysAbstainVotingPower = networkMetricsAlwaysAbstainVotingPower
, getNetworkMetricsResponseAlwaysNoConfidenceVotingPower = networkMetricsAlwaysNoConfidenceVotingPower
}

validateMetadata :: App m => MetadataValidationParams -> m MetadataValidationResponse
validateMetadata MetadataValidationParams {..} = do
CacheEnv {metadataValidationCache} <- asks vvaCache
result <- cacheRequest metadataValidationCache (metadataValidationParamsUrl, unHexText metadataValidationParamsHash)
$ Metadata.validateMetadata metadataValidationParamsUrl (unHexText metadataValidationParamsHash)
case fromJSON result of
Error e -> throwError $ InternalError $ pack $ show e
Success a -> return a
72 changes: 72 additions & 0 deletions govtool/backend/src/VVA/API/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -841,3 +841,75 @@ instance ToSchema GetNetworkMetricsResponse where
& description ?~ "GetNetworkMetricsResponse"
& example
?~ toJSON exampleGetNetworkMetricsResponse


data MetadataValidationStatus
= IncorrectFormat
| IncorrectJSONLD
| IncorrectHash
| UrlNotFound
deriving (Show, Eq)

instance ToJSON MetadataValidationStatus where
toJSON IncorrectFormat = "INCORRECT_FORMTAT"
toJSON IncorrectJSONLD = "INCORRECT_JSONLD"
toJSON IncorrectHash = "INCORRECT_HASH"
toJSON UrlNotFound = "URL_NOT_FOUND"

instance FromJSON MetadataValidationStatus where
parseJSON = withText "MetadataValidationStatus" $ \case
"INCORRECT_FORMTAT" -> pure IncorrectFormat
"INCORRECT_JSONLD" -> pure IncorrectJSONLD
"INCORRECT_HASH" -> pure IncorrectHash
"URL_NOT_FOUND" -> pure UrlNotFound
_ -> fail "Invalid MetadataValidationStatus"

instance ToSchema MetadataValidationStatus where
declareNamedSchema _ = pure $ NamedSchema (Just "MetadataValidationStatus") $ mempty
& type_ ?~ OpenApiString
& description ?~ "Metadata Validation Status"
& enum_ ?~ map toJSON [IncorrectFormat, IncorrectJSONLD, IncorrectHash, UrlNotFound]

data MetadataValidationResponse
= MetadataValidationResponse
{ metadataValidationResponseStatus :: Maybe MetadataValidationStatus
, metadataValidationResponseValid :: Bool
}
deriving (Generic, Show)

deriveJSON (jsonOptions "metadataValidationResponse") ''MetadataValidationResponse

instance ToSchema MetadataValidationResponse where
declareNamedSchema _ = do
NamedSchema name_ schema_ <-
genericDeclareNamedSchema
( fromAesonOptions $ jsonOptions "metadataValidationResponse" )
(Proxy :: Proxy MetadataValidationResponse)
return $
NamedSchema name_ $
schema_
& description ?~ "Metadata Validation Response"
& example
?~ toJSON ("{\"status\": \"INCORRECT_FORMTAT\", \"valid\":false}" :: Text)

data MetadataValidationParams
= MetadataValidationParams
{ metadataValidationParamsUrl :: Text
, metadataValidationParamsHash :: HexText
}
deriving (Generic, Show)

deriveJSON (jsonOptions "metadataValidationParams") ''MetadataValidationParams

instance ToSchema MetadataValidationParams where
declareNamedSchema proxy = do
NamedSchema name_ schema_ <-
genericDeclareNamedSchema
( fromAesonOptions $ jsonOptions "metadataValidationParams" )
proxy
return $
NamedSchema name_ $
schema_
& description ?~ "Metadata Validation Params"
& example
?~ toJSON ("{\"url\": \"https://metadata.xyz\", \"hash\": \"9af10e89979e51b8cdc827c963124a1ef4920d1253eef34a1d5cfe76438e3f11\"}" :: Text)
40 changes: 33 additions & 7 deletions govtool/backend/src/VVA/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,8 @@ module VVA.Config
, getServerHost
, getServerPort
, vvaConfigToText
, getMetadataValidationHost
, getMetadataValidationPort
) where

import Conferer
Expand Down Expand Up @@ -69,15 +71,19 @@ instance DefaultConfig DBConfig where
data VVAConfigInternal
= VVAConfigInternal
{ -- | db-sync database access.
vVAConfigInternalDbsyncconfig :: DBConfig
vVAConfigInternalDbsyncconfig :: DBConfig
-- | Server port.
, vVAConfigInternalPort :: Int
, vVAConfigInternalPort :: Int
-- | Server host.
, vVAConfigInternalHost :: Text
, vVAConfigInternalHost :: Text
-- | Request cache duration
, vVaConfigInternalCacheDurationSeconds :: Int
, vVaConfigInternalCacheDurationSeconds :: Int
-- | Sentry DSN
, vVAConfigInternalSentrydsn :: String
, vVAConfigInternalSentrydsn :: String
-- | Metadata validation service host
, vVAConfigInternalMetadataValidationHost :: Text
-- | Metadata validation service port
, vVAConfigInternalMetadataValidationPort :: Int
}
deriving (FromConfig, Generic, Show)

Expand All @@ -88,7 +94,9 @@ instance DefaultConfig VVAConfigInternal where
vVAConfigInternalPort = 3000,
vVAConfigInternalHost = "localhost",
vVaConfigInternalCacheDurationSeconds = 20,
vVAConfigInternalSentrydsn = "https://username:password@senty.host/id"
vVAConfigInternalSentrydsn = "https://username:password@senty.host/id",
vVAConfigInternalMetadataValidationHost = "localhost",
vVAConfigInternalMetadataValidationPort = 3001
}

-- | DEX configuration.
Expand All @@ -104,6 +112,10 @@ data VVAConfig
, cacheDurationSeconds :: Int
-- | Sentry DSN
, sentryDSN :: String
-- | Metadata validation service host
, metadataValidationHost :: Text
-- | Metadata validation service port
, metadataValidationPort :: Int
}
deriving (Generic, Show, ToJSON)

Expand Down Expand Up @@ -143,7 +155,9 @@ convertConfig VVAConfigInternal {..} =
serverPort = vVAConfigInternalPort,
serverHost = vVAConfigInternalHost,
cacheDurationSeconds = vVaConfigInternalCacheDurationSeconds,
sentryDSN = vVAConfigInternalSentrydsn
sentryDSN = vVAConfigInternalSentrydsn,
metadataValidationHost = vVAConfigInternalMetadataValidationHost,
metadataValidationPort = vVAConfigInternalMetadataValidationPort
}

-- | Load configuration from a file specified on the command line. Load from
Expand Down Expand Up @@ -181,3 +195,15 @@ getServerHost ::
(Has VVAConfig r, MonadReader r m) =>
m Text
getServerHost = asks (serverHost . getter)

-- | Access MetadataValidationService host
getMetadataValidationHost ::
(Has VVAConfig r, MonadReader r m) =>
m Text
getMetadataValidationHost = asks (metadataValidationHost . getter)

-- | Access MetadataValidationService port
getMetadataValidationPort ::
(Has VVAConfig r, MonadReader r m) =>
m Int
getMetadataValidationPort = asks (metadataValidationPort . getter)
17 changes: 16 additions & 1 deletion govtool/backend/src/VVA/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ import Database.PostgreSQL.Simple (Connection)

import VVA.Cache
import VVA.Config
import Network.HTTP.Client (Manager)

type App m = (MonadReader AppEnv m, MonadIO m, MonadFail m, MonadError AppError m)

Expand All @@ -31,6 +32,7 @@ data AppEnv
{ vvaConfig :: VVAConfig
, vvaCache :: CacheEnv
, vvaConnectionPool :: Pool Connection
, vvaTlsManager :: Manager
}

instance Has VVAConfig AppEnv where
Expand All @@ -45,10 +47,15 @@ instance Has (Pool Connection) AppEnv where
getter AppEnv {vvaConnectionPool} = vvaConnectionPool
modifier f a@AppEnv {vvaConnectionPool} = a {vvaConnectionPool = f vvaConnectionPool}

instance Has Manager AppEnv where
getter AppEnv {vvaTlsManager} = vvaTlsManager
modifier f a@AppEnv {vvaTlsManager} = a {vvaTlsManager = f vvaTlsManager}

data AppError
= ValidationError Text
| NotFoundError Text
| CriticalError Text
| InternalError Text
deriving (Show)

instance Exception AppError
Expand Down Expand Up @@ -138,6 +145,7 @@ data CacheEnv
, dRepVotingPowerCache :: Cache.Cache Text Integer
, dRepListCache :: Cache.Cache () [DRepRegistration]
, networkMetricsCache :: Cache.Cache () NetworkMetrics
, metadataValidationCache :: Cache.Cache (Text, Text) Value
}

data NetworkMetrics
Expand All @@ -159,4 +167,11 @@ data Delegation
{ delegationDRepHash :: Maybe Text
, delegationDRepView :: Text
, delegationTxHash :: Text
}
}


data MetadataValidationStatus
= IncorrectFormat
| IncorrectJSONLD
| IncorrectHash
| UrlNotFound
4 changes: 4 additions & 0 deletions govtool/backend/vva-be.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -67,6 +67,8 @@ executable vva-be
, http-client
, http-client-tls
, raven-haskell >= 0.1.4.1
, http-client
, http-client-tls

hs-source-dirs: app
default-language: Haskell2010
Expand Down Expand Up @@ -98,6 +100,8 @@ library
, data-has
, resource-pool
, swagger2
, http-client
, http-client-tls


exposed-modules: VVA.Config
Expand Down
2 changes: 1 addition & 1 deletion govtool/metadata-validation/src/main.ts
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ import { DocumentBuilder, SwaggerModule } from '@nestjs/swagger';
import { AppModule } from './app.module';

async function bootstrap() {
const app = await NestFactory.create(AppModule);
const app = await NestFactory.create(AppModule, { cors: true });

const config = new DocumentBuilder()
.setTitle('Submission Tool')
Expand Down

0 comments on commit 189ef65

Please sign in to comment.