Add BlockBreak.
authorJulien Moutinho <julm+hdoc@autogeree.net>
Sun, 6 May 2018 01:42:14 +0000 (03:42 +0200)
committerJulien Moutinho <julm+hdoc@autogeree.net>
Sun, 6 May 2018 01:42:14 +0000 (03:42 +0200)
Language/DTC/Anchor.hs
Language/DTC/Document.hs
Language/DTC/Sym.hs
Language/DTC/Write/HTML5.hs
Language/DTC/Write/Plain.hs
Language/DTC/Write/XML.hs
Language/TCT/Write/XML.hs
Text/Blaze/DTC.hs

index 6790f1c14024ad643507f7e520e9d62a2d9e7ca6..13f53aebca83c37af2a55ee4b49acc621d5f8592 100644 (file)
@@ -116,6 +116,7 @@ instance Anchorify BodyNode where
 instance Anchorify Block where
        anchorify = \case
         BlockPara p -> BlockPara <$> anchorify p
+        b@BlockBreak{}   -> return b
         b@BlockToC{}     -> return b
         b@BlockToF{}     -> return b
         b@BlockIndex{}   -> return b
@@ -202,7 +203,7 @@ instance Anchorify (Tree PlainNode) where
                        let (irefs,para) = indexifyWords state_section state_irefs (wordify txt)
                        S.modify $ \s -> s{state_irefs=irefs}
                        return $ Tree PlainGroup para
-                PlainBR -> return t
+                PlainBreak -> return t
                 _ -> Tree n <$> traverse anchorify ts
 
 instance Anchorify Title where
index e2541c69f30c696bb15f9aa4038cf90c8f3c759b..9635dc7d9fec97c31c1fd2147feaa5e043d4681f 100644 (file)
@@ -112,6 +112,7 @@ data BodyNode
 -- * Type 'Block'
 data Block
  = BlockPara       Para
+ | BlockBreak      { attrs    :: CommonAttrs }
  | BlockToC        { pos      :: Pos
                    , attrs    :: CommonAttrs
                    , depth    :: Maybe Nat
@@ -192,7 +193,7 @@ data PlainNode
              , to :: Ident
              } -- ^ Reference reference
  -- Leafs
- | PlainBR -- ^ Line break (\n)
+ | PlainBreak -- ^ Line break (\n)
  | PlainText TL.Text
  | PlainNote { number :: Maybe Nat1
              , note   :: [Para]
index 346ca4bc140d319bfee5c2dee7cc08efedacb41f..492ec92e4cf14418dd91cd20ea162364ab1b58c7 100644 (file)
@@ -45,6 +45,7 @@ class RNC.Sym_RNC repr => Sym_DTC repr where
        include          :: repr DTC.Include
        
        block            :: repr DTC.Block
+       blockBreak       :: repr DTC.Block
        blockToC         :: repr DTC.Block
        blockToF         :: repr DTC.Block
        blockIndex       :: repr DTC.Block
@@ -120,6 +121,7 @@ class RNC.Sym_RNC repr => Sym_DTC repr where
        block = rule "block" $
                choice
                 [ DTC.BlockPara <$> para
+                , blockBreak
                 , blockToC
                 , blockToF
                 , blockIndex
@@ -131,6 +133,10 @@ class RNC.Sym_RNC repr => Sym_DTC repr where
                                 "" -> figure n
                 -}
                 ]
+       blockBreak = rule "break" $
+               element "break" $
+               DTC.BlockBreak
+                <$> commonAttrs
        blockToC =
                rule "blockToC" $
                element "toc" $
@@ -203,16 +209,16 @@ class RNC.Sym_RNC repr => Sym_DTC repr where
                rule "plainNode" $
                choice
                 [ tree0 . DTC.PlainText <$> text
-                , element "br"   $ tree0   DTC.PlainBR   <$ none
-                , element "b"    $ Tree    DTC.PlainB    <$> plain
-                , element "code" $ Tree    DTC.PlainCode <$> plain
-                , element "del"  $ Tree    DTC.PlainDel  <$> plain
-                , element "i"    $ Tree    DTC.PlainI    <$> plain
-                , element "q"    $ Tree    DTC.PlainQ    <$> plain
-                , element "sc"   $ Tree    DTC.PlainSC   <$> plain
-                , element "sub"  $ Tree    DTC.PlainSub  <$> plain
-                , element "sup"  $ Tree    DTC.PlainSup  <$> plain
-                , element "u"    $ Tree    DTC.PlainU    <$> plain
+                , element "br"   $ tree0   DTC.PlainBreak <$ none
+                , element "b"    $ Tree    DTC.PlainB     <$> plain
+                , element "code" $ Tree    DTC.PlainCode  <$> plain
+                , element "del"  $ Tree    DTC.PlainDel   <$> plain
+                , element "i"    $ Tree    DTC.PlainI     <$> plain
+                , element "q"    $ Tree    DTC.PlainQ     <$> plain
+                , element "sc"   $ Tree    DTC.PlainSC    <$> plain
+                , element "sub"  $ Tree    DTC.PlainSub   <$> plain
+                , element "sup"  $ Tree    DTC.PlainSup   <$> plain
+                , element "u"    $ Tree    DTC.PlainU     <$> plain
                 , element "note" $ tree0 . DTC.PlainNote Nothing <$> many para
                 , element "iref" $ Tree .  DTC.PlainIref Nothing . wordify <$> attribute "to" text <*> plain
                 , element "eref" $ Tree .  DTC.PlainEref <$> attribute "to" url <*> plain
index f074487bf0ea97619608d0923f019eac2a6d73e5..b5dd5d7bbc058ed0d84480d2e3751b1742445ddd 100644 (file)
@@ -277,9 +277,10 @@ instance KeysOf (Tree BodyNode) where
                 BodyBlock b -> keys b
 instance KeysOf DTC.Block where
        keys = \case
-        BlockPara{} -> return ()
-        BlockToC{}  -> return ()
-        BlockToF{}  -> return ()
+        BlockPara{}  -> return ()
+        BlockBreak{} -> return ()
+        BlockToC{}   -> return ()
+        BlockToF{}   -> return ()
         BlockIndex{..} ->
                S.modify $ \s -> s{keys_index=
                        Map.insert pos terms $ keys_index s}
@@ -402,6 +403,11 @@ instance Html5ify [Anchor.Note] where
 instance Html5ify Block where
        html5ify = \case
         BlockPara para -> html5ify para
+        BlockBreak{..} ->
+               html5CommonAttrs attrs
+                { classes = "page-break":"print-only":classes attrs } $
+               H.div $$
+                       H.p $$ " " -- NOTE: force page break
         BlockToC{..} -> mempty -- NOTE: done in Html5ify BodyCursor
         BlockToF{..} -> do
                H.nav ! HA.class_ "tof"
@@ -605,7 +611,7 @@ instance Html5ify Plain where
 instance Html5ify (Tree PlainNode)
  where html5ify (Tree n ls) =
        case n of
-        PlainBR     -> html5ify H.br
+        PlainBreak  -> html5ify H.br
         PlainText t -> html5ify t
         PlainGroup  -> html5ify ls
         PlainB      -> H.strong $$ html5ify ls
index a00a77eac1d5d606e340871075acd1fe38ac5d5d..34b864309ef6116454804f096c30581f5231c06f 100644 (file)
@@ -90,7 +90,7 @@ instance Plainify DTC.Plain where
 instance Plainify (Tree PlainNode) where
        plainify (Tree n ls) =
                case n of
-                PlainBR       -> "\n"
+                PlainBreak    -> "\n"
                 PlainText txt -> plainify txt
                 PlainGroup    -> plainify ls
                 PlainB        -> "*"<>plainify ls<>"*"
index c24c91154f0b288b92be239037181134d5cdb232..66d85321fec7aa2236bab34604186df7b553a544 100644 (file)
@@ -61,6 +61,9 @@ instance Xmlify (Tree BodyNode) where
 instance Xmlify Block where
        xmlify = \case
         BlockPara para -> xmlify para
+        BlockBreak{..} ->
+               xmlCommonAttrs attrs $
+               XML.break
         BlockToC{..} ->
                xmlCommonAttrs attrs $
                XML.toc
@@ -115,7 +118,7 @@ instance Xmlify (Tree PlainNode) where
        xmlify (Tree n ts) =
                case n of
                 PlainText t   -> xmlify t
-                PlainBR       -> XML.br
+                PlainBreak    -> XML.br
                 PlainGroup    -> xmlify ts
                 PlainB        -> XML.b    $ xmlify ts
                 PlainCode     -> XML.code $ xmlify ts
index 5b01f4eaf33952db9d3e72aab8ebf0c4a72fd7ef..6b39dbdb56d62875f9dc81564bafca0e476b063f 100644 (file)
@@ -413,6 +413,7 @@ elems =
  , "authors"
  , "bcp14"
  , "br"
+ , "break"
  , "call"
  , "city"
  , "code"
index bf4ce6f74a2b7aae6a0870f67f8c950819ac113f..71f02b0a4a11058948f72f785e4995918fa9ea90 100644 (file)
@@ -49,6 +49,8 @@ b :: DTC -> DTC
 b = Parent "b" "<b" "</b>"
 br :: DTC
 br = Leaf "br" "<br" " />" ()
+break :: DTC
+break = Leaf "break" "<break" " />" ()
 call :: DTC -> DTC
 call = Parent "call" "<call" "</call>"
 code :: DTC -> DTC