1
1
mirror of https://github.com/srid/ema.git synced 2024-11-22 04:13:06 +03:00

Run treefmt

This commit is contained in:
Sridhar Ratnakumar 2023-11-25 12:17:43 -05:00 committed by Sridhar Ratnakumar
parent 3c96f445eb
commit d8c9da9b99
12 changed files with 17 additions and 17 deletions

View File

@ -114,7 +114,7 @@ instance EmaSite Route where
liftIO (eitherDecodeFileStrict' $ dataDir </> "store.json") >>= \case
Left err -> liftIO $ throwIO $ StoreFileMalformed err
Right store -> pure store
log :: MonadLogger m => Text -> m ()
log :: (MonadLogger m) => Text -> m ()
log = logInfoNS "Ex03_Store"
siteOutput rp (Model storeName ps cats) r =
pure . Ema.AssetGenerated Ema.Html $

View File

@ -47,7 +47,7 @@ instance (IsRoute r, IsString k, ToString k, Ord k, Show r) => IsRoute (MapRoute
)
where
-- Breaks a path once on the first slash.
breakPath :: HasCallStack => String -> (String, Maybe [Char])
breakPath :: (HasCallStack) => String -> (String, Maybe [Char])
breakPath (s :: String) =
case T.breakOn "/" (toText s) of
(p, "") -> (toString p, Nothing)

View File

@ -50,14 +50,14 @@ fromNum n = do
pure $ fromInteger . toInteger $ n - 1
-- | Enumerate list of all pages given the total number of pages.
pageRange :: forall a. HasCallStack => Int -> NonEmpty (Page a)
pageRange :: forall a. (HasCallStack) => Int -> NonEmpty (Page a)
pageRange total =
fromMaybe (error "pageRange: total must be positive and non-zero") $ do
end <- fromNum @a total
nonEmpty [def .. end]
-- | Retrieve the given page from the list.
lookupPage :: HasCallStack => Page a -> NonEmpty [a] -> [a]
lookupPage :: (HasCallStack) => Page a -> NonEmpty [a] -> [a]
lookupPage r xs =
fromMaybe (error outOfBoundsError) $ lookupPage' r xs
where

View File

@ -79,7 +79,7 @@ lookupPandocRoute model r = do
let render = PandocHtml . renderHtml (argWriterOpts $ modelArg model)
pure (pandoc, render)
where
renderHtml :: HasCallStack => Pandoc.WriterOptions -> Pandoc -> Text
renderHtml :: (HasCallStack) => Pandoc.WriterOptions -> Pandoc -> Text
renderHtml writerSettings pandoc =
either (throw . PandocError_RenderError . show) id $
Pandoc.runPure $
@ -155,7 +155,7 @@ pandocFilesDyn baseDir formats readerOpts = do
Right doc -> do
pure (r, doc)
log :: MonadLogger m => Text -> m ()
log :: (MonadLogger m) => Text -> m ()
log = logInfoNS "PandocRoute"
data PandocError

View File

@ -47,7 +47,7 @@ instance IsRoute (StaticRoute baseDir) where
routeUniverse (modelFiles -> files) =
StaticRoute <$> Map.keys files
instance KnownSymbol baseDir => EmaSite (StaticRoute baseDir) where
instance (KnownSymbol baseDir) => EmaSite (StaticRoute baseDir) where
siteInput cliAct _ = do
files <- staticFilesDynamic $ symbolVal (Proxy @baseDir)
pure $ Model cliAct <$> files

View File

@ -16,7 +16,7 @@ import Generics.SOP (I (..), NP (Nil, (:*)))
import Optics.Core (united, view)
import Prelude hiding (All)
class HasSubRoutes r => HasSubModels r where
class (HasSubRoutes r) => HasSubModels r where
-- | Break the model into a list of sub-models used correspondingly by the sub-routes.
subModels :: RouteModel r -> NP I (MultiModel (SubRoutes r))
@ -38,5 +38,5 @@ instance
instance {-# OVERLAPPING #-} HasAny () s s () () where
the = united
instance HasAny sel s t a b => HasAny (Proxy sel) s t a b where
instance (HasAny sel s t a b) => HasAny (Proxy sel) s t a b where
the = the @sel

View File

@ -28,7 +28,7 @@ import System.Directory (copyFile, createDirectoryIfMissing, doesDirectoryExist,
import System.FilePath (takeDirectory, (</>))
import System.FilePattern.Directory (getDirectoryFiles)
log :: MonadLogger m => LogLevel -> Text -> m ()
log :: (MonadLogger m) => LogLevel -> Text -> m ()
log = logWithoutLoc "ema.generate"
{- | Generate the static site at `dest`

View File

@ -18,7 +18,7 @@ import Optics.Core (coercedTo, only, (%))
newtype FileRoute (filename :: Symbol) = FileRoute ()
deriving stock (Eq, Ord, Show, Generic)
instance KnownSymbol fn => IsRoute (FileRoute fn) where
instance (KnownSymbol fn) => IsRoute (FileRoute fn) where
type RouteModel (FileRoute fn) = ()
routePrism () =
toPrism_ $

View File

@ -34,7 +34,7 @@ instance (EmaStaticSite r, KnownSymbol prefix) => EmaSite (FolderRoute prefix r)
-- | Prefix the encoding of the given route prism.
prefixRoutePrism ::
forall prefix r.
KnownSymbol prefix =>
(KnownSymbol prefix) =>
(RouteModel r -> Prism_ FilePath r) ->
(RouteModel r -> Prism_ FilePath (FolderRoute prefix r))
prefixRoutePrism =

View File

@ -20,7 +20,7 @@ import Optics.Core (Prism', review)
site's base URL or path (typically just `/`). Otherwise you must accordingly
make these URLs absolute yourself.
-}
routeUrlWith :: HasCallStack => UrlStrategy -> Prism' FilePath r -> r -> Text
routeUrlWith :: (HasCallStack) => UrlStrategy -> Prism' FilePath r -> r -> Text
routeUrlWith urlStrategy rp =
relUrlFromPath . review rp
where
@ -36,7 +36,7 @@ routeUrlWith urlStrategy rp =
Nothing ->
T.intercalate "/" $ filepathToUrl fp
where
removeLastIfOneOf :: Eq a => [a] -> NonEmpty a -> [a]
removeLastIfOneOf :: (Eq a) => [a] -> NonEmpty a -> [a]
removeLastIfOneOf x xs =
if last xs `elem` x
then init xs
@ -54,7 +54,7 @@ urlToFilePath =
toString . T.intercalate "/" . fmap (Slug.unSlug . Slug.decodeSlug) . T.splitOn "/"
-- | Like `routeUrlWith` but uses @UrlDirect@ strategy
routeUrl :: HasCallStack => Prism' FilePath r -> r -> Text
routeUrl :: (HasCallStack) => Prism' FilePath r -> r -> Text
routeUrl =
routeUrlWith UrlDirect

View File

@ -202,7 +202,7 @@ data BadRouteEncoding r = BadRouteEncoding
}
deriving stock (Show)
badRouteEncodingMsg :: Show r => BadRouteEncoding r -> Text
badRouteEncodingMsg :: (Show r) => BadRouteEncoding r -> Text
badRouteEncodingMsg BadRouteEncoding {..} =
toText $
"A route Prism' is unlawful.\n\nThe URL '"

View File

@ -33,7 +33,7 @@ import UnliftIO (MonadUnliftIO)
Finally, `Ema.App.runSite @r arg` (where `arg` is of type `SiteArg`) is run
from the `main` entry point to run your Ema site.
-}
class IsRoute r => EmaSite r where
class (IsRoute r) => EmaSite r where
-- | `SiteArg` is typically settings from the environment (config file, or
-- command-line arguments) that your Dynamic-producing `siteInput` function
-- consumes as argument.