Skip to content

Commit a2e7a33

Browse files
committed
Expose some potentially useful internal modules
1 parent 6612fcd commit a2e7a33

File tree

9 files changed

+55
-15
lines changed

9 files changed

+55
-15
lines changed

CHANGELOG.md

+5
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,8 @@
1+
## Upcoming
2+
3+
* Exposed the following modules: `Text.MMark.Internal.Type`,
4+
`Text.MMark.Render`, `Text.MMark.Trans`, `Text.MMark.Util`.
5+
16
## MMark 0.0.7.6
27

38
* The test suite now passes with `modern-uri-0.3.4.4`.

Text/MMark.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -135,9 +135,9 @@ where
135135

136136
import Control.Foldl qualified as L
137137
import Data.Aeson
138+
import Text.MMark.Internal.Type
138139
import Text.MMark.Parser (MMarkErr (..), parse)
139140
import Text.MMark.Render (render)
140-
import Text.MMark.Type
141141

142142
----------------------------------------------------------------------------
143143
-- Extensions

Text/MMark/Extension.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -105,7 +105,7 @@ where
105105
import Control.Foldl qualified as L
106106
import Data.Monoid hiding ((<>))
107107
import Lucid
108-
import Text.MMark.Type
108+
import Text.MMark.Internal.Type
109109
import Text.MMark.Util
110110

111111
-- | Create an extension that performs a transformation on 'Block's of

Text/MMark/Type.hs Text/MMark/Internal/Type.hs

+8-4
Original file line numberDiff line numberDiff line change
@@ -5,17 +5,19 @@
55
{-# LANGUAGE RecordWildCards #-}
66

77
-- |
8-
-- Module : Text.MMark.Type
8+
-- Module : Text.MMark.Internal.Type
99
-- Copyright : © 2017–present Mark Karpov
1010
-- License : BSD 3 clause
1111
--
1212
-- Maintainer : Mark Karpov <[email protected]>
1313
-- Stability : experimental
1414
-- Portability : portable
1515
--
16-
-- Internal type definitions. Some of these are re-exported in the public
17-
-- modules.
18-
module Text.MMark.Type
16+
-- Internal type definitions. The public subset of these is re-exported from
17+
-- "Text.MMark.Extension".
18+
--
19+
-- @since 0.0.8.0
20+
module Text.MMark.Internal.Type
1921
( MMark (..),
2022
Extension (..),
2123
Render (..),
@@ -116,6 +118,8 @@ instance Monoid Extension where
116118
-- | An internal type that captures the extensible rendering process we use.
117119
-- 'Render' has a function inside which transforms a rendering function of
118120
-- the type @a -> Html ()@.
121+
--
122+
-- @since 0.0.8.0
119123
newtype Render a = Render
120124
{runRender :: (a -> Html ()) -> a -> Html ()}
121125

Text/MMark/Parser.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -45,8 +45,8 @@ import Data.Text qualified as T
4545
import Data.Text.Encoding qualified as TE
4646
import Lens.Micro ((^.))
4747
import Text.Email.Validate qualified as Email
48+
import Text.MMark.Internal.Type
4849
import Text.MMark.Parser.Internal
49-
import Text.MMark.Type
5050
import Text.MMark.Util
5151
import Text.Megaparsec hiding (State (..), parse)
5252
import Text.Megaparsec.Char hiding (eol)

Text/MMark/Render.hs

+18-1
Original file line numberDiff line numberDiff line change
@@ -12,8 +12,15 @@
1212
-- Portability : portable
1313
--
1414
-- MMark rendering machinery.
15+
--
16+
-- @since 0.0.8.0
1517
module Text.MMark.Render
1618
( render,
19+
applyBlockRender,
20+
defaultBlockRender,
21+
applyInlineRender,
22+
defaultInlineRender,
23+
newline,
1724
)
1825
where
1926

@@ -25,8 +32,8 @@ import Data.List.NonEmpty (NonEmpty (..))
2532
import Data.List.NonEmpty qualified as NE
2633
import Data.Text qualified as T
2734
import Lucid
35+
import Text.MMark.Internal.Type
2836
import Text.MMark.Trans
29-
import Text.MMark.Type
3037
import Text.MMark.Util
3138
import Text.URI qualified as URI
3239

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

5259
-- | Apply a 'Render' to a given @'Block' 'Html' ()@.
60+
--
61+
-- @since 0.0.8.0
5362
applyBlockRender ::
5463
Render (Block (Ois, Html ())) ->
5564
Block (Ois, Html ()) ->
5665
Html ()
5766
applyBlockRender r = fix (runRender r . defaultBlockRender)
5867

5968
-- | The default 'Block' render.
69+
--
70+
-- @since 0.0.8.0
6071
defaultBlockRender ::
6172
-- | Rendering function to use to render sub-blocks
6273
(Block (Ois, Html ()) -> Html ()) ->
@@ -131,10 +142,14 @@ defaultBlockRender blockRender = \case
131142
CellAlignCenter -> [style_ "text-align:center"]
132143

133144
-- | Apply a render to a given 'Inline'.
145+
--
146+
-- @since 0.0.8.0
134147
applyInlineRender :: Render Inline -> Inline -> Html ()
135148
applyInlineRender r = fix (runRender r . defaultInlineRender)
136149

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

167182
-- | HTML containing a newline.
183+
--
184+
-- @since 0.0.8.0
168185
newline :: Html ()
169186
newline = "\n"

Text/MMark/Trans.hs

+7-1
Original file line numberDiff line numberDiff line change
@@ -10,16 +10,20 @@
1010
-- Portability : portable
1111
--
1212
-- MMark block\/inline transformation helpers.
13+
--
14+
-- @since 0.0.8.0
1315
module Text.MMark.Trans
1416
( applyBlockTrans,
1517
applyInlineTrans,
1618
)
1719
where
1820

1921
import Data.Monoid hiding ((<>))
20-
import Text.MMark.Type
22+
import Text.MMark.Internal.Type
2123

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

3236
-- | Apply inline transformation in the @'Endo' 'Inline'@ form to an
3337
-- 'Inline'.
38+
--
39+
-- @since 0.0.8.0
3440
applyInlineTrans :: Endo Inline -> Inline -> Inline
3541
applyInlineTrans trans@(Endo f) = \case
3642
Emphasis xs -> f (Emphasis (s xs))

Text/MMark/Util.hs

+10-2
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,9 @@
1010
-- Stability : experimental
1111
-- Portability : portable
1212
--
13-
-- Internal utilities.
13+
-- Misc utilities.
14+
--
15+
-- @since 0.0.8.0
1416
module Text.MMark.Util
1517
( asPlainText,
1618
headerId,
@@ -22,12 +24,14 @@ import Data.Char (isAlphaNum, isSpace)
2224
import Data.List.NonEmpty (NonEmpty (..))
2325
import Data.Text (Text)
2426
import Data.Text qualified as T
25-
import Text.MMark.Type
27+
import Text.MMark.Internal.Type
2628
import Text.URI (URI (..))
2729
import Text.URI qualified as URI
2830

2931
-- | Convert a non-empty collection of 'Inline's into their plain text
3032
-- representation. This is used e.g. to render image descriptions.
33+
--
34+
-- @since 0.0.8.0
3135
asPlainText :: NonEmpty Inline -> Text
3236
asPlainText = foldMap $ \case
3337
Plain txt -> txt
@@ -46,6 +50,8 @@ asPlainText = foldMap $ \case
4650
-- extensions.
4751
--
4852
-- See also: 'headerFragment'.
53+
--
54+
-- @since 0.0.8.0
4955
headerId :: NonEmpty Inline -> Text
5056
headerId =
5157
T.intercalate "-"
@@ -56,6 +62,8 @@ headerId =
5662

5763
-- | Generate a 'URI' containing only a fragment from its textual
5864
-- representation. Useful for getting URL from id of a header.
65+
--
66+
-- @since 0.0.8.0
5967
headerFragment :: Text -> URI
6068
headerFragment fragment =
6169
URI

mmark.cabal

+4-4
Original file line numberDiff line numberDiff line change
@@ -33,15 +33,15 @@ library
3333
exposed-modules:
3434
Text.MMark
3535
Text.MMark.Extension
36+
Text.MMark.Internal.Type
37+
Text.MMark.Render
38+
Text.MMark.Trans
39+
Text.MMark.Util
3640

3741
other-modules:
3842
Text.MMark.Parser
3943
Text.MMark.Parser.Internal
4044
Text.MMark.Parser.Internal.Type
41-
Text.MMark.Render
42-
Text.MMark.Trans
43-
Text.MMark.Type
44-
Text.MMark.Util
4545

4646
default-language: GHC2021
4747
build-depends:

0 commit comments

Comments
 (0)