Skip to content

Commit

Permalink
Expose some potentially useful internal modules
Browse files Browse the repository at this point in the history
  • Loading branch information
mrkkrp committed Jul 8, 2024
1 parent 6612fcd commit a2e7a33
Show file tree
Hide file tree
Showing 9 changed files with 55 additions and 15 deletions.
5 changes: 5 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,8 @@
## Upcoming

* Exposed the following modules: `Text.MMark.Internal.Type`,
`Text.MMark.Render`, `Text.MMark.Trans`, `Text.MMark.Util`.

## MMark 0.0.7.6

* The test suite now passes with `modern-uri-0.3.4.4`.
Expand Down
2 changes: 1 addition & 1 deletion Text/MMark.hs
Original file line number Diff line number Diff line change
Expand Up @@ -135,9 +135,9 @@ where

import Control.Foldl qualified as L
import Data.Aeson
import Text.MMark.Internal.Type
import Text.MMark.Parser (MMarkErr (..), parse)
import Text.MMark.Render (render)
import Text.MMark.Type

----------------------------------------------------------------------------
-- Extensions
Expand Down
2 changes: 1 addition & 1 deletion Text/MMark/Extension.hs
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,7 @@ where
import Control.Foldl qualified as L
import Data.Monoid hiding ((<>))
import Lucid
import Text.MMark.Type
import Text.MMark.Internal.Type
import Text.MMark.Util

-- | Create an extension that performs a transformation on 'Block's of
Expand Down
12 changes: 8 additions & 4 deletions Text/MMark/Type.hs → Text/MMark/Internal/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,17 +5,19 @@
{-# LANGUAGE RecordWildCards #-}

-- |
-- Module : Text.MMark.Type
-- Module : Text.MMark.Internal.Type
-- Copyright : © 2017–present Mark Karpov
-- License : BSD 3 clause
--
-- Maintainer : Mark Karpov <[email protected]>
-- Stability : experimental
-- Portability : portable
--
-- Internal type definitions. Some of these are re-exported in the public
-- modules.
module Text.MMark.Type
-- Internal type definitions. The public subset of these is re-exported from
-- "Text.MMark.Extension".
--
-- @since 0.0.8.0
module Text.MMark.Internal.Type
( MMark (..),
Extension (..),
Render (..),
Expand Down Expand Up @@ -116,6 +118,8 @@ instance Monoid Extension where
-- | An internal type that captures the extensible rendering process we use.
-- 'Render' has a function inside which transforms a rendering function of
-- the type @a -> Html ()@.
--
-- @since 0.0.8.0
newtype Render a = Render
{runRender :: (a -> Html ()) -> a -> Html ()}

Expand Down
2 changes: 1 addition & 1 deletion Text/MMark/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,8 +45,8 @@ import Data.Text qualified as T
import Data.Text.Encoding qualified as TE
import Lens.Micro ((^.))
import Text.Email.Validate qualified as Email
import Text.MMark.Internal.Type
import Text.MMark.Parser.Internal
import Text.MMark.Type
import Text.MMark.Util
import Text.Megaparsec hiding (State (..), parse)
import Text.Megaparsec.Char hiding (eol)
Expand Down
19 changes: 18 additions & 1 deletion Text/MMark/Render.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,15 @@
-- Portability : portable
--
-- MMark rendering machinery.
--
-- @since 0.0.8.0
module Text.MMark.Render
( render,
applyBlockRender,
defaultBlockRender,
applyInlineRender,
defaultInlineRender,
newline,
)
where

Expand All @@ -25,8 +32,8 @@ import Data.List.NonEmpty (NonEmpty (..))
import Data.List.NonEmpty qualified as NE
import Data.Text qualified as T
import Lucid
import Text.MMark.Internal.Type
import Text.MMark.Trans
import Text.MMark.Type
import Text.MMark.Util
import Text.URI qualified as URI

Expand All @@ -50,13 +57,17 @@ render MMark {..} =
. fmap (applyInlineTrans extInlineTrans)

-- | Apply a 'Render' to a given @'Block' 'Html' ()@.
--
-- @since 0.0.8.0
applyBlockRender ::
Render (Block (Ois, Html ())) ->
Block (Ois, Html ()) ->
Html ()
applyBlockRender r = fix (runRender r . defaultBlockRender)

-- | The default 'Block' render.
--
-- @since 0.0.8.0
defaultBlockRender ::
-- | Rendering function to use to render sub-blocks
(Block (Ois, Html ()) -> Html ()) ->
Expand Down Expand Up @@ -131,10 +142,14 @@ defaultBlockRender blockRender = \case
CellAlignCenter -> [style_ "text-align:center"]

-- | Apply a render to a given 'Inline'.
--
-- @since 0.0.8.0
applyInlineRender :: Render Inline -> Inline -> Html ()
applyInlineRender r = fix (runRender r . defaultInlineRender)

-- | The default render for 'Inline' elements.
--
-- @since 0.0.8.0
defaultInlineRender ::
-- | Rendering function to use to render sub-inlines
(Inline -> Html ()) ->
Expand Down Expand Up @@ -165,5 +180,7 @@ defaultInlineRender inlineRender = \case
in img_ (alt_ (asPlainText desc) : src_ (URI.render src) : title)

-- | HTML containing a newline.
--
-- @since 0.0.8.0
newline :: Html ()
newline = "\n"
8 changes: 7 additions & 1 deletion Text/MMark/Trans.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,16 +10,20 @@
-- Portability : portable
--
-- MMark block\/inline transformation helpers.
--
-- @since 0.0.8.0
module Text.MMark.Trans
( applyBlockTrans,
applyInlineTrans,
)
where

import Data.Monoid hiding ((<>))
import Text.MMark.Type
import Text.MMark.Internal.Type

-- | Apply block transformation in the @'Endo' 'Bni'@ form to a block 'Bni'.
--
-- @since 0.0.8.0
applyBlockTrans :: Endo Bni -> Bni -> Bni
applyBlockTrans trans@(Endo f) = \case
Blockquote xs -> f (Blockquote (s xs))
Expand All @@ -31,6 +35,8 @@ applyBlockTrans trans@(Endo f) = \case

-- | Apply inline transformation in the @'Endo' 'Inline'@ form to an
-- 'Inline'.
--
-- @since 0.0.8.0
applyInlineTrans :: Endo Inline -> Inline -> Inline
applyInlineTrans trans@(Endo f) = \case
Emphasis xs -> f (Emphasis (s xs))
Expand Down
12 changes: 10 additions & 2 deletions Text/MMark/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,9 @@
-- Stability : experimental
-- Portability : portable
--
-- Internal utilities.
-- Misc utilities.
--
-- @since 0.0.8.0
module Text.MMark.Util
( asPlainText,
headerId,
Expand All @@ -22,12 +24,14 @@ import Data.Char (isAlphaNum, isSpace)
import Data.List.NonEmpty (NonEmpty (..))
import Data.Text (Text)
import Data.Text qualified as T
import Text.MMark.Type
import Text.MMark.Internal.Type
import Text.URI (URI (..))
import Text.URI qualified as URI

-- | Convert a non-empty collection of 'Inline's into their plain text
-- representation. This is used e.g. to render image descriptions.
--
-- @since 0.0.8.0
asPlainText :: NonEmpty Inline -> Text
asPlainText = foldMap $ \case
Plain txt -> txt
Expand All @@ -46,6 +50,8 @@ asPlainText = foldMap $ \case
-- extensions.
--
-- See also: 'headerFragment'.
--
-- @since 0.0.8.0
headerId :: NonEmpty Inline -> Text
headerId =
T.intercalate "-"
Expand All @@ -56,6 +62,8 @@ headerId =

-- | Generate a 'URI' containing only a fragment from its textual
-- representation. Useful for getting URL from id of a header.
--
-- @since 0.0.8.0
headerFragment :: Text -> URI
headerFragment fragment =
URI
Expand Down
8 changes: 4 additions & 4 deletions mmark.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -33,15 +33,15 @@ library
exposed-modules:
Text.MMark
Text.MMark.Extension
Text.MMark.Internal.Type
Text.MMark.Render
Text.MMark.Trans
Text.MMark.Util

other-modules:
Text.MMark.Parser
Text.MMark.Parser.Internal
Text.MMark.Parser.Internal.Type
Text.MMark.Render
Text.MMark.Trans
Text.MMark.Type
Text.MMark.Util

default-language: GHC2021
build-depends:
Expand Down

0 comments on commit a2e7a33

Please sign in to comment.