1
1
mirror of https://github.com/srid/rib.git synced 2024-11-25 08:52:09 +03:00

Bunch of refactor

This commit is contained in:
Sridhar Ratnakumar 2020-03-26 17:02:14 -04:00
parent ed18aeeb05
commit 86c75bd376
2 changed files with 39 additions and 13 deletions

View File

@ -1,6 +1,8 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
@ -9,10 +11,11 @@ module Rib.Logging
( prettyPrintPathFile,
prettyPrintPathDir,
RibSettings (..),
withRelativeFileMaybe,
withRelativeDirMaybe,
)
where
import Control.Monad.Catch
import Path
import Path.IO
import Relude
@ -26,16 +29,38 @@ data RibSettings
}
deriving (Typeable)
prettyPrintPathFile :: (MonadIO m, MonadThrow m) => RibSettings -> Path b File -> m Text
prettyPrintPathFile RibSettings {..} fp = do
fpAbs <- makeAbsolute fp
if (toFilePath _ribSettings_workingDir) `isPrefixOf` (toFilePath fpAbs)
then toText . toFilePath <$> makeRelative _ribSettings_workingDir fp
else toText . toFilePath <$> pure fp
prettyPrintPathFile :: (MonadIO m, Typeable b) => RibSettings -> Path b File -> m Text
prettyPrintPathFile s@RibSettings {..} fp = do
withRelativeFileMaybe s fp $
pure . toText . toFilePath
prettyPrintPathDir :: (MonadIO m, MonadThrow m) => RibSettings -> Path b Dir -> m Text
prettyPrintPathDir RibSettings {..} fp = do
fpAbs <- makeAbsolute fp
if (toFilePath _ribSettings_workingDir) `isPrefixOf` (toFilePath fpAbs)
then toText . toFilePath <$> makeRelative _ribSettings_workingDir fp
else toText . toFilePath <$> pure fp
prettyPrintPathDir :: (MonadIO m, Typeable b) => RibSettings -> Path b Dir -> m Text
prettyPrintPathDir s@RibSettings {..} fp = do
withRelativeDirMaybe s fp $
pure . toText . toFilePath
withRelativeFileMaybe ::
forall m b a.
(MonadIO m, Typeable b) =>
RibSettings ->
Path b File ->
(forall b1. Typeable b1 => Path b1 File -> m a) ->
m a
withRelativeFileMaybe RibSettings {..} p f = do
pAbs <- makeAbsolute p
if (toFilePath _ribSettings_workingDir) `isPrefixOf` (toFilePath pAbs)
then f =<< liftIO (makeRelative _ribSettings_workingDir p)
else f p
withRelativeDirMaybe ::
forall m b a.
(MonadIO m, Typeable b) =>
RibSettings ->
Path b Dir ->
(forall b1. Typeable b1 => Path b1 Dir -> m a) ->
m a
withRelativeDirMaybe RibSettings {..} p f = do
pAbs <- makeAbsolute p
if (toFilePath _ribSettings_workingDir) `isPrefixOf` (toFilePath pAbs)
then f =<< liftIO (makeRelative _ribSettings_workingDir p)
else f p

View File

@ -27,6 +27,7 @@ staticSiteServerSettings root =
--
-- Binds the server to host 127.0.0.1.
serve ::
Typeable b =>
RibSettings ->
-- | Port number to bind to
Int ->