Skip to content

Commit

Permalink
Apply stylish-haskell code formatting
Browse files Browse the repository at this point in the history
Addressed formatting issues in various Haskell source files using
stylish-haskell to automatically reorganize imports, align pragmas, and
adjust layout for better code readability and consistency.

These improvements contribute to maintaining a clean and consistent
codebase, ensuring that our Haskell code adheres to community standards
and best practices for style and formatting.
  • Loading branch information
placek committed Jul 17, 2024
1 parent b56cffe commit 638263c
Show file tree
Hide file tree
Showing 12 changed files with 170 additions and 196 deletions.
34 changes: 12 additions & 22 deletions govtool/backend/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,9 +9,7 @@
module Main where

import Control.Concurrent.QSem (newQSem)
import Control.Exception (Exception,
SomeException,
fromException, throw)
import Control.Exception (Exception, SomeException, fromException, throw)
import Control.Lens.Operators ((.~))
import Control.Monad
import Control.Monad.IO.Class
Expand All @@ -25,12 +23,8 @@ import qualified Data.Cache as Cache
import Data.Function ((&))
import Data.Has (getter)
import Data.Monoid (mempty)
import Data.OpenApi (OpenApi,
Server (Server),
_openApiServers,
_serverDescription,
_serverUrl,
_serverVariables,
import Data.OpenApi (OpenApi, Server (Server), _openApiServers,
_serverDescription, _serverUrl, _serverVariables,
servers)
import Data.Pool (createPool)
import Data.Proxy
Expand All @@ -42,9 +36,10 @@ import qualified Data.Text.IO as Text
import qualified Data.Text.Lazy as LazyText
import qualified Data.Text.Lazy.Encoding as LazyText

import Database.PostgreSQL.Simple (close,
connectPostgreSQL)
import Database.PostgreSQL.Simple (close, connectPostgreSQL)

import Network.HTTP.Client hiding (Proxy, Request)
import Network.HTTP.Client.TLS
import Network.Wai
import Network.Wai.Handler.Warp
import Network.Wai.Middleware.Cors
Expand All @@ -55,27 +50,22 @@ import Servant
import Servant.API.ContentTypes
import Servant.OpenApi (toOpenApi)
import qualified Servant.Server as Servant
import Servant.Swagger.UI (SwaggerSchemaUI,
swaggerSchemaUIServer)
import Servant.Swagger.UI (SwaggerSchemaUI, swaggerSchemaUIServer)

import System.Clock (TimeSpec (TimeSpec))
import System.IO (stderr)
import System.Log.Raven (initRaven, register,
silentFallback)
import System.Log.Raven (initRaven, register, silentFallback)
import System.Log.Raven.Transport.HttpConduit (sendRecord)
import System.Log.Raven.Types (SentryLevel (Error),
SentryRecord (..))
import System.Log.Raven.Types (SentryLevel (Error), SentryRecord (..))
import System.TimeManager (TimeoutThread (..))

import VVA.API
import VVA.API.Types
import VVA.CommandLine
import VVA.Config
import VVA.Types (AppEnv (..),
AppError (CriticalError, NotFoundError, ValidationError, InternalError),
AppError (CriticalError, InternalError, 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 @@ -146,10 +136,10 @@ exceptionHandler vvaConfig mRequest exception = do
print exception
let isNotTimeoutThread x = case fromException x of
Just TimeoutThread -> False
_ -> True
_ -> True
isNotConnectionClosedByPeer x = case fromException x of
Just ConnectionClosedByPeer -> False
_ -> True
_ -> True
guard . isNotTimeoutThread $ exception
guard . isNotConnectionClosedByPeer $ exception
let env = sentryEnv vvaConfig
Expand Down
64 changes: 32 additions & 32 deletions govtool/backend/src/VVA/API.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,42 +8,42 @@

module VVA.API where

import Control.Concurrent.QSem (waitQSem, signalQSem)
import Control.Concurrent.Async (mapConcurrently)
import Control.Exception (throw, throwIO)
import Control.Monad.Except (throwError, runExceptT)
import Control.Concurrent.Async (mapConcurrently)
import Control.Concurrent.QSem (signalQSem, waitQSem)
import Control.Exception (throw, throwIO)
import Control.Monad.Except (runExceptT, 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
import Data.Maybe (Maybe (Nothing), fromMaybe, catMaybes)
import Data.Ord (Down (..))
import Data.Text hiding (drop, elem, filter, length, map,
null, take, any)
import qualified Data.Text as Text

import Numeric.Natural (Natural)

import Data.Aeson (Result (Error, Success), fromJSON)
import Data.Bool (Bool)
import Data.List (sortOn)
import qualified Data.Map as Map
import Data.Maybe (Maybe (Nothing), catMaybes, fromMaybe)
import Data.Ord (Down (..))
import Data.Text hiding (any, drop, elem, filter, length, map, null, take)
import qualified Data.Text as Text

import Numeric.Natural (Natural)

import Servant.API
import Servant.Server

import Text.Read (readMaybe)
import Text.Read (readMaybe)

import qualified VVA.AdaHolder as AdaHolder
import qualified VVA.AdaHolder as AdaHolder
import VVA.API.Types
import VVA.Cache (cacheRequest)
import VVA.Cache (cacheRequest)
import VVA.Config
import qualified VVA.DRep as DRep
import qualified VVA.Epoch as Epoch
import VVA.Network as Network
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, InternalError),
CacheEnv (..))
import qualified VVA.Metadata as Metadata
import qualified VVA.DRep as DRep
import qualified VVA.Epoch as Epoch
import qualified VVA.Metadata as Metadata
import VVA.Network as Network
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, InternalError, ValidationError),
CacheEnv (..))

type VVAApi =
"drep" :> "list"
Expand Down Expand Up @@ -230,13 +230,13 @@ proposalToResponse Types.Proposal {..} Types.MetadataValidationResult{..} =
}
where
getTitle p Nothing = p
getTitle _ m = Types.proposalMetadataTitle <$> m
getTitle _ m = Types.proposalMetadataTitle <$> m
getAbstract p Nothing = p
getAbstract _ m = Types.proposalMetadataAbstract <$> m
getAbstract _ m = Types.proposalMetadataAbstract <$> m
getMotivation p Nothing = p
getMotivation _ m = Types.proposalMetadataMotivation <$> m
getMotivation _ m = Types.proposalMetadataMotivation <$> m
getRationale p Nothing = p
getRationale _ m = Types.proposalMetadataRationale <$> m
getRationale _ m = Types.proposalMetadataRationale <$> m
-- TODO: convert aeson references to [Text] from database
--getReferences p Nothing = p
getReferences _ = maybe [] Types.proposalMetadataReferences
Expand Down
49 changes: 19 additions & 30 deletions govtool/backend/src/VVA/API/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,8 +46,7 @@ import Database.PostgreSQL.Simple (Connection)
import GHC.Exts (toList)
import GHC.Generics

import Servant.API (FromHttpApiData, parseQueryParam,
parseUrlPiece)
import Servant.API (FromHttpApiData, parseQueryParam, parseUrlPiece)

import Text.Read (readMaybe)

Expand Down Expand Up @@ -112,26 +111,24 @@ instance ToSchema AnyValue where
& example
?~ toJSON exampleAnyValue

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

instance ToJSON MetadataValidationStatus where
toJSON IncorrectFormat = "INCORRECT_FORMTAT"
toJSON IncorrectJSONLD = "INVALID_JSONLD"
toJSON IncorrectHash = "INVALID_HASH"
toJSON UrlNotFound = "URL_NOT_FOUND"
toJSON IncorrectHash = "INVALID_HASH"
toJSON UrlNotFound = "URL_NOT_FOUND"

instance FromJSON MetadataValidationStatus where
parseJSON (String s) = case s of
"INCORRECT_FORMTAT" -> pure IncorrectFormat
"INVALID_JSONLD" -> pure IncorrectJSONLD
"INVALID_HASH" -> pure IncorrectHash
"URL_NOT_FOUND" -> pure UrlNotFound
_ -> fail "Invalid MetadataValidationStatus"
"INVALID_JSONLD" -> pure IncorrectJSONLD
"INVALID_HASH" -> pure IncorrectHash
"URL_NOT_FOUND" -> pure UrlNotFound
_ -> fail "Invalid MetadataValidationStatus"
parseJSON _ = fail "Invalid MetadataValidationStatus"

instance ToSchema MetadataValidationStatus where
Expand Down Expand Up @@ -168,7 +165,7 @@ instance ToSchema InternalMetadataValidationResponse where
data MetadataValidationResponse
= MetadataValidationResponse
{ metadataValidationResponseStatus :: Maybe Text
, metadataValidationResponseValid :: Bool
, metadataValidationResponseValid :: Bool
}
deriving (Generic, Show)

Expand All @@ -189,7 +186,7 @@ instance ToSchema MetadataValidationResponse where

data MetadataValidationParams
= MetadataValidationParams
{ metadataValidationParamsUrl :: Text
{ metadataValidationParamsUrl :: Text
, metadataValidationParamsHash :: HexText
}
deriving (Generic, Show)
Expand Down Expand Up @@ -302,19 +299,11 @@ instance ToParamSchema GovernanceActionType where
& enum_ ?~ map toJSON (enumFromTo minBound maxBound :: [GovernanceActionType])


data DRepSortMode = VotingPower | RegistrationDate | Status
deriving
( Bounded
, Enum
, Eq
, Generic
, Read
, Show
)
data DRepSortMode = VotingPower | RegistrationDate | Status deriving (Bounded, Enum, Eq, Generic, Read, Show)

instance FromJSON DRepSortMode where
parseJSON (Aeson.String dRepSortMode) = pure $ fromJust $ readMaybe (Text.unpack dRepSortMode)
parseJSON _ = fail ""
parseJSON _ = fail ""

instance ToJSON DRepSortMode where
toJSON x = Aeson.String $ Text.pack $ show x
Expand Down Expand Up @@ -769,7 +758,7 @@ instance ToSchema DRepHash where
?~ toJSON exampleDrepHash


data DRepStatus = Active | Inactive | Retired deriving (Generic, Show, Eq, Ord, Enum, Bounded, Read)
data DRepStatus = Active | Inactive | Retired deriving (Bounded, Enum, Eq, Generic, Ord, Read, Show)

-- ToJSON instance for DRepStatus
instance ToJSON DRepStatus where
Expand Down Expand Up @@ -925,9 +914,9 @@ instance ToSchema ListDRepsResponse where

data DelegationResponse
= DelegationResponse
{ delegationResponseDRepHash :: Maybe HexText
, delegationResponseDRepView :: Text
, delegationResponseTxHash :: HexText
{ delegationResponseDRepHash :: Maybe HexText
, delegationResponseDRepView :: Text
, delegationResponseTxHash :: HexText
}
deriveJSON (jsonOptions "delegationResponse") ''DelegationResponse

Expand Down
6 changes: 3 additions & 3 deletions govtool/backend/src/VVA/API/Utils.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
module VVA.API.Utils where

import Data.Aeson (Options (..), defaultOptions)
import Data.Char
import Data.Aeson (Options (..), defaultOptions)
import Data.Char

import Foreign (pooledMalloc)
import Foreign (pooledMalloc)

-- | Apply function to first element in the list.
applyFirst :: (a -> a) -> [a] -> [a]
Expand Down
4 changes: 2 additions & 2 deletions govtool/backend/src/VVA/AdaHolder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,9 +42,9 @@ getCurrentDelegation ::
getCurrentDelegation stakeKey = withPool $ \conn -> do
result <- liftIO $ SQL.query conn getCurrentDelegationSql (SQL.Only stakeKey)
case result of
[] -> return Nothing
[] -> return Nothing
[(mDRepHash, dRepView, txHash)] -> return $ Just $ Delegation mDRepHash dRepView txHash
_ -> error ("multiple delegations for stake key: " <> unpack stakeKey)
_ -> error ("multiple delegations for stake key: " <> unpack stakeKey)

getVotingPowerSql :: SQL.Query
getVotingPowerSql = sqlFrom $(embedFile "sql/get-stake-key-voting-power.sql")
Expand Down
2 changes: 1 addition & 1 deletion govtool/backend/src/VVA/CommandLine.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module VVA.CommandLine
, cmdParser
) where

import Options.Applicative
import Options.Applicative

data Command = StartApp | ShowConfig deriving (Show)

Expand Down
Loading

0 comments on commit 638263c

Please sign in to comment.