{-# LANGUAGE OverloadedStrings     #-}
{- |
   Module      : Text.Pandoc.Readers.HTML.TagCategories
   Copyright   : Copyright (C) 2006-2021 John MacFarlane
   License     : GNU GPL, version 2 or above

   Maintainer  : John MacFarlane <jgm@berkeley.edu>
   Stability   : alpha
   Portability : portable

Categories of tags.
-}
module Text.Pandoc.Readers.HTML.TagCategories
  ( blockHtmlTags
  , blockDocBookTags
  , eitherBlockOrInline
  , epubTags
  , blockTags
  , sectioningContent
  , groupingContent
  )
where

import Data.Set (Set, fromList, unions)
import Data.Text (Text)

eitherBlockOrInline :: Set Text
eitherBlockOrInline :: Set Text
eitherBlockOrInline = [Text] -> Set Text
forall a. Ord a => [a] -> Set a
fromList
  [Text
"audio", Text
"applet", Text
"button", Text
"iframe", Text
"embed",
   Text
"del", Text
"ins", Text
"progress", Text
"map", Text
"area", Text
"noscript", Text
"script",
   Text
"object", Text
"svg", Text
"video", Text
"source"]

blockHtmlTags :: Set Text
blockHtmlTags :: Set Text
blockHtmlTags = [Text] -> Set Text
forall a. Ord a => [a] -> Set a
fromList
   [Text
"?xml", Text
"!DOCTYPE", Text
"address", Text
"article", Text
"aside",
    Text
"blockquote", Text
"body", Text
"canvas",
    Text
"caption", Text
"center", Text
"col", Text
"colgroup", Text
"dd", Text
"details",
    Text
"dir", Text
"div", Text
"dl", Text
"dt", Text
"fieldset", Text
"figcaption", Text
"figure",
    Text
"footer", Text
"form", Text
"h1", Text
"h2", Text
"h3", Text
"h4",
    Text
"h5", Text
"h6", Text
"head", Text
"header", Text
"hgroup", Text
"hr", Text
"html",
    Text
"isindex", Text
"main", Text
"menu", Text
"meta", Text
"noframes", Text
"nav",
    Text
"ol", Text
"output", Text
"p", Text
"pre",
    Text
"section", Text
"summary", Text
"table", Text
"tbody", Text
"textarea",
    Text
"thead", Text
"tfoot", Text
"ul", Text
"dd",
    Text
"dt", Text
"frameset", Text
"li", Text
"tbody", Text
"td", Text
"tfoot",
    Text
"th", Text
"thead", Text
"tr", Text
"script", Text
"style"]

-- We want to allow raw docbook in markdown documents, so we
-- include docbook block tags here too.
blockDocBookTags :: Set Text
blockDocBookTags :: Set Text
blockDocBookTags = [Text] -> Set Text
forall a. Ord a => [a] -> Set a
fromList
   [Text
"calloutlist", Text
"bibliolist", Text
"glosslist", Text
"itemizedlist",
    Text
"orderedlist", Text
"segmentedlist", Text
"simplelist",
    Text
"variablelist", Text
"caution", Text
"important", Text
"note", Text
"tip",
    Text
"warning", Text
"address", Text
"literallayout", Text
"programlisting",
    Text
"programlistingco", Text
"screen", Text
"screenco", Text
"screenshot",
    Text
"synopsis", Text
"example", Text
"informalexample", Text
"figure",
    Text
"informalfigure", Text
"table", Text
"informaltable", Text
"para",
    Text
"simpara", Text
"formalpara", Text
"equation", Text
"informalequation",
    Text
"figure", Text
"screenshot", Text
"mediaobject", Text
"qandaset",
    Text
"procedure", Text
"task", Text
"cmdsynopsis", Text
"funcsynopsis",
    Text
"classsynopsis", Text
"blockquote", Text
"epigraph", Text
"msgset",
    Text
"sidebar", Text
"title"]

epubTags :: Set Text
epubTags :: Set Text
epubTags = [Text] -> Set Text
forall a. Ord a => [a] -> Set a
fromList [Text
"case", Text
"switch", Text
"default"]

blockTags :: Set Text
blockTags :: Set Text
blockTags = [Set Text] -> Set Text
forall (f :: * -> *) a. (Foldable f, Ord a) => f (Set a) -> Set a
unions [Set Text
blockHtmlTags, Set Text
blockDocBookTags, Set Text
epubTags]

sectioningContent :: [Text]
sectioningContent :: [Text]
sectioningContent = [Text
"article", Text
"aside", Text
"nav", Text
"section"]


groupingContent :: [Text]
groupingContent :: [Text]
groupingContent = [Text
"p", Text
"hr", Text
"pre", Text
"blockquote", Text
"ol"
                  , Text
"ul", Text
"li", Text
"dl", Text
"dt", Text
"dt", Text
"dd"
                  , Text
"figure", Text
"figcaption", Text
"div", Text
"main"]