reploy/Utils.hs

40 lines
1.1 KiB
Haskell

module Utils where
import Control.Monad.IO.Class
import Data.List.Extra (stripSuffix)
import Data.Maybe (isJust)
import Text.Pandoc.Definition
import qualified Text.Pandoc.Walk
import qualified Data.Text as T
import Types
-- | A shortcut for `liftIO`.
io :: MonadIO m => IO a -> m a
io = liftIO
-- | A helper for throwing an error if something is `Nothing`
just :: String -> Maybe a -> a
just _ (Just val) = val
just err Nothing = error ("Missing: " ++ err)
-- | Test for whether something listy has a suffix
hasSuffix :: Eq a => [a] -> [a] -> Bool
hasSuffix s = isJust . stripSuffix s
-- | The same second as from arrows et al.
second :: (a -> b) -> (c, a) -> (c, b)
second f (a, b) = (a, f b)
-- | A pandoc walker for printing the URLs.
walkURLs :: (FilePath -> Site FilePath) -> Text.Pandoc.Definition.Pandoc -> Site Text.Pandoc.Definition.Pandoc
walkURLs f = Text.Pandoc.Walk.walkM go
where
go (Link a i (u,t)) = do
u' <- T.pack <$> f (T.unpack u)
pure $ Link a i (u',t)
go (Image a i (u,t)) = do
u' <- T.pack <$> f (T.unpack u)
pure $ Image a i (u',t)
go x = pure x