Skip to content

Commit

Permalink
Update stylish haskell config; apply all; add CI config (PostgREST#1299)
Browse files Browse the repository at this point in the history
* Update config default; Copy non-defaults

* Update .stylish-haskell config version to match pgrst

* Apply stylish haskell to all files

* CircleCI config

* Remove redundant import.

What is used from Network.HTTP.Types.Headers is also exported by Network.HTTP.Types.

* Grouped imports

* Show un-styled files on CircleCI failure

* Fix styling imports

* Apply adhoc standard correctly
  • Loading branch information
Qu4tro authored and steve-chavez committed May 23, 2019
1 parent 16af470 commit 28b3d6c
Show file tree
Hide file tree
Showing 43 changed files with 604 additions and 550 deletions.
5 changes: 4 additions & 1 deletion .circleci/config.yml
Original file line number Diff line number Diff line change
Expand Up @@ -77,7 +77,7 @@ jobs:
sudo apt-get install -y postgresql-client
stack setup
rm -rf $(stack path --dist-dir) $(stack path --local-install-root)
stack install hlint packdeps cabal-install
stack install hlint packdeps cabal-install stylish-haskell
- run:
name: build src and tests
command: |
Expand All @@ -91,6 +91,9 @@ jobs:
- run:
name: run linter
command: git ls-files | grep '\.l\?hs$' | xargs stack exec -- hlint -X QuasiQuotes -X NoPatternSynonyms "$@"
- run:
name: run styler
command: git ls-files | grep '\.l\?hs$' | xargs stack exec -- stylish-haskell -i && git diff-index --exit-code HEAD --
- save_cache:
paths:
- "~/.stack"
Expand Down
45 changes: 40 additions & 5 deletions .stylish-haskell.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -39,9 +39,9 @@ steps:
# - none: Do not perform any alignment.
#
# Default: global.
align: global
align: group

# Folowing options affect only import list alignment.
# The following options affect only import list alignment.
#
# List align has following options:
#
Expand All @@ -64,6 +64,25 @@ steps:
# Default: after_alias
list_align: after_alias

# Right-pad the module names to align imports in a group:
#
# - true: a little more readable
#
# > import qualified Data.List as List (concat, foldl, foldr,
# > init, last, length)
# > import qualified Data.List.Extra as List (concat, foldl, foldr,
# > init, last, length)
#
# - false: diff-safe
#
# > import qualified Data.List as List (concat, foldl, foldr, init,
# > last, length)
# > import qualified Data.List.Extra as List (concat, foldl, foldr,
# > init, last, length)
#
# Default: true
pad_module_names: true

# Long list align style takes effect when import is too long. This is
# determined by 'columns' setting.
#
Expand All @@ -75,7 +94,7 @@ steps:
# short enough to fit to single line. Otherwise it'll be multiline.
#
# - multiline: One line per import list entry.
# Type with contructor list acts like single import.
# Type with constructor list acts like single import.
#
# > import qualified Data.Map as M
# > ( empty
Expand Down Expand Up @@ -109,7 +128,7 @@ steps:
# Useful for 'file' and 'group' align settings.
list_padding: 4

# Separate lists option affects formating of import list for type
# Separate lists option affects formatting of import list for type
# or class. The only difference is single space between type and list
# of constructors, selectors and class functions.
#
Expand All @@ -126,6 +145,22 @@ steps:
# Default: true
separate_lists: true

# Space surround option affects formatting of import lists on a single
# line. The only difference is single space after the initial
# parenthesis and a single space before the terminal parenthesis.
#
# - true: There is single space associated with the enclosing
# parenthesis.
#
# > import Data.Foo ( foo )
#
# - false: There is no space associated with the enclosing parenthesis
#
# > import Data.Foo (foo)
#
# Default: false
space_surround: false

# Language pragmas
- language_pragmas:
# We can generate different styles of language pragma lists.
Expand All @@ -142,7 +177,7 @@ steps:

# Align affects alignment of closing pragma brackets.
#
# - true: Brackets are aligned in same collumn.
# - true: Brackets are aligned in same column.
#
# - false: Brackets are not aligned together. There is only one space
# between actual import and closing bracket.
Expand Down
65 changes: 33 additions & 32 deletions main/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,41 +2,42 @@

module Main where


import PostgREST.App (postgrest)
import PostgREST.Config (AppConfig (..), configPoolTimeout',
prettyVersion, readOptions)
import PostgREST.DbStructure (getDbStructure, getPgVersion)
import PostgREST.Error (errorPayload, checkIsFatal, PgError(PgError))
import PostgREST.OpenAPI (isMalformedProxyUri)
import PostgREST.Types (DbStructure, Schema, PgVersion(..), minimumPgVersion, ConnectionStatus(..))
import Protolude hiding (hPutStrLn, replace)


import Control.AutoUpdate (defaultUpdateSettings,
mkAutoUpdate, updateAction)
import Control.Retry (RetryStatus, capDelay,
exponentialBackoff,
retrying, rsPreviousDelay)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base64 as B64
import Data.IORef (IORef, atomicWriteIORef,
newIORef, readIORef)
import Data.String (IsString (..))
import Data.Text (pack, replace, stripPrefix, strip)
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import Data.Text.IO (hPutStrLn, readFile)
import Data.Time.Clock (getCurrentTime)
import qualified Hasql.Pool as P
import qualified Hasql.Transaction.Sessions as HT
import Network.Wai.Handler.Warp (defaultSettings,
runSettings, setHost,
setPort, setServerName)
import System.IO (BufferMode (..),
hSetBuffering)

import Control.AutoUpdate (defaultUpdateSettings, mkAutoUpdate,
updateAction)
import Control.Retry (RetryStatus, capDelay,
exponentialBackoff, retrying,
rsPreviousDelay)
import Data.IORef (IORef, atomicWriteIORef, newIORef,
readIORef)
import Data.String (IsString (..))
import Data.Text (pack, replace, strip, stripPrefix)
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import Data.Text.IO (hPutStrLn, readFile)
import Data.Time.Clock (getCurrentTime)
import Network.Wai.Handler.Warp (defaultSettings, runSettings,
setHost, setPort, setServerName)
import System.IO (BufferMode (..), hSetBuffering)

import PostgREST.App (postgrest)
import PostgREST.Config (AppConfig (..), configPoolTimeout',
prettyVersion, readOptions)
import PostgREST.DbStructure (getDbStructure, getPgVersion)
import PostgREST.Error (PgError (PgError), checkIsFatal,
errorPayload)
import PostgREST.OpenAPI (isMalformedProxyUri)
import PostgREST.Types (ConnectionStatus (..), DbStructure,
PgVersion (..), Schema,
minimumPgVersion)
import Protolude hiding (hPutStrLn, replace)


#ifndef mingw32_HOST_OS
import System.Posix.Signals
import System.Posix.Signals
#endif

{-|
Expand Down Expand Up @@ -75,7 +76,7 @@ connectionWorker mainTid pool schema refDbStructure refIsWorkerOn = do
putStrLn ("Attempting to connect to the database..." :: Text)
connected <- connectionStatus pool
case connected of
FatalConnectionError reason -> hPutStrLn stderr reason
FatalConnectionError reason -> hPutStrLn stderr reason
>> killThread mainTid -- Fatal error when connecting
NotConnected -> return () -- Unreachable
Connected actualPgVersion -> do -- Procede with initialization
Expand All @@ -87,7 +88,7 @@ connectionWorker mainTid pool schema refDbStructure refIsWorkerOn = do
putStrLn ("Failed to query the database. Retrying." :: Text)
hPutStrLn stderr . toS . errorPayload $ PgError False e
work

Right _ -> do
atomicWriteIORef refIsWorkerOn False
putStrLn ("Connection successful" :: Text)
Expand Down Expand Up @@ -298,6 +299,6 @@ loadDbUriFile conf = extractDbUri mDbUri
extractDbUri dbUri =
fmap setDbUri $
case stripPrefix "@" dbUri of
Nothing -> return dbUri
Nothing -> return dbUri
Just filename -> strip <$> readFile (toS filename)
setDbUri dbUri = conf {configDatabase = dbUri}
98 changes: 53 additions & 45 deletions src/PostgREST/ApiRequest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ Description : PostgREST functions to translate HTTP request to a domain type cal
-}
{-# LANGUAGE LambdaCase #-}

module PostgREST.ApiRequest (
module PostgREST.ApiRequest (
ApiRequest(..)
, ContentType(..)
, Action(..)
Expand All @@ -14,33 +14,41 @@ module PostgREST.ApiRequest (
, userApiRequest
) where

import Protolude
import qualified Data.Aeson as JSON
import Data.Aeson.Types (emptyObject, emptyArray)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Internal as BS (c2w)
import qualified Data.ByteString.Lazy as BL
import qualified Data.Csv as CSV
import qualified Data.List as L
import Data.List (lookup, last, partition)
import qualified Data.HashMap.Strict as M
import qualified Data.Set as S
import Data.Maybe (fromJust)
import Control.Arrow ((***))
import qualified Data.Text as T
import qualified Data.Vector as V
import Network.HTTP.Base (urlEncodeVars)
import Network.HTTP.Types.Header (hAuthorization, hCookie)
import Network.HTTP.Types.URI (parseSimpleQuery, parseQueryReplacePlus)
import Network.Wai (Request (..))
import Network.Wai.Parse (parseHttpAccept)
import PostgREST.RangeQuery (NonnegRange, rangeRequested, restrictRange, rangeGeq, allRange, rangeLimit, rangeOffset)
import Data.Ranged.Boundaries
import PostgREST.Types
import PostgREST.Error (ApiRequestError(..))
import Data.Ranged.Ranges (Range(..), rangeIntersection, emptyRange)
import qualified Data.CaseInsensitive as CI
import Web.Cookie (parseCookiesText)
import qualified Data.Aeson as JSON
import qualified Data.ByteString as BS
import qualified Data.ByteString.Internal as BS (c2w)
import qualified Data.ByteString.Lazy as BL
import qualified Data.CaseInsensitive as CI
import qualified Data.Csv as CSV
import qualified Data.HashMap.Strict as M
import qualified Data.List as L
import qualified Data.Set as S
import qualified Data.Text as T
import qualified Data.Vector as V

import Control.Arrow ((***))
import Data.Aeson.Types (emptyArray, emptyObject)
import Data.List (last, lookup, partition)
import Data.Maybe (fromJust)
import Data.Ranged.Ranges (Range (..), emptyRange,
rangeIntersection)
import Network.HTTP.Base (urlEncodeVars)
import Network.HTTP.Types.Header (hAuthorization, hCookie)
import Network.HTTP.Types.URI (parseQueryReplacePlus,
parseSimpleQuery)
import Network.Wai (Request (..))
import Network.Wai.Parse (parseHttpAccept)
import Web.Cookie (parseCookiesText)


import Data.Ranged.Boundaries

import PostgREST.Error (ApiRequestError (..))
import PostgREST.RangeQuery (NonnegRange, allRange, rangeGeq,
rangeLimit, rangeOffset, rangeRequested,
restrictRange)
import PostgREST.Types
import Protolude

type RequestBody = BL.ByteString

Expand Down Expand Up @@ -68,41 +76,41 @@ data PreferRepresentation = Full | HeadersOnly | None deriving Eq
-}
data ApiRequest = ApiRequest {
-- | Similar but not identical to HTTP verb, e.g. Create/Invoke both POST
iAction :: Action
iAction :: Action
-- | Requested range of rows within response
, iRange :: M.HashMap ByteString NonnegRange
, iRange :: M.HashMap ByteString NonnegRange
-- | The target, be it calling a proc or accessing a table
, iTarget :: Target
, iTarget :: Target
-- | Content types the client will accept, [CTAny] if no Accept header
, iAccepts :: [ContentType]
, iAccepts :: [ContentType]
-- | Data sent by client and used for mutation actions
, iPayload :: Maybe PayloadJSON
, iPayload :: Maybe PayloadJSON
-- | If client wants created items echoed back
, iPreferRepresentation :: PreferRepresentation
, iPreferRepresentation :: PreferRepresentation
-- | Pass all parameters as a single json object to a stored procedure
, iPreferSingleObjectParameter :: Bool
-- | Whether the client wants a result count (slower)
, iPreferCount :: Bool
, iPreferCount :: Bool
-- | Whether the client wants to UPSERT or ignore records on PK conflict
, iPreferResolution :: Maybe PreferResolution
, iPreferResolution :: Maybe PreferResolution
-- | Filters on the result ("id", "eq.10")
, iFilters :: [(Text, Text)]
, iFilters :: [(Text, Text)]
-- | &and and &or parameters used for complex boolean logic
, iLogic :: [(Text, Text)]
, iLogic :: [(Text, Text)]
-- | &select parameter used to shape the response
, iSelect :: Text
, iSelect :: Text
-- | &columns parameter used to shape the payload
, iColumns :: Maybe Text
, iColumns :: Maybe Text
-- | &order parameters for each level
, iOrder :: [(Text, Text)]
, iOrder :: [(Text, Text)]
-- | Alphabetized (canonical) request query string for response URLs
, iCanonicalQS :: ByteString
, iCanonicalQS :: ByteString
-- | JSON Web Token
, iJWT :: Text
, iJWT :: Text
-- | HTTP request headers
, iHeaders :: [(Text, Text)]
, iHeaders :: [(Text, Text)]
-- | Request Cookies
, iCookies :: [(Text, Text)]
, iCookies :: [(Text, Text)]
}

-- | Examines HTTP request and translates it into user intent.
Expand Down
Loading

0 comments on commit 28b3d6c

Please sign in to comment.