Skip to content

Commit

Permalink
Replace ConfigProvider and LoggingProvider with dot notation
Browse files Browse the repository at this point in the history
  • Loading branch information
mpscholten committed Oct 17, 2022
1 parent bd51649 commit be0860d
Show file tree
Hide file tree
Showing 17 changed files with 38 additions and 84 deletions.
4 changes: 1 addition & 3 deletions IHP/Assets/ViewFunctions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,5 @@ assetPath assetPath = assetPath <> "?v=" <> assetVersion
-- The asset version can be configured using the
-- @IHP_ASSET_VERSION@ environment variable.
assetVersion :: (?context :: ControllerContext) => Text
assetVersion = ?context
|> Config.getFrameworkConfig
|> get #assetVersion
assetVersion = ?context.frameworkConfig.assetVersion
{-# INLINABLE assetVersion #-}
10 changes: 5 additions & 5 deletions IHP/Controller/Context.hs
Original file line number Diff line number Diff line change
Expand Up @@ -133,9 +133,9 @@ putContext value = do

newtype ActionType = ActionType Typeable.TypeRep

instance ConfigProvider ControllerContext where
getFrameworkConfig context = getFrameworkConfig (get #requestContext context)
{-# INLINABLE getFrameworkConfig #-}
instance HasField "frameworkConfig" ControllerContext FrameworkConfig where
getField controllerContext = controllerContext.requestContext.frameworkConfig
{-# INLINABLE getField #-}

instance LoggingProvider ControllerContext where
getLogger = getLogger . getFrameworkConfig
instance HasField "logger" ControllerContext Logger where
getField controllerContext = controllerContext.frameworkConfig.logger
2 changes: 1 addition & 1 deletion IHP/Controller/Redirect.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ redirectTo action = redirectToPath (pathTo action)
--
-- Use 'redirectTo' if you want to redirect to a controller action.
redirectToPath :: (?context :: ControllerContext) => Text -> IO ()
redirectToPath path = redirectToUrl (fromConfig baseUrl <> path)
redirectToPath path = redirectToUrl (?context.frameworkConfig.baseUrl <> path)
{-# INLINABLE redirectToPath #-}

-- | Redirects to a url (given as a string)
Expand Down
4 changes: 0 additions & 4 deletions IHP/Controller/RequestContext.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
module IHP.Controller.RequestContext
( RequestContext (..)
, Respond
, getConfig
, RequestBody (..)
) where

Expand All @@ -28,6 +27,3 @@ data RequestContext = RequestContext
, vault :: (Vault.Key (Session IO ByteString ByteString))
, frameworkConfig :: FrameworkConfig
}

instance ConfigProvider RequestContext where
getFrameworkConfig = frameworkConfig
4 changes: 1 addition & 3 deletions IHP/ControllerSupport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -342,9 +342,7 @@ respondAndExit response = do
-- > putStrLn ("Stripe public key: " <> stripePublicKey)
--
getAppConfig :: forall configParameter context. (?context :: context, ConfigProvider context, Typeable configParameter) => configParameter
getAppConfig = ?context
|> getFrameworkConfig
|> get #appConfig
getAppConfig = ?context.frameworkConfig.appConfig
|> TypeMap.lookup @configParameter
|> fromMaybe (error ("Could not find " <> (show (Typeable.typeRep (Typeable.Proxy @configParameter))) <>" in config"))
{-# INLINE getAppConfig #-}
16 changes: 6 additions & 10 deletions IHP/ErrorController.hs
Original file line number Diff line number Diff line change
Expand Up @@ -161,7 +161,7 @@ displayException exception action additionalInfo = do
[ recordNotFoundExceptionHandlerProd
]

let allHandlers = if fromConfig environment == Environment.Development
let allHandlers = if ?context.frameworkConfig.environment == Environment.Development
then devHandlers
else prodHandlers

Expand Down Expand Up @@ -199,7 +199,7 @@ genericHandler exception controller additionalInfo = do
let prodErrorMessage = [hsx|An exception was raised while running the action|]
let prodTitle = [hsx|An error happened|]

let (errorMessage, errorTitle) = if fromConfig environment == Environment.Development
let (errorMessage, errorTitle) = if ?context.frameworkConfig.environment == Environment.Development
then (devErrorMessage, devTitle)
else (prodErrorMessage, prodTitle)
let RequestContext { respond } = get #requestContext ?context
Expand All @@ -211,9 +211,7 @@ postgresHandler exception controller additionalInfo = do
let
handlePostgresOutdatedError :: Show exception => exception -> H.Html -> IO ResponseReceived
handlePostgresOutdatedError exception errorText = do
let ihpIdeBaseUrl = ?context
|> getFrameworkConfig
|> get #ideBaseUrl
let ihpIdeBaseUrl = ?context.frameworkConfig.ideBaseUrl
let title = [hsx|Database looks outdated. {errorText}|]
let errorMessage = [hsx|
<h2>Possible Solutions</h2>
Expand All @@ -234,10 +232,8 @@ postgresHandler exception controller additionalInfo = do

handleSqlError :: ModelSupport.EnhancedSqlError -> IO ResponseReceived
handleSqlError exception = do
let ihpIdeBaseUrl = ?context
|> getFrameworkConfig
|> get #ideBaseUrl
let sqlError = get #sqlError exception
let ihpIdeBaseUrl = ?context.frameworkConfig.ideBaseUrl
let sqlError = exception.sqlError
let title = [hsx|{get #sqlErrorMsg sqlError}|]
let errorMessage = [hsx|
<h2>While running the following Query:</h2>
Expand Down Expand Up @@ -585,7 +581,7 @@ renderError errorTitle view = H.docTypeHtml ! A.lang "en" $ [hsx|
</body>
|]
where
shouldShowHelpFooter = (fromConfig environment) == Environment.Development
shouldShowHelpFooter = ?context.frameworkConfig.environment == Environment.Development
helpFooter = [hsx|
<div class="ihp-error-other-solutions">
<a href="https://stackoverflow.com/questions/tagged/ihp" target="_blank">Ask the IHP Community on StackOverflow</a>
Expand Down
11 changes: 5 additions & 6 deletions IHP/FileStorage/ControllerFunctions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -106,8 +106,8 @@ storeFileWithOptions fileInfo options = do
|> get #fileContent
|> LBS.writeFile (cs destPath)

let frameworkConfig = getFrameworkConfig ?context
pure $ (get #baseUrl frameworkConfig) <> "/" <> objectPath
let frameworkConfig = ?context.frameworkConfig
pure $ frameworkConfig.baseUrl <> "/" <> objectPath
S3Storage { connectInfo, bucket, baseUrl } -> do
let payload = fileInfo
|> get #fileContent
Expand Down Expand Up @@ -220,8 +220,8 @@ createTemporaryDownloadUrlFromPathWithExpiredAt validInSeconds objectPath = do
publicUrlExpiredAt <- addUTCTime (fromIntegral validInSeconds) <$> getCurrentTime
case storage of
StaticDirStorage -> do
let frameworkConfig = getFrameworkConfig ?context
let url = (get #baseUrl frameworkConfig) <> "/" <> objectPath
let frameworkConfig = ?context.frameworkConfig
let url = frameworkConfig.baseUrl <> "/" <> objectPath

pure TemporaryDownloadUrl { url = cs url, expiredAt = publicUrlExpiredAt }
S3Storage { connectInfo, bucket} -> do
Expand Down Expand Up @@ -361,7 +361,6 @@ removeFileFromStorage StoredFile { path, url } = do

-- | Returns the current storage configured in Config.hs
storage :: (?context :: context, ConfigProvider context) => FileStorage
storage = getFrameworkConfig ?context
|> get #appConfig
storage = ?context.frameworkConfig.appConfig
|> TMap.lookup @FileStorage
|> fromMaybe (error "Could not find FileStorage in config. Did you call initS3Storage from your Config.hs?")
23 changes: 4 additions & 19 deletions IHP/FrameworkConfig.hs
Original file line number Diff line number Diff line change
Expand Up @@ -457,25 +457,10 @@ data FrameworkConfig = FrameworkConfig
, customMiddleware :: !CustomMiddleware
}

class ConfigProvider a where
getFrameworkConfig :: a -> FrameworkConfig
instance HasField "frameworkConfig" FrameworkConfig FrameworkConfig where
getField frameworkConfig = frameworkConfig

instance ConfigProvider FrameworkConfig where
getFrameworkConfig = id

instance LoggingProvider FrameworkConfig where
getLogger = get #logger


-- | Proxies FrameworkConfig fields contained in some context that can provider a FrameworkConfig
fromConfig :: (?context :: context, ConfigProvider context) => (FrameworkConfig -> a) -> a
fromConfig selector = (selector . getFrameworkConfig) ?context
{-# INLINE fromConfig #-}

-- | Get the current frameworkConfig
getConfig :: (?context :: context, ConfigProvider context) => FrameworkConfig
getConfig = fromConfig id
{-# INLINE getConfig #-}
type ConfigProvider context = HasField "frameworkConfig" context FrameworkConfig

-- | Returns the default IHP session cookie configuration. Useful when you want to override the default settings in 'sessionCookie'
defaultIHPSessionCookie :: Text -> Cookie.SetCookie
Expand Down Expand Up @@ -506,7 +491,7 @@ defaultLoggerForEnv = \case

-- Returns 'True' when the application is running in a given environment
isEnvironment :: (?context :: context, ConfigProvider context) => Environment -> Bool
isEnvironment environment = (getFrameworkConfig ?context |> get #environment) == environment
isEnvironment environment = ?context.frameworkConfig.environment == environment
{-# INLINABLE isEnvironment #-}

-- | Returns 'True' when the application is running in Development mode
Expand Down
2 changes: 1 addition & 1 deletion IHP/IDE/Data/Controller.hs
Original file line number Diff line number Diff line change
Expand Up @@ -199,7 +199,7 @@ instance Controller DataController where
Nothing -> renderNotFound

connectToAppDb :: (?context :: ControllerContext) => IO PG.Connection
connectToAppDb = PG.connectPostgreSQL $ fromConfig databaseUrl
connectToAppDb = PG.connectPostgreSQL ?context.frameworkConfig.databaseUrl

fetchTableNames :: PG.Connection -> IO [Text]
fetchTableNames connection = do
Expand Down
5 changes: 1 addition & 4 deletions IHP/IDE/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -130,7 +130,4 @@ data Context = Context
}

dispatch :: (?context :: Context) => Action -> IO ()
dispatch = let Context { .. } = ?context in putMVar actionVar

instance Log.LoggingProvider Context where
getLogger Context { logger } = logger
dispatch = let Context { .. } = ?context in putMVar actionVar
3 changes: 1 addition & 2 deletions IHP/Log.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,7 @@ import qualified System.Log.FastLogger as FastLogger
-- function corresponding to the desired log level.
log :: (?context :: context, LoggingProvider context, FastLogger.ToLogStr string) => LogLevel -> string -> IO ()
log level text = do
let logger = getLogger ?context
writeLog level logger text
writeLog level ?context.logger text

-- | Log a debug level message.
--
Expand Down
12 changes: 6 additions & 6 deletions IHP/Log/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,7 @@ import System.Log.FastLogger (
)

import qualified System.Log.FastLogger as FastLogger (FormattedTime)
import GHC.Records


-- some functions brought over from IHP.Prelude
Expand Down Expand Up @@ -200,13 +201,12 @@ defaultDestination :: LogDestination
defaultDestination = Stdout defaultBufSize

-- | Used to get the logger for a given environment.
class LoggingProvider a where
-- | Call in any instance of 'LoggingProvider' get the the environment's current logger.
-- Useful in controller and model actions, which both have logging contexts.
getLogger :: a -> Logger
-- | Call in any instance of 'LoggingProvider' get the the environment's current logger.
-- Useful in controller and model actions, which both have logging contexts.
type LoggingProvider context = HasField "logger" context Logger

instance {-# OVERLAPS #-} LoggingProvider Logger where
getLogger = id
instance HasField "logger" Logger Logger where
getField logger = logger

-- | Create a new 'FastLogger' and wrap it in an IHP 'Logger'.
-- Use with the default logger settings and record update syntax for nice configuration:
Expand Down
6 changes: 2 additions & 4 deletions IHP/LoginSupport/Helper/Controller.hs
Original file line number Diff line number Diff line change
Expand Up @@ -165,10 +165,8 @@ enableRowLevelSecurityIfLoggedIn ::
enableRowLevelSecurityIfLoggedIn = do
case currentUserOrNothing of
Just user -> do
let rlsAuthenticatedRole = ?context
|> FrameworkConfig.getFrameworkConfig
|> get #rlsAuthenticatedRole
let rlsUserId = PG.toField (get #id user)
let rlsAuthenticatedRole = ?context.frameworkConfig.rlsAuthenticatedRole
let rlsUserId = PG.toField user.id
let rlsContext = ModelSupport.RowLevelSecurityContext { rlsAuthenticatedRole, rlsUserId}
putContext rlsContext
Nothing -> pure ()
2 changes: 1 addition & 1 deletion IHP/Mail.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ buildMail mail =
--
-- Uses the mail server provided in the controller context, configured in Config/Config.hs
sendMail :: (BuildMail mail, ?context :: context, ConfigProvider context) => mail -> IO ()
sendMail mail = sendWithMailServer (fromConfig mailServer) (buildMail mail)
sendMail mail = sendWithMailServer ?context.frameworkConfig.mailServer (buildMail mail)

sendWithMailServer :: MailServer -> Mail -> IO ()
sendWithMailServer SES { .. } mail = do
Expand Down
3 changes: 0 additions & 3 deletions IHP/ModelSupport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -92,9 +92,6 @@ createModelContext idleTime maxConnections databaseUrl logger = do
let rowLevelSecurity = Nothing
pure ModelContext { .. }

instance LoggingProvider ModelContext where
getLogger ModelContext { .. } = logger

type family GetModelById id :: Type where
GetModelById (Maybe (Id' tableName)) = Maybe (GetModelByTableName tableName)
GetModelById (Id' tableName) = GetModelByTableName tableName
Expand Down
2 changes: 1 addition & 1 deletion IHP/RouterSupport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -157,7 +157,7 @@ class HasPath controller where
-- >>> urlTo ShowUserAction { userId = "a32913dd-ef80-4f3e-9a91-7879e17b2ece" }
-- "http://localhost:8000/ShowUser?userId=a32913dd-ef80-4f3e-9a91-7879e17b2ece"
urlTo :: (?context :: context, ConfigProvider context, HasPath action) => action -> Text
urlTo action = (fromConfig baseUrl) <> pathTo action
urlTo action = ?context.frameworkConfig.baseUrl <> pathTo action
{-# INLINE urlTo #-}

class HasPath controller => CanRoute controller where
Expand Down
13 changes: 2 additions & 11 deletions IHP/ViewSupport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -244,9 +244,7 @@ fromCSSFramework :: (?context :: ControllerContext, KnownSymbol field, HasField
fromCSSFramework field = let cssFramework = theCSSFramework in (get field cssFramework) cssFramework

theCSSFramework :: (?context :: ControllerContext) => CSSFramework
theCSSFramework = ?context
|> FrameworkConfig.getFrameworkConfig
|> get #cssFramework
theCSSFramework = ?context.frameworkConfig.cssFramework

-- | Replaces all newline characters with a @<br>@ tag. Useful for displaying preformatted text.
--
Expand All @@ -258,17 +256,10 @@ nl2br content = content
|> map (\line -> [hsx|{line}<br/>|])
|> mconcat

instance {-# OVERLAPPABLE #-} HasField "requestContext" viewContext RequestContext => FrameworkConfig.ConfigProvider viewContext where
getFrameworkConfig viewContext = viewContext
|> get #requestContext
|> get #frameworkConfig

type Html = HtmlWithContext ControllerContext

-- | The URL for the dev-mode live reload server. Typically "ws://localhost:8001"
liveReloadWebsocketUrl :: (?context :: ControllerContext) => Text
liveReloadWebsocketUrl = ?context
|> FrameworkConfig.getFrameworkConfig
|> get #ideBaseUrl
liveReloadWebsocketUrl = ?context.frameworkConfig.ideBaseUrl
|> Text.replace "http://" "ws://"
|> Text.replace "https://" "wss://"

0 comments on commit be0860d

Please sign in to comment.