{-# OPTIONS_GHC -Wno-orphans #-}
module Lorentz.UStore.Doc
( UStoreTemplateHasDoc (..)
, UStoreMarkerHasDoc (..)
, DUStoreTemplate (..)
, dUStoreTemplateRef
, DocumentTW
) where
import Data.Constraint (Dict(..))
import Fmt (build)
import Lorentz.Doc
import Lorentz.UStore.Traversal
import Lorentz.UStore.Types
import Michelson.Typed.Haskell.Doc
import Util.Generic
import Util.Label
import Util.Markdown
import Util.Typeable
import Util.TypeLits
class Typeable template => UStoreTemplateHasDoc template where
ustoreTemplateDocName :: Text
default ustoreTemplateDocName
:: (Generic template, KnownSymbol (GenericTypeName template))
=> Text
ustoreTemplateDocName = KnownSymbol (GenericTypeName template) => Text
forall (s :: Symbol). KnownSymbol s => Text
symbolValT' @(GenericTypeName template)
where _needGeneric :: Dict (Generic template)
_needGeneric = Generic template => Dict (Generic template)
forall (a :: Constraint). a => Dict a
Dict @(Generic template)
ustoreTemplateDocDescription :: Markdown
ustoreTemplateDocContents :: Markdown
default ustoreTemplateDocContents
:: (UStoreTraversable DocumentTW template) => Markdown
ustoreTemplateDocContents =
"\n" Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> Proxy template -> Markdown
forall template.
UStoreTraversable DocumentTW template =>
Proxy template -> Markdown
documentUStore (Proxy template
forall k (t :: k). Proxy t
Proxy @template)
ustoreTemplateDocDependencies :: [SomeTypeWithDoc]
default ustoreTemplateDocDependencies
:: (UStoreTraversable DocumentTW template) => [SomeTypeWithDoc]
ustoreTemplateDocDependencies =
Proxy template -> [SomeTypeWithDoc]
forall template.
UStoreTraversable DocumentTW template =>
Proxy template -> [SomeTypeWithDoc]
gatherUStoreDeps (Proxy template
forall k (t :: k). Proxy t
Proxy @template)
class (KnownUStoreMarker marker) =>
(marker :: UStoreMarkerType) where
:: Text -> Text
instance UStoreTemplateHasDoc template =>
TypeHasDoc (UStore template) where
typeDocName :: Proxy (UStore template) -> Text
typeDocName _ = "Upgradeable storage"
typeDocMdDescription :: Markdown
typeDocMdDescription = [md|
Storage with not hardcoded structure, which allows upgrading the contract
in place. UStore is capable of storing simple fields and multiple submaps.
|]
typeDocMdReference :: Proxy (UStore template) -> WithinParens -> Markdown
typeDocMdReference tp :: Proxy (UStore template)
tp wp :: WithinParens
wp =
WithinParens -> Markdown -> Markdown
applyWithinParens WithinParens
wp (Markdown -> Markdown) -> Markdown -> Markdown
forall a b. (a -> b) -> a -> b
$ [Markdown] -> Markdown
forall a. Monoid a => [a] -> a
mconcat
[ Markdown -> DocItemRef 'DocItemInDefinitions 'True -> Markdown
forall anchor. ToAnchor anchor => Markdown -> anchor -> Markdown
mdLocalRef (Markdown -> Markdown
mdTicked "UStore") (DType
-> DocItemRef (DocItemPlacement DType) (DocItemReferenced DType)
forall d.
DocItem d =>
d -> DocItemRef (DocItemPlacement d) (DocItemReferenced d)
docItemRef (Proxy (UStore template) -> DType
forall a. TypeHasDoc a => Proxy a -> DType
DType Proxy (UStore template)
tp))
, " "
, DUStoreTemplate -> Markdown
dUStoreTemplateRef (Proxy template -> DUStoreTemplate
forall template.
UStoreTemplateHasDoc template =>
Proxy template -> DUStoreTemplate
DUStoreTemplate (Proxy template
forall k (t :: k). Proxy t
Proxy @template))
]
typeDocHaskellRep :: TypeDocHaskellRep (UStore template)
typeDocHaskellRep = TypeDocHaskellRep (UStore template)
forall a. (Generic a, GTypeHasDoc (Rep a)) => TypeDocHaskellRep a
homomorphicTypeDocHaskellRep
typeDocMichelsonRep :: TypeDocMichelsonRep (UStore template)
typeDocMichelsonRep = TypeDocMichelsonRep (UStore template)
forall a. SingI (ToT a) => TypeDocMichelsonRep a
homomorphicTypeDocMichelsonRep
typeDocDependencies :: Proxy (UStore template) -> [SomeDocDefinitionItem]
typeDocDependencies p :: Proxy (UStore template)
p =
Proxy (UStore template) -> [SomeDocDefinitionItem]
forall a.
(Generic a, GTypeHasDoc (Rep a)) =>
Proxy a -> [SomeDocDefinitionItem]
genericTypeDocDependencies Proxy (UStore template)
p [SomeDocDefinitionItem]
-> [SomeDocDefinitionItem] -> [SomeDocDefinitionItem]
forall a. Semigroup a => a -> a -> a
<>
[DUStoreTemplate -> SomeDocDefinitionItem
forall d.
(DocItem d, DocItemPlacement d ~ 'DocItemInDefinitions) =>
d -> SomeDocDefinitionItem
SomeDocDefinitionItem (Proxy template -> DUStoreTemplate
forall template.
UStoreTemplateHasDoc template =>
Proxy template -> DUStoreTemplate
DUStoreTemplate (Proxy template -> DUStoreTemplate)
-> Proxy template -> DUStoreTemplate
forall a b. (a -> b) -> a -> b
$ Proxy template
forall k (t :: k). Proxy t
Proxy @template)]
data DUStoreTemplate where
DUStoreTemplate
:: UStoreTemplateHasDoc template
=> Proxy template -> DUStoreTemplate
instance Eq DUStoreTemplate where
DUStoreTemplate p1 :: Proxy template
p1 == :: DUStoreTemplate -> DUStoreTemplate -> Bool
== DUStoreTemplate p2 :: Proxy template
p2 = Proxy template -> Proxy template -> Bool
forall k (a1 :: k) (a2 :: k) (t :: k -> *).
(Typeable a1, Typeable a2, Eq (t a1)) =>
t a1 -> t a2 -> Bool
eqParam1 Proxy template
p1 Proxy template
p2
instance Ord DUStoreTemplate where
DUStoreTemplate p1 :: Proxy template
p1 compare :: DUStoreTemplate -> DUStoreTemplate -> Ordering
`compare` DUStoreTemplate p2 :: Proxy template
p2 = Proxy template -> Proxy template -> Ordering
forall a1 a2.
(Typeable a1, Typeable a2, Ord a1) =>
a1 -> a2 -> Ordering
compareExt Proxy template
p1 Proxy template
p2
instance DocItem DUStoreTemplate where
type DocItemPlacement DUStoreTemplate = 'DocItemInDefinitions
type DocItemReferenced DUStoreTemplate = 'True
docItemPos :: Natural
docItemPos = 12700
docItemSectionName :: Maybe Text
docItemSectionName = Text -> Maybe Text
forall a. a -> Maybe a
Just "Used upgradeable storage formats"
docItemSectionDescription :: Maybe Markdown
docItemSectionDescription = Markdown -> Maybe Markdown
forall a. a -> Maybe a
Just
"This section describes formats (aka _templates_) of upgradeable storages \
\mentioned across the given document. \
\Each format describes set of fields and virtual submaps which the storage \
\must have."
docItemToMarkdown :: HeaderLevel -> DUStoreTemplate -> Markdown
docItemToMarkdown lvl :: HeaderLevel
lvl (DUStoreTemplate (Proxy template
_ :: Proxy template)) =
[Markdown] -> Markdown
forall a. Monoid a => [a] -> a
mconcat
[ Markdown
mdSeparator
, HeaderLevel -> Markdown -> Markdown
mdHeader HeaderLevel
lvl (Markdown -> Markdown
mdTicked (Markdown -> Markdown) -> (Text -> Markdown) -> Text -> Markdown
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Markdown
forall p. Buildable p => p -> Markdown
build (Text -> Markdown) -> Text -> Markdown
forall a b. (a -> b) -> a -> b
$ UStoreTemplateHasDoc template => Text
forall template. UStoreTemplateHasDoc template => Text
ustoreTemplateDocName @template)
, UStoreTemplateHasDoc template => Markdown
forall template. UStoreTemplateHasDoc template => Markdown
ustoreTemplateDocDescription @template
, "\n\n"
, Markdown -> Markdown -> Markdown
mdSubsection "Contents" (Markdown -> Markdown) -> Markdown -> Markdown
forall a b. (a -> b) -> a -> b
$ UStoreTemplateHasDoc template => Markdown
forall template. UStoreTemplateHasDoc template => Markdown
ustoreTemplateDocContents @template
, "\n\n"
]
docItemRef :: DUStoreTemplate
-> DocItemRef
(DocItemPlacement DUStoreTemplate)
(DocItemReferenced DUStoreTemplate)
docItemRef (DUStoreTemplate (Proxy template
_ :: Proxy template)) =
DocItemId -> DocItemRef 'DocItemInDefinitions 'True
DocItemRef (DocItemId -> DocItemRef 'DocItemInDefinitions 'True)
-> (Text -> DocItemId)
-> Text
-> DocItemRef 'DocItemInDefinitions 'True
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> DocItemId
DocItemId (Text
-> DocItemRef
(DocItemPlacement DUStoreTemplate)
(DocItemReferenced DUStoreTemplate))
-> Text
-> DocItemRef
(DocItemPlacement DUStoreTemplate)
(DocItemReferenced DUStoreTemplate)
forall a b. (a -> b) -> a -> b
$
"ustore-template-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> UStoreTemplateHasDoc template => Text
forall template. UStoreTemplateHasDoc template => Text
ustoreTemplateDocName @template
docItemDependencies :: DUStoreTemplate -> [SomeDocDefinitionItem]
docItemDependencies (DUStoreTemplate (Proxy template
_ :: Proxy template)) =
UStoreTemplateHasDoc template => [SomeTypeWithDoc]
forall template. UStoreTemplateHasDoc template => [SomeTypeWithDoc]
ustoreTemplateDocDependencies @template [SomeTypeWithDoc]
-> (SomeTypeWithDoc -> SomeDocDefinitionItem)
-> [SomeDocDefinitionItem]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\(SomeTypeWithDoc t :: Proxy td
t) -> DType -> SomeDocDefinitionItem
forall d.
(DocItem d, DocItemPlacement d ~ 'DocItemInDefinitions) =>
d -> SomeDocDefinitionItem
SomeDocDefinitionItem (Proxy td -> DType
forall a. TypeHasDoc a => Proxy a -> DType
DType Proxy td
t)
dUStoreTemplateRef :: DUStoreTemplate -> Markdown
dUStoreTemplateRef :: DUStoreTemplate -> Markdown
dUStoreTemplateRef (DUStoreTemplate (Proxy template
_ :: Proxy template)) =
Markdown -> DocItemRef 'DocItemInDefinitions 'True -> Markdown
forall anchor. ToAnchor anchor => Markdown -> anchor -> Markdown
mdLocalRef (Markdown -> Markdown
mdTicked (Markdown -> Markdown) -> (Text -> Markdown) -> Text -> Markdown
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Markdown
forall p. Buildable p => p -> Markdown
build (Text -> Markdown) -> Text -> Markdown
forall a b. (a -> b) -> a -> b
$ UStoreTemplateHasDoc template => Text
forall template. UStoreTemplateHasDoc template => Text
ustoreTemplateDocName @template)
(DUStoreTemplate
-> DocItemRef
(DocItemPlacement DUStoreTemplate)
(DocItemReferenced DUStoreTemplate)
forall d.
DocItem d =>
d -> DocItemRef (DocItemPlacement d) (DocItemReferenced d)
docItemRef (Proxy template -> DUStoreTemplate
forall template.
UStoreTemplateHasDoc template =>
Proxy template -> DUStoreTemplate
DUStoreTemplate (Proxy template
forall k (t :: k). Proxy t
Proxy @template)))
instance UStoreTemplateHasDoc () where
ustoreTemplateDocName :: Text
ustoreTemplateDocName = "empty"
ustoreTemplateDocDescription :: Markdown
ustoreTemplateDocDescription = ""
ustoreTemplateDocContents :: Markdown
ustoreTemplateDocContents =
Markdown -> Markdown
mdItalic "empty"
instance UStoreMarkerHasDoc UMarkerPlainField where
ustoreMarkerKeyEncoding :: Text -> Text
ustoreMarkerKeyEncoding k :: Text
k = "pack (" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
k Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ")"
documentUStore
:: forall template.
(UStoreTraversable DocumentTW template)
=> Proxy template -> Markdown
documentUStore :: Proxy template -> Markdown
documentUStore _ =
let Const collected :: DocCollector
collected = DocumentTW
-> UStoreTraversalArgumentWrapper DocumentTW template
-> UStoreTraversalMonad DocumentTW template
forall way template.
UStoreTraversable way template =>
way
-> UStoreTraversalArgumentWrapper way template
-> UStoreTraversalMonad way template
traverseUStore @_ @template DocumentTW
DocumentTW (() -> Const () template
forall k a (b :: k). a -> Const a b
Const ())
entries :: [Markdown]
entries = Endo [Markdown] -> [Markdown] -> [Markdown]
forall a. Endo a -> a -> a
appEndo (DocCollector -> Endo [Markdown]
dcEntries DocCollector
collected) []
in if [Markdown] -> Bool
forall t. Container t => t -> Bool
null [Markdown]
entries
then Markdown -> Markdown
mdTicked "<empty>"
else [Markdown] -> Markdown
forall a. Monoid a => [a] -> a
mconcat ([Markdown] -> Markdown) -> [Markdown] -> Markdown
forall a b. (a -> b) -> a -> b
$ (Markdown -> Markdown) -> [Markdown] -> [Markdown]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
map (\e :: Markdown
e -> "* " Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> Markdown
e Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> "\n") [Markdown]
entries
gatherUStoreDeps
:: forall template.
(UStoreTraversable DocumentTW template)
=> Proxy template -> [SomeTypeWithDoc]
gatherUStoreDeps :: Proxy template -> [SomeTypeWithDoc]
gatherUStoreDeps _ =
let Const collected :: DocCollector
collected = DocumentTW
-> UStoreTraversalArgumentWrapper DocumentTW template
-> UStoreTraversalMonad DocumentTW template
forall way template.
UStoreTraversable way template =>
way
-> UStoreTraversalArgumentWrapper way template
-> UStoreTraversalMonad way template
traverseUStore @_ @template DocumentTW
DocumentTW (() -> Const () template
forall k a (b :: k). a -> Const a b
Const ())
in Endo [SomeTypeWithDoc] -> [SomeTypeWithDoc] -> [SomeTypeWithDoc]
forall a. Endo a -> a -> a
appEndo (DocCollector -> Endo [SomeTypeWithDoc]
dcDependencies DocCollector
collected) []
data DocCollector = DocCollector
{ DocCollector -> Endo [Markdown]
dcEntries :: Endo [Markdown]
, DocCollector -> Endo [SomeTypeWithDoc]
dcDependencies :: Endo [SomeTypeWithDoc]
}
data DocumentTW = DocumentTW
instance Semigroup DocCollector where
DocCollector e1 :: Endo [Markdown]
e1 d1 :: Endo [SomeTypeWithDoc]
d1 <> :: DocCollector -> DocCollector -> DocCollector
<> DocCollector e2 :: Endo [Markdown]
e2 d2 :: Endo [SomeTypeWithDoc]
d2 = Endo [Markdown] -> Endo [SomeTypeWithDoc] -> DocCollector
DocCollector (Endo [Markdown]
e1 Endo [Markdown] -> Endo [Markdown] -> Endo [Markdown]
forall a. Semigroup a => a -> a -> a
<> Endo [Markdown]
e2) (Endo [SomeTypeWithDoc]
d1 Endo [SomeTypeWithDoc]
-> Endo [SomeTypeWithDoc] -> Endo [SomeTypeWithDoc]
forall a. Semigroup a => a -> a -> a
<> Endo [SomeTypeWithDoc]
d2)
instance Monoid DocCollector where
mempty :: DocCollector
mempty = Endo [Markdown] -> Endo [SomeTypeWithDoc] -> DocCollector
DocCollector Endo [Markdown]
forall a. Monoid a => a
mempty Endo [SomeTypeWithDoc]
forall a. Monoid a => a
mempty
instance UStoreTraversalWay DocumentTW where
type UStoreTraversalArgumentWrapper DocumentTW = Const ()
type UStoreTraversalMonad DocumentTW = Const DocCollector
instance (UStoreMarkerHasDoc marker, TypeHasDoc v) =>
UStoreTraversalFieldHandler DocumentTW marker v where
ustoreTraversalFieldHandler :: DocumentTW
-> Label name
-> UStoreTraversalArgumentWrapper DocumentTW v
-> UStoreTraversalMonad DocumentTW v
ustoreTraversalFieldHandler DocumentTW fieldName :: Label name
fieldName (Const ()) =
DocCollector -> Const DocCollector v
forall k a (b :: k). a -> Const a b
Const $WDocCollector :: Endo [Markdown] -> Endo [SomeTypeWithDoc] -> DocCollector
DocCollector
{ dcEntries :: Endo [Markdown]
dcEntries = ([Markdown] -> [Markdown]) -> Endo [Markdown]
forall a. (a -> a) -> Endo a
Endo (([Markdown] -> [Markdown]) -> Endo [Markdown])
-> (Markdown -> [Markdown] -> [Markdown])
-> Markdown
-> Endo [Markdown]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:) (Markdown -> Endo [Markdown]) -> Markdown -> Endo [Markdown]
forall a b. (a -> b) -> a -> b
$ [Markdown] -> Markdown
forall a. Monoid a => [a] -> a
mconcat
[ Markdown -> Markdown
mdBold "Field" Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> " "
, Markdown -> Markdown
mdTicked (Text -> Markdown
forall p. Buildable p => p -> Markdown
build (Text -> Markdown) -> Text -> Markdown
forall a b. (a -> b) -> a -> b
$ Label name -> Text
forall (name :: Symbol). Label name -> Text
labelToText Label name
fieldName)
, ": "
, Proxy v -> WithinParens -> Markdown
forall a. TypeHasDoc a => Proxy a -> WithinParens -> Markdown
typeDocMdReference (Proxy v
forall k (t :: k). Proxy t
Proxy @v) (Bool -> WithinParens
WithinParens Bool
False)
, "\n"
, Markdown -> Markdown -> Markdown
mdSpoiler "Encoding" (Markdown -> Markdown) -> Markdown -> Markdown
forall a b. (a -> b) -> a -> b
$ [Markdown] -> Markdown
forall a. Monoid a => [a] -> a
mconcat
[ "\n"
, let key :: Markdown
key = Text -> Markdown
forall p. Buildable p => p -> Markdown
build (Text -> Markdown) -> Text -> Markdown
forall a b. (a -> b) -> a -> b
$
Text -> Text
forall (marker :: UStoreMarkerType).
UStoreMarkerHasDoc marker =>
Text -> Text
ustoreMarkerKeyEncoding @marker
("\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Label name -> Text
forall (name :: Symbol). Label name -> Text
labelToText Label name
fieldName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "\"")
in
" + " Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> Markdown -> Markdown
mdTicked ("key = " Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> Markdown
key) Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> "\n\n"
, " + " Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> Markdown -> Markdown
mdTicked "value = pack (<field value>)" Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> "\n\n"
, Markdown
mdSeparator
]
, "\n"
]
, dcDependencies :: Endo [SomeTypeWithDoc]
dcDependencies = ([SomeTypeWithDoc] -> [SomeTypeWithDoc]) -> Endo [SomeTypeWithDoc]
forall a. (a -> a) -> Endo a
Endo (([SomeTypeWithDoc] -> [SomeTypeWithDoc])
-> Endo [SomeTypeWithDoc])
-> ([SomeTypeWithDoc] -> [SomeTypeWithDoc] -> [SomeTypeWithDoc])
-> [SomeTypeWithDoc]
-> Endo [SomeTypeWithDoc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [SomeTypeWithDoc] -> [SomeTypeWithDoc] -> [SomeTypeWithDoc]
forall a. Semigroup a => a -> a -> a
(<>) ([SomeTypeWithDoc] -> Endo [SomeTypeWithDoc])
-> [SomeTypeWithDoc] -> Endo [SomeTypeWithDoc]
forall a b. (a -> b) -> a -> b
$
[ Proxy v -> SomeTypeWithDoc
forall td. TypeHasDoc td => Proxy td -> SomeTypeWithDoc
SomeTypeWithDoc (Proxy v
forall k (t :: k). Proxy t
Proxy @v)
]
}
instance (TypeHasDoc k, TypeHasDoc v) =>
UStoreTraversalSubmapHandler DocumentTW k v where
ustoreTraversalSubmapHandler :: DocumentTW
-> Label name
-> UStoreTraversalArgumentWrapper DocumentTW (Map k v)
-> UStoreTraversalMonad DocumentTW (Map k v)
ustoreTraversalSubmapHandler DocumentTW fieldName :: Label name
fieldName (Const ()) =
DocCollector -> Const DocCollector (Map k v)
forall k a (b :: k). a -> Const a b
Const $WDocCollector :: Endo [Markdown] -> Endo [SomeTypeWithDoc] -> DocCollector
DocCollector
{ dcEntries :: Endo [Markdown]
dcEntries = ([Markdown] -> [Markdown]) -> Endo [Markdown]
forall a. (a -> a) -> Endo a
Endo (([Markdown] -> [Markdown]) -> Endo [Markdown])
-> (Markdown -> [Markdown] -> [Markdown])
-> Markdown
-> Endo [Markdown]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:) (Markdown -> Endo [Markdown]) -> Markdown -> Endo [Markdown]
forall a b. (a -> b) -> a -> b
$ [Markdown] -> Markdown
forall a. Monoid a => [a] -> a
mconcat
[ Markdown -> Markdown
mdBold "Submap" Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> " "
, Markdown -> Markdown
mdTicked (Text -> Markdown
forall p. Buildable p => p -> Markdown
build (Text -> Markdown) -> Text -> Markdown
forall a b. (a -> b) -> a -> b
$ Label name -> Text
forall (name :: Symbol). Label name -> Text
labelToText Label name
fieldName)
, ": "
, Proxy k -> WithinParens -> Markdown
forall a. TypeHasDoc a => Proxy a -> WithinParens -> Markdown
typeDocMdReference (Proxy k
forall k (t :: k). Proxy t
Proxy @k) (Bool -> WithinParens
WithinParens Bool
False)
, " -> "
, Proxy v -> WithinParens -> Markdown
forall a. TypeHasDoc a => Proxy a -> WithinParens -> Markdown
typeDocMdReference (Proxy v
forall k (t :: k). Proxy t
Proxy @v) (Bool -> WithinParens
WithinParens Bool
False)
, "\n"
, Markdown -> Markdown -> Markdown
mdSpoiler "Encoding" (Markdown -> Markdown) -> Markdown -> Markdown
forall a b. (a -> b) -> a -> b
$ [Markdown] -> Markdown
forall a. Monoid a => [a] -> a
mconcat
[ "\n"
, " + " Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> Markdown -> Markdown
mdTicked "key = pack (<submap key>)" Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> "\n\n"
, " + " Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> Markdown -> Markdown
mdTicked "value = pack (<submap value>)" Markdown -> Markdown -> Markdown
forall a. Semigroup a => a -> a -> a
<> "\n\n"
, Markdown
mdSeparator
]
, "\n"
]
, dcDependencies :: Endo [SomeTypeWithDoc]
dcDependencies = ([SomeTypeWithDoc] -> [SomeTypeWithDoc]) -> Endo [SomeTypeWithDoc]
forall a. (a -> a) -> Endo a
Endo (([SomeTypeWithDoc] -> [SomeTypeWithDoc])
-> Endo [SomeTypeWithDoc])
-> ([SomeTypeWithDoc] -> [SomeTypeWithDoc] -> [SomeTypeWithDoc])
-> [SomeTypeWithDoc]
-> Endo [SomeTypeWithDoc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [SomeTypeWithDoc] -> [SomeTypeWithDoc] -> [SomeTypeWithDoc]
forall a. Semigroup a => a -> a -> a
(<>) ([SomeTypeWithDoc] -> Endo [SomeTypeWithDoc])
-> [SomeTypeWithDoc] -> Endo [SomeTypeWithDoc]
forall a b. (a -> b) -> a -> b
$
[ Proxy k -> SomeTypeWithDoc
forall td. TypeHasDoc td => Proxy td -> SomeTypeWithDoc
SomeTypeWithDoc (Proxy k
forall k (t :: k). Proxy t
Proxy @k)
, Proxy v -> SomeTypeWithDoc
forall td. TypeHasDoc td => Proxy td -> SomeTypeWithDoc
SomeTypeWithDoc (Proxy v
forall k (t :: k). Proxy t
Proxy @v)
]
}