| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Hs.DocString
Description
An exactprintable structure for docstrings
Synopsis
- type LHsDocString = Located HsDocString
 - data HsDocString
 - data HsDocStringDecorator
 - newtype HsDocStringChunk = HsDocStringChunk ByteString
 - type LHsDocStringChunk = Located HsDocStringChunk
 - isEmptyDocString :: HsDocString -> Bool
 - unpackHDSC :: HsDocStringChunk -> String
 - mkHsDocStringChunk :: String -> HsDocStringChunk
 - mkHsDocStringChunkUtf8ByteString :: ByteString -> HsDocStringChunk
 - pprHsDocString :: HsDocString -> SDoc
 - pprHsDocStrings :: [HsDocString] -> SDoc
 - mkGeneratedHsDocString :: String -> HsDocString
 - docStringChunks :: HsDocString -> [LHsDocStringChunk]
 - renderHsDocString :: HsDocString -> String
 - renderHsDocStrings :: [HsDocString] -> String
 - exactPrintHsDocString :: HsDocString -> String
 - pprWithDocString :: HsDocString -> SDoc -> SDoc
 
Documentation
type LHsDocString = Located HsDocString Source #
data HsDocString Source #
Haskell Documentation String
Rich structure to support exact printing The location around each chunk doesn't include the decorators
Constructors
| MultiLineDocString !HsDocStringDecorator !(NonEmpty LHsDocStringChunk) | The first chunk is preceded by "-- decorator" and each following chunk is preceded by "--"
 Example: -- | This is a docstring for   | 
| NestedDocString !HsDocStringDecorator LHsDocStringChunk | The docstring is preceded by "{-decorator" and followed by "-}" The chunk contains balanced pairs of '{-' and '-}'  | 
| GeneratedDocString HsDocStringChunk | A docstring generated either internally or via TH
 Pretty printed with the '-- |' decorator
 This is because it may contain unbalanced pairs of '{-' and '-}' and
 not form a valid   | 
Instances
data HsDocStringDecorator Source #
Constructors
| HsDocStringNext | '|' is the decorator  | 
| HsDocStringPrevious | 
  | 
| HsDocStringNamed !String | '$string' is the decorator  | 
| HsDocStringGroup !Int | The decorator is the given number of   | 
Instances
newtype HsDocStringChunk Source #
A contiguous chunk of documentation
Constructors
| HsDocStringChunk ByteString | 
Instances
isEmptyDocString :: HsDocString -> Bool Source #
unpackHDSC :: HsDocStringChunk -> String Source #
mkHsDocStringChunkUtf8ByteString :: ByteString -> HsDocStringChunk Source #
Create a HsDocString from a UTF8-encoded ByteString.
pprHsDocString :: HsDocString -> SDoc Source #
Pretty print with decorators, exactly as the user wrote it
pprHsDocStrings :: [HsDocString] -> SDoc Source #
renderHsDocString :: HsDocString -> String Source #
Just get the docstring, without any decorators
renderHsDocStrings :: [HsDocString] -> String Source #
Just get the docstring, without any decorators Separates docstrings using "nn", which is how haddock likes to render them
exactPrintHsDocString :: HsDocString -> String Source #
Pretty print with decorators, exactly as the user wrote it
pprWithDocString :: HsDocString -> SDoc -> SDoc Source #
Annotate a pretty printed thing with its doc
 The docstring comes after if is HsDocStringPrevious
 Otherwise it comes before.
 Note - we convert MultiLineDocString HsDocStringPrevious to HsDocStringNext
 because we can't control if something else will be pretty printed on the same line