" + innerText + "
" |> Some }
+ |> applyFormatter
+
+let private paragraph =
+ { TagName = "para"
+ Formatter =
+ function
+ | VoidElement _ -> None
+
+ | NonVoidElement(innerText, _) -> "" + innerText + "
" |> Some } + |> applyFormatter + +let private block = + { TagName = "block" + Formatter = + function + | VoidElement _ -> None + + | NonVoidElement(innerText, _) -> newLine + innerText + newLine |> Some } + |> applyFormatter + +let private see = + let getCRef (attributes: Map" + extractMemberText cref + "
" |> Some
+
+ | None -> None
+
+ | NonVoidElement(innerText, attributes) ->
+ if String.IsNullOrWhiteSpace innerText then
+ match getCRef attributes with
+ | Some cref ->
+ // TODO: Add config to generates command
+ "" + extractMemberText cref + "
" |> Some
+
+ | None -> None
+ else
+ match getHref attributes with
+ | Some href -> sprintf "[%s](%s)" innerText href |> Some
+
+ | None -> "" + innerText + "
" |> Some }
+ |> applyFormatter
+
+let private paramRef =
+ let getName (attributes: Map" + name + "
" |> Some
+
+ | None -> None
+
+ | NonVoidElement(innerText, attributes) -> None
+
+ }
+ |> applyFormatter
+
+let private typeParamRef =
+ let getName (attributes: Map" + name + "
" |> Some
+
+ | None -> None
+
+ | NonVoidElement(innerText, attributes) -> None }
+ |> applyFormatter
+
+type private Term = string
+type private Definition = string
+
+type private ListStyle =
+ | Bulleted
+ | Numbered
+ | Tablered
+
+/// ItemList allow a permissive representation of an Item.
+/// In theory, TermOnly should not exist but we added it so part of the documentation doesn't disappear
+/// TODO: Allow direct text support without Example
""" + + newLine + + innerText + + newLine + + " tags
+ |> see
+ |> paramRef
+ |> typeParamRef
+ |> list
+ |> unescapeSpecialCharacters
+ |> Markdown.ToHtml
+
+///
+/// Extract and format only the summary tag
+///
+///
+///
+let formatSummaryOnly (text: string) =
+ let pattern = tagPattern "summary"
+
+ // Match all the param tags
+ match Regex.Match(text, pattern, RegexOptions.IgnoreCase) with
+ | m when m.Success ->
+ if m.Groups.["void_element"].Success then
+ ""
+ else if m.Groups.["non_void_element"].Success then
+ m.Groups.["non_void_innerText"].Value |> format
+
+ else
+ // Should not happen but we are forced to handle it by F# compiler
+ ""
+
+ | _ -> ""
+
+///
+/// Try to extract a specific param tag and format
+///
+///
+/// Return the formatted param tag doc if found.
+///
+/// Otherwise, it returns None
+///
+let tryFormatParam (parameterName: string) (text: string) =
+ let pattern = tagPattern "param"
+
+ // Match all the param tags
+ Regex.Matches(text, pattern, RegexOptions.IgnoreCase)
+ // Try find the param tag that has name attribute equal to the parameterName
+ |> Seq.tryFind (fun m ->
+ if m.Groups.["void_element"].Success then
+ false
+ else if m.Groups.["non_void_element"].Success then
+ let attributes = getAttributes m.Groups.["non_void_attributes"]
+
+ match Map.tryFind "name" attributes with
+ | Some name -> name = parameterName
+
+ | None -> false
+ else
+ // Should not happen but we are forced to handle it by F# compiler
+ false)
+ // Extract the inner text of the param tag
+ |> Option.map (fun m -> m.Groups.["non_void_innerText"].Value |> format)
+
+let tryFormatReturnsOnly (text: string) =
+ let pattern = tagPattern "returns"
+
+ match Regex.Match(text, pattern, RegexOptions.IgnoreCase) with
+ | m when m.Success ->
+ if m.Groups.["void_element"].Success then
+ None
+ else if m.Groups.["non_void_element"].Success then
+ m.Groups.["non_void_innerText"].Value |> format |> Some
+
+ else
+ // Should not happen but we are forced to handle it by F# compiler
+ None
+
+ | _ -> None
diff --git a/src/FSharp.Formatting.ApiDocs/FSharp.Formatting.ApiDocs.fsproj b/src/FSharp.Formatting.ApiDocs/FSharp.Formatting.ApiDocs.fsproj
index 1255480c..b3ae7573 100644
--- a/src/FSharp.Formatting.ApiDocs/FSharp.Formatting.ApiDocs.fsproj
+++ b/src/FSharp.Formatting.ApiDocs/FSharp.Formatting.ApiDocs.fsproj
@@ -10,8 +10,11 @@
Common\StringParsing.fs
+
+
+
diff --git a/src/FSharp.Formatting.ApiDocs/GenerateHtml.fs b/src/FSharp.Formatting.ApiDocs/GenerateHtml.fs
index a6067d23..ab002d80 100644
--- a/src/FSharp.Formatting.ApiDocs/GenerateHtml.fs
+++ b/src/FSharp.Formatting.ApiDocs/GenerateHtml.fs
@@ -9,6 +9,9 @@ open FSharp.Compiler.Symbols
open FSharp.Formatting.Templating
open FSharp.Formatting.HtmlModel
open FSharp.Formatting.HtmlModel.Html
+open System.Xml.Linq
+open System.Text.RegularExpressions
+open FSharp.Formatting.ApiDocs.GenerateSignature
/// Embed some HTML generated in GenerateModel
let embed (x: ApiDocHtml) = !!x.HtmlText
@@ -20,6 +23,36 @@ let fsdocsSummary (x: ApiDocHtml) =
else
div [ Class "fsdocs-summary-contents" ] [ p [ Class "fsdocs-summary" ] [ embed x ] ]
+let formatXmlComment (commentOpt: XElement option) : string =
+
+ match commentOpt with
+ | Some comment ->
+ let docComment = comment.ToString()
+
+ let pattern = $"""((?'xml_doc'(?:(?!)(?!<\/member>)[\s\S])*)<\/member\s*>)"""
+
+ let m = Regex.Match(docComment, pattern)
+
+ // Remove the and tags
+ if m.Success then
+ let xmlDoc = m.Groups.["xml_doc"].Value
+
+ let lines = xmlDoc |> String.splitLines |> Array.toList
+
+ // Remove the non meaning full indentation
+ let content =
+ lines
+ |> List.map (fun line ->
+ // Add a small protection in case the user didn't align all it's tags
+ if line.StartsWith(" ") then line.Substring(1) else line)
+ |> String.concat "\n"
+
+ CommentFormatter.format content
+ else
+ CommentFormatter.format docComment
+
+ | None -> ""
+
type HtmlRender(model: ApiDocModel, ?menuTemplateFolder: string) =
let root = model.Root
let collectionName = model.Collection.CollectionName
@@ -101,6 +134,151 @@ type HtmlRender(model: ApiDocModel, ?menuTemplateFolder: string) =
| :? FSharpEntity as v -> copyXmlSigIconMarkdown (removeParen v.XmlDocSig)
| _ -> () ]
+ let renderValueOrFunctions (entities: ApiDocMember list) =
+
+ if entities.IsEmpty then
+ []
+ else
+
+ [ h3 [] [ !! "Functions and values" ]
+
+ for entity in entities do
+ let (ApiDocMemberDetails(usageHtml,
+ paramTypes,
+ returnType,
+ modifiers,
+ typars,
+ baseType,
+ location,
+ compiledName)) =
+ entity.Details
+
+ let returnHtml =
+ // TODO: Parse the return type information from
+ // let x = entity.Symbol :?> FSharpMemberOrFunctionOrValue
+ // x.FullType <-- Here we have access to all the type including the argument for the function that we should ignore... (making the processing complex)
+ // For now, we are just using returnType.HtmlText to have something ready as parsing from
+ // FSharpMemberOrFunctionOrValue seems to be quite complex
+ match returnType with
+ | Some(_, returnType) ->
+ // Remove the starting and ending
+ returnType.HtmlText.[6 .. returnType.HtmlText.Length - 8]
+ // Adapt the text to have basic syntax highlighting
+ |> fun text -> text.Replace("<", Html.lessThan.ToMinifiedHtml())
+ |> fun text -> text.Replace(">", Html.greaterThan.ToMinifiedHtml())
+ |> fun text -> text.Replace(",", Html.comma.ToMinifiedHtml())
+
+ | None -> "unit"
+
+ let initial = Signature.ParamTypesInformation.Init entity.Name
+
+ let paramTypesInfo = Signature.extractParamTypesInformation initial paramTypes
+
+ div [ Class "fsdocs-block" ] [
+
+ div [ Class "actions-buttons" ] [
+ yield! sourceLink entity.SourceLocation
+ yield! copyXmlSigIconForSymbol entity.Symbol
+ yield! copyXmlSigIconForSymbolMarkdown entity.Symbol
+ ]
+
+ // This is a value
+ if paramTypesInfo.Infos.IsEmpty then
+ div [ Class "fsdocs-api-code" ] [
+ div [] [ Html.val'; Html.space; !!entity.Name; Html.space; Html.colon; !!returnHtml ]
+ ]
+
+ // This is a function
+ else
+
+ div [ Class "fsdocs-api-code" ] [
+ [ TextNode.Div [
+ TextNode.Keyword "val"
+ TextNode.Space
+ TextNode.AnchorWithId($"#{entity.Name}", entity.Name, entity.Name)
+ TextNode.Space
+ TextNode.Colon
+ ] ]
+ |> TextNode.Node
+ |> TextNode.ToHtmlElement
+
+ for index in 0 .. paramTypesInfo.Infos.Length - 1 do
+ let (name, returnType) = paramTypesInfo.Infos.[index]
+
+ div [] [
+ Html.spaces 4 // Equivalent to 'val '
+ !!name
+ Html.spaces (paramTypesInfo.MaxNameLength - name.Length + 1) // Complete with space to align ':'
+ Html.colon
+ Html.space
+ !! returnType.HtmlElement.ToMinifiedHtml()
+
+ Html.spaces (paramTypesInfo.MaxReturnTypeLength - returnType.Length + 1) // Complete with space to align '->'
+
+ // Don't add the arrow for the last parameter
+ if index <> paramTypesInfo.Infos.Length - 1 then
+ Html.arrow
+ ]
+ |> Html.minify
+
+ div [] [
+ Html.spaces (4 + paramTypesInfo.MaxNameLength + 1) // Equivalent to 'val ' + the max length of parameter name + ':'
+ Html.arrow
+ Html.space
+ !!returnHtml
+ ]
+ |> Html.minify
+ ]
+
+ match entity.Comment.Xml with
+ | Some xmlComment ->
+ let comment = xmlComment.ToString()
+ !!(CommentFormatter.formatSummaryOnly comment)
+
+ if not paramTypesInfo.Infos.IsEmpty then
+ p [] [ strong [] [ !! "Parameters" ] ]
+
+
+ for (name, returnType) in paramTypesInfo.Infos do
+ let paramDoc =
+ CommentFormatter.tryFormatParam name comment
+ |> Option.map (fun paramDoc -> !!paramDoc)
+ |> Option.defaultValue Html.nothing
+
+ div [ Class "fsdocs-doc-parameter" ] [
+ [ TextNode.DivWithClass(
+ "fsdocs-api-code",
+ [ TextNode.Property name
+ TextNode.Space
+ TextNode.Colon
+ TextNode.Space
+ returnType ]
+ ) ]
+ |> TextNode.Node
+ |> TextNode.ToHtmlElement
+
+ paramDoc
+ ]
+
+ match CommentFormatter.tryFormatReturnsOnly comment with
+ | Some returnDoc ->
+ p [] [ strong [] [ !! "Returns" ] ]
+
+ !!returnDoc
+
+ | None -> ()
+
+ // TODO: Should we r``ender a minimal documentation here with the information we have?
+ // For example, we can render the list of parameters and the return type
+ // This is to make the documentation more consistent
+ // However, these minimal information will be rondontant with the information displayed in the signature
+ | None -> ()
+ ]
+
+ // hr []
+
+ ]
+
let renderMembers header tableHeader (members: ApiDocMember list) =
[ if members.Length > 0 then
h3 [] [ !!header ]
@@ -330,7 +508,9 @@ type HtmlRender(model: ApiDocModel, ?menuTemplateFolder: string) =
]
td [ Class "fsdocs-entity-xmldoc" ] [
div [] [
- fsdocsSummary e.Comment.Summary
+
+ div [ Class "fsdocs-summary-contents" ] [ !!(formatXmlComment e.Comment.Xml) ]
+
div [ Class "icon-button-row" ] [
yield! sourceLink e.SourceLocation
yield! copyXmlSigIconForSymbol e.Symbol
@@ -481,7 +661,7 @@ type HtmlRender(model: ApiDocModel, ?menuTemplateFolder: string) =
let constructors = ms |> List.filter (fun m -> m.Kind = ApiDocMemberKind.Constructor)
let instanceMembers = ms |> List.filter (fun m -> m.Kind = ApiDocMemberKind.InstanceMember)
let staticMembers = ms |> List.filter (fun m -> m.Kind = ApiDocMemberKind.StaticMember)
- div [] (renderMembers "Functions and values" "Function or value" functionsOrValues)
+ div [] (renderValueOrFunctions functionsOrValues)
div [] (renderMembers "Type extensions" "Type extension" extensions)
div [] (renderMembers "Active patterns" "Active pattern" activePatterns)
div [] (renderMembers "Union cases" "Union case" unionCases)
diff --git a/src/FSharp.Formatting.ApiDocs/GenerateSignature.fs b/src/FSharp.Formatting.ApiDocs/GenerateSignature.fs
new file mode 100644
index 00000000..3d53d818
--- /dev/null
+++ b/src/FSharp.Formatting.ApiDocs/GenerateSignature.fs
@@ -0,0 +1,320 @@
+module internal FSharp.Formatting.ApiDocs.GenerateSignature
+
+open System
+open System.Collections.Generic
+open System.IO
+open System.Web
+open FSharp.Formatting.Common
+open FSharp.Compiler.Symbols
+open FSharp.Formatting.Templating
+open FSharp.Formatting.HtmlModel
+open FSharp.Formatting.HtmlModel.Html
+open System.Xml.Linq
+open System.Text.RegularExpressions
+
+///
+/// Type used to represent a text node.
+///
+/// This is mostly used to render API signature while also being able to compute the length of the text
+/// in term of characters to align the signature.
+///
+[]
+type TextNode =
+ | Text of string
+ | Anchor of url: string * label: string
+ | AnchorWithId of url: string * id: string * label: string
+ | Space
+ | Dot
+ | Comma
+ | Arrow
+ | GreaterThan
+ | Colon
+ | LessThan
+ | LeftParent
+ | RightParent
+ | Equal
+ | Tick
+ | Node of TextNode list
+ | Keyword of string
+ | NewLine
+ | Spaces of int
+ | Div of TextNode list
+ | DivWithClass of string * TextNode list
+ | Property of string
+ | Paragraph of TextNode list
+
+ static member ToHtmlElement(node: TextNode) : HtmlElement = node.HtmlElement
+
+ member this.HtmlElement: HtmlElement =
+ match this with
+ | Text s -> !!s
+ | Colon -> Html.colon
+ | Anchor(url, text) -> a [ Href url ] [ !!text ]
+ | AnchorWithId(url, id, text) -> a [ Href url; Id id ] [ !!text ]
+ | Keyword text -> Html.keyword text
+ | Property text -> Html.property text
+ | Div nodes -> div [] (nodes |> List.map (fun node -> node.HtmlElement))
+ | DivWithClass(cls, nodes) -> div [ Class cls ] (nodes |> List.map (fun node -> node.HtmlElement))
+ | Paragraph nodes -> p [] (nodes |> List.map (fun node -> node.HtmlElement))
+ | Spaces n ->
+ [ for _ in 0..n do
+ Space ]
+ |> Node
+ |> TextNode.ToHtmlElement
+ | NewLine -> !! "\n" // Should it be
instead?
+ | Arrow -> Html.arrow
+ | Dot -> Html.dot
+ | Comma -> Html.comma
+ | Space -> Html.space
+ | GreaterThan -> Html.greaterThan
+ | LessThan -> Html.lessThan
+ | Equal -> Html.keyword "="
+ | Tick -> !! "'"
+ | LeftParent -> Html.leftParent
+ | RightParent -> Html.rightParent
+ | Node node ->
+ // TODO: Can we have something similar to fragments in React?
+ let elements = span [] (node |> List.map (fun node -> node.HtmlElement))
+
+ !! elements.ToMinifiedHtml()
+
+ member this.Length =
+ match this with
+ | NewLine -> 0
+ // 1 character
+ | Comma
+ | Colon
+ | Dot
+ | Space
+ | GreaterThan
+ | LessThan
+ | LeftParent
+ | RightParent
+ | Equal
+ | Tick -> 1
+ // 2 characters
+ | Anchor(_, text)
+ | AnchorWithId(_, _, text)
+ | Keyword text
+ | Property text -> text.Length
+ | Arrow -> 2
+ // X characters
+ | Text s -> s.Length
+ | Spaces count -> count
+ // Sum of children
+ | Node nodes
+ | Div nodes
+ | DivWithClass(_, nodes)
+ | Paragraph nodes -> nodes |> List.map (fun node -> node.Length) |> List.sum
+
+[]
+module Signature =
+
+ ///
+ /// Generate a list of generic parameters
+ ///
+ /// 'T, 'T2, 'MyType
+ ///
+ ///
+ ///
+ ///
+ let renderGenericParameters (parameters: IList) : TextNode =
+ [ for index in 0 .. parameters.Count - 1 do
+ let param = parameters.[index]
+
+ if index <> 0 then
+ TextNode.Comma
+ TextNode.Space
+
+ TextNode.Tick
+ TextNode.Text param.DisplayName ]
+ |> TextNode.Node
+
+ let rec renderParameterType (isTopLevel: bool) (typ: FSharpType) : TextNode =
+ // This correspond to a generic paramter like: 'T
+ if typ.IsGenericParameter then
+ TextNode.Node [ TextNode.Tick; TextNode.Text typ.GenericParameter.DisplayName ]
+ // Not a generic type we can display it as it is
+ // Example:
+ // - string
+ // - int
+ // - MyObject
+ else if typ.GenericArguments.Count = 0 then
+ TextNode.Text typ.TypeDefinition.DisplayName
+
+ // This is a generic type we need more logic
+ else if
+ // This is a function, we need to generate something like:
+ // - 'T -> string
+ // - 'T -> 'T option
+ typ.IsFunctionType
+ then
+ let separator = TextNode.Node [ TextNode.Space; TextNode.Arrow; TextNode.Space ]
+
+ let result =
+ [ for index in 0 .. typ.GenericArguments.Count - 1 do
+ let arg = typ.GenericArguments.[index]
+
+ // Add the separator if this is not the first argument
+ if index <> 0 then
+ separator
+
+ // This correspond to a generic paramter like: 'T
+ if arg.IsGenericParameter then
+ TextNode.Tick
+ TextNode.Text arg.GenericParameter.DisplayName
+
+ // This is a type definition like: 'T option or Choice<'T1, 'T2>
+ else if arg.HasTypeDefinition then
+ // For some generic types definition we don't add the generic arguments
+ if
+ arg.TypeDefinition.DisplayName = "exn"
+ || arg.TypeDefinition.DisplayName = "unit"
+ then
+
+ TextNode.Text arg.TypeDefinition.DisplayName
+
+ else
+ // This is the name of the type definition
+ // In Choice<'T1, 'T2> this correspond to Choice
+ TextNode.Text arg.TypeDefinition.DisplayName
+ TextNode.LessThan
+ // Render the generic parameters list in the form of 'T1, 'T2
+ renderGenericParameters arg.TypeDefinition.GenericParameters
+
+ TextNode.GreaterThan
+
+ else if arg.IsFunctionType then
+
+ let res =
+ [ for index in 0 .. arg.GenericArguments.Count - 1 do
+ let arg = arg.GenericArguments.[index]
+
+ if index <> 0 then
+ TextNode.Space
+ TextNode.Arrow
+ TextNode.Space
+
+ renderParameterType false arg ]
+
+ // Try to detect curried case
+ // Like in:
+ // let create (f: ('T -> unit) -> (exn -> unit) -> unit): JS.Promise<'T> = jsNative
+ // FCS gives back an equivalent of :
+ // let create (f: ('T -> unit) -> ((exn -> unit) -> unit)): JS.Promise<'T> = jsNative
+ // So we try to detect it to avoid the extract Parents
+ match res with
+ | (TextNode.Node(TextNode.LeftParent :: _) :: _) -> TextNode.Node res
+
+ | _ ->
+ TextNode.Node
+ [ TextNode.LeftParent
+
+ yield! res
+
+ TextNode.RightParent ]
+
+ else
+ TextNode.Text "Unkown syntax please open an issue" ]
+
+ // If this is a top level function we don't neeed to add the parenthesis
+ TextNode.Node
+ [ if not isTopLevel then
+ TextNode.LeftParent
+
+ TextNode.Node result
+
+ if not isTopLevel then
+ TextNode.RightParent ]
+
+ else
+ let separator = TextNode.Node [ TextNode.Space; TextNode.Comma ]
+
+ let result =
+ [ for index in 0 .. typ.GenericArguments.Count - 1 do
+ let arg = typ.GenericArguments.[index]
+
+ // Add the separator if this is not the first argument
+ if index <> 0 then
+ separator
+
+ if arg.IsGenericParameter then
+ TextNode.Tick
+ TextNode.Text arg.GenericParameter.DisplayName
+ else
+ // TODO: Generate an URL with the version of the package
+
+ let url =
+ // FIXME: This is a temporary fix to avoid the error
+ try
+ arg.TypeDefinition.FullName
+ |> String.toLower
+ |> String.replace "." "-"
+ |> String.append ".html"
+ with _ ->
+ ""
+
+ let subType = renderParameterType false arg
+
+ TextNode.Anchor(url, arg.TypeDefinition.DisplayName)
+ TextNode.LessThan
+
+ subType
+
+ TextNode.GreaterThan ]
+
+ TextNode.Node result
+
+ type ParamTypesInformation =
+ { Infos: (string * TextNode) list
+ MaxNameLength: int
+ MaxReturnTypeLength: int }
+
+ static member Init(entityName: string) =
+ { Infos = []
+ MaxNameLength = entityName.Length
+ MaxReturnTypeLength = 0 }
+
+ ///
+ /// Extracts parameter types information from a list of parameter types.
+ ///
+ /// The goals is to extract the information about the max length of the name and the return type
+ /// to be able to format the information in a nice way.
+ ///
+ /// It will allows us to align the colon, arrows and other symbols.
+ ///
+ /// The current state of parameter types information
+ /// The list of parameter types to extract information from
+ /// The list of parameters and the max length of the name and return type
+ let rec extractParamTypesInformation
+ (state: ParamTypesInformation)
+ (paramTypes: list * string * ApiDocHtml>)
+ =
+
+ match paramTypes with
+ | paramType :: tail ->
+ match paramType with
+ | Choice1Of2 fsharpParameter, name, _apiDoc ->
+ let returnType = renderParameterType true fsharpParameter.Type
+
+ let newState =
+ { state with
+ Infos = state.Infos @ [ name, returnType ]
+ MaxNameLength = System.Math.Max(state.MaxNameLength, name.Length)
+ MaxReturnTypeLength = System.Math.Max(state.MaxReturnTypeLength, returnType.Length) }
+
+ extractParamTypesInformation newState tail
+
+ // TODO: I didn't encounter this case yet, so I a not sure how to handle it
+ | Choice2Of2 _fsharpField, _name, _apiDoc ->
+ let newState =
+ { state with
+ Infos =
+ state.Infos
+ @ [ "TODO: extractParamTypesInformation -> fsharpField", TextNode.Div [] ] }
+
+ failwith "Not implemented"
+
+ extractParamTypesInformation newState tail
+
+ | [] -> state
diff --git a/src/FSharp.Formatting.ApiDocs/Prelude.fs b/src/FSharp.Formatting.ApiDocs/Prelude.fs
new file mode 100644
index 00000000..eb404d02
--- /dev/null
+++ b/src/FSharp.Formatting.ApiDocs/Prelude.fs
@@ -0,0 +1,44 @@
+[]
+module internal FSharp.Formatting.ApiDocs.Prelude
+
+open FSharp.Formatting.HtmlModel
+open FSharp.Formatting.HtmlModel.Html
+
+[]
+module Html =
+ let wrapInClass cls text = span [ Class cls ] [ !!text ]
+ let keyword text = wrapInClass "keyword" text
+ let property text = wrapInClass "property" text
+
+ let val' = keyword "val"
+ let space = !! " "
+ let spaces count = !!(String.replicate count " ")
+ let comma = keyword ","
+ let colon = keyword ":"
+ let arrow = keyword "->"
+ let dot = keyword "."
+
+ let greaterThan = keyword ">"
+ let lessThan = keyword "<"
+ let nothing = !! ""
+ let equal = keyword "="
+ let leftParent = keyword "("
+ let rightParent = keyword ")"
+
+ let minify (html: HtmlElement) = !!(html.ToMinifiedHtml())
+
+[]
+module String =
+
+ let normalizeEndOfLine (text: string) = text.Replace("\r\n", "\n")
+
+ let splitBy (c: char) (text: string) = text.Split(c)
+
+ let splitLines (text: string) =
+ text |> normalizeEndOfLine |> splitBy '\n'
+
+ let toLower (text: string) = text.ToLower()
+
+ let replace (oldValue: string) (newValue: string) (text: string) = text.Replace(oldValue, newValue)
+
+ let append (value: string) (text: string) = text + value
diff --git a/src/FSharp.Formatting.Common/HtmlModel.fs b/src/FSharp.Formatting.Common/HtmlModel.fs
index 17da8ae8..51e6bdd8 100644
--- a/src/FSharp.Formatting.Common/HtmlModel.fs
+++ b/src/FSharp.Formatting.Common/HtmlModel.fs
@@ -435,6 +435,176 @@ type internal HtmlElement =
| EncodeString of string
| CustomElement of element: string * props: HtmlProperties list * children: HtmlElement list
+ // TODO: The way F# Formatting format the HTML is causing issues because it "beautifies" the HTML too much
+ // which causes issues with the control over the spaces.
+ // Do we need to have a beautiful HTML generated?
+ // In theory, for performance reasons, we should the most minified HTML possible.
+ member tag.ToMinifiedHtml() =
+ let rec format tag (props: HtmlProperties list) (children: HtmlElement list) =
+ let cnt =
+ if children.Length > 0 then
+ (children
+ |> List.map (fun n -> (String.replicate 0 " ") + helper n)
+ |> String.concat "")
+ else
+ ""
+
+ let attrs =
+ if props.Length > 0 then
+ " " + (props |> List.map string |> String.concat " ")
+ else
+ ""
+
+ sprintf "<%s%s>%s%s>" tag attrs cnt tag
+
+ and formatVoid tag (props: HtmlProperties list) =
+ let attrs =
+ if props.Length > 0 then
+ " " + (props |> List.map string |> String.concat " ")
+ else
+ ""
+
+ sprintf "<%s%s/>" tag attrs
+
+ and helper tag =
+ match tag with
+ | A(props, children) -> format "a" props children
+ | Abbr(props, children) -> format "abbr" props children
+ | Address(props, children) -> format "address" props children
+ | Area(props) -> formatVoid "area" props
+ | Article(props, children) -> format "article" props children
+ | Aside(props, children) -> format "aside" props children
+ | Audio(props, children) -> format "audio" props children
+ | B(props, children) -> format "b" props children
+ | Base(props) -> formatVoid "base" props
+ | Bdi(props, children) -> format "bdi" props children
+ | Bdo(props, children) -> format "bdo" props children
+ | Big(props, children) -> format "big" props children
+ | Blockquote(props, children) -> format "blockquote" props children
+ | Body(props, children) -> format "body" props children
+ | Br(props) -> formatVoid "br" props
+ | Button(props, children) -> format "button" props children
+ | Canvas(props, children) -> format "canvas" props children
+ | Caption(props, children) -> format "caption" props children
+ | Cite(props, children) -> format "cite" props children
+ | Code(props, children) -> format "code" props children
+ | Col(props) -> formatVoid "col" props
+ | Colgroup(props, children) -> format "colgroup" props children
+ | Data(props, children) -> format "data" props children
+ | Datalist(props, children) -> format "datalist" props children
+ | Dd(props, children) -> format "dd" props children
+ | Del(props, children) -> format "del" props children
+ | Details(props, children) -> format "details" props children
+ | Dfn(props, children) -> format "dfn" props children
+ | Dialog(props, children) -> format "dialog" props children
+ | Div(props, children) -> format "div" props children
+ | Dl(props, children) -> format "dl" props children
+ | Dt(props, children) -> format "dt" props children
+ | Em(props, children) -> format "em" props children
+ | Embed(props) -> formatVoid "embed" props
+ | Fieldset(props, children) -> format "fieldset" props children
+ | Figcaption(props, children) -> format "figcaption" props children
+ | Figure(props, children) -> format "figure" props children
+ | Footer(props, children) -> format "footer" props children
+ | Form(props, children) -> format "form" props children
+ | H1(props, children) -> format "h1" props children
+ | H2(props, children) -> format "h2" props children
+ | H3(props, children) -> format "h3" props children
+ | H4(props, children) -> format "h4" props children
+ | H5(props, children) -> format "h5" props children
+ | H6(props, children) -> format "h6" props children
+ | Head(props, children) -> format "head" props children
+ | Header(props, children) -> format "header" props children
+ | Hgroup(props, children) -> format "hgroup" props children
+ | Hr(props) -> formatVoid "hr" props
+ | Html(props, children) -> format "html" props children
+ | I(props, children) -> format "i" props children
+ | Iframe(props, children) -> format "iframe" props children
+ | Img(props) -> formatVoid "img" props
+ | Input(props) -> formatVoid "input" props
+ | Ins(props, children) -> format "ins" props children
+ | Kbd(props, children) -> format "kbd" props children
+ | Keygen(props) -> formatVoid "keygen" props
+ | Label(props, children) -> format "label" props children
+ | Legend(props, children) -> format "legend" props children
+ | Li(props, children) -> format "li" props children
+ | Link(props) -> formatVoid "link" props
+ | Main(props, children) -> format "main" props children
+ | Map(props, children) -> format "map" props children
+ | Mark(props, children) -> format "mark" props children
+ | Menu(props, children) -> format "menu" props children
+ | Menuitem(props) -> formatVoid "menuitem" props
+ | Meta(props) -> formatVoid "meta" props
+ | Meter(props, children) -> format "meter" props children
+ | Nav(props, children) -> format "nav" props children
+ | Noscript(props, children) -> format "noscript" props children
+ | Object(props, children) -> format "object" props children
+ | Ol(props, children) -> format "ol" props children
+ | Optgroup(props, children) -> format "optgroup" props children
+ | Option(props, children) -> format "option" props children
+ | Output(props, children) -> format "output" props children
+ | P(props, children) -> format "p" props children
+ | Param(props) -> formatVoid "param" props
+ | Picture(props, children) -> format "picture" props children
+ | Pre(props, children) -> format "pre" props children
+ | Progress(props, children) -> format "progress" props children
+ | Q(props, children) -> format "q" props children
+ | Rp(props, children) -> format "rp" props children
+ | Rt(props, children) -> format "rt" props children
+ | Ruby(props, children) -> format "ruby" props children
+ | S(props, children) -> format "s" props children
+ | Samp(props, children) -> format "samp" props children
+ | Script(props, children) -> format "script" props children
+ | Section(props, children) -> format "section" props children
+ | Select(props, children) -> format "select" props children
+ | Small(props, children) -> format "small" props children
+ | Source(props) -> formatVoid "source" props
+ | Span(props, children) -> format "span" props children
+ | Strong(props, children) -> format "strong" props children
+ | Style(props, children) -> format "style" props children
+ | Sub(props, children) -> format "sub" props children
+ | Summary(props, children) -> format "summary" props children
+ | Sup(props, children) -> format "sup" props children
+ | Table(props, children) -> format "table" props children
+ | Tbody(props, children) -> format "tbody" props children
+ | Td(props, children) -> format "td" props children
+ | Textarea(props, children) -> format "textarea" props children
+ | Tfoot(props, children) -> format "tfoot" props children
+ | Th(props, children) -> format "th" props children
+ | Thead(props, children) -> format "thead" props children
+ | Time(props, children) -> format "time" props children
+ | Title(props, children) -> format "title" props children
+ | Tr(props, children) -> format "tr" props children
+ | Track(props) -> formatVoid "track" props
+ | U(props, children) -> format "u" props children
+ | Ul(props, children) -> format "ul" props children
+ | Var(props, children) -> format "var" props children
+ | Video(props, children) -> format "video" props children
+ | Wbr(props) -> formatVoid "wbr" props
+ | Svg(props, children) -> format "svg" props children
+ | Circle(props, children) -> format "circle" props children
+ | Defs(props, children) -> format "defs" props children
+ | Ellipse(props, children) -> format "ellipse" props children
+ | G(props, children) -> format "g" props children
+ | Image(props, children) -> format "image" props children
+ | Line(props, children) -> format "line" props children
+ | LinearGradient(props, children) -> format "radient" props children
+ | Mask(props, children) -> format "mask" props children
+ | Path(props, children) -> format "path" props children
+ | Pattern(props, children) -> format "pattern" props children
+ | Polygon(props, children) -> format "polygon" props children
+ | Polyline(props, children) -> format "polyline" props children
+ | RadialGradient(props, children) -> format "radient" props children
+ | Rect(props, children) -> format "rect" props children
+ | Stop(props, children) -> format "stop" props children
+ | Text(props, children) -> format "text" props children
+ | Tspan(props, children) -> format "tspan" props children
+ | String str -> str
+ | EncodeString str -> System.Web.HttpUtility.HtmlEncode str
+ | CustomElement(element, props, children) -> format element props children
+
+ helper tag
+
override tag.ToString() =
let rec format tag (props: HtmlProperties list) (children: HtmlElement list) level =
let cnt =
@@ -745,6 +915,7 @@ module internal Html =
let tspan (props: HtmlProperties list) (children: HtmlElement list) = HtmlElement.Tspan(props, children)
//let string str = HtmlElement.String str
let (!!) str = HtmlElement.String str
+ let rawString str = HtmlElement.EncodeString str
let encode str = HtmlElement.EncodeString str
/// Web component from https://iconify.design/docs/
diff --git a/src/fsdocs-tool/Options.fs b/src/fsdocs-tool/Options.fs
index 97928d04..a0a44b55 100644
--- a/src/fsdocs-tool/Options.fs
+++ b/src/fsdocs-tool/Options.fs
@@ -32,5 +32,5 @@ module Common =
let waitForKey b =
if b then
- printf "\nPress any key to continue ..."
+ printfn "\nPress any key to continue ..."
System.Console.ReadKey() |> ignore