MiniDocs/src/MiniDocs/String.extension.st

163 lines
4.6 KiB
Smalltalk

Extension { #name : #String }
{ #category : #'*MiniDocs' }
String >> accentedCharactersCorrection [
| modified corrections |
corrections := {
'ó' -> 'ó' . 'ú' -> 'ú' . 'ñ' -> 'ñ' .
'í' -> 'í' . 'á' -> 'á' . 'é' -> 'é' . '’' -> $' asString} asDictionary.
modified := self copy.
corrections keysAndValuesDo: [ :k :v |
modified := modified copyReplaceAll: k with: v
].
^ modified
]
{ #category : #'*MiniDocs' }
String >> asDashedLowercase [
"I convert phrases like 'This is a phrase' into 'this-is-a-phrase'."
^ '-' join: (self substrings collect: [:each | each asLowercase ])
]
{ #category : #'*MiniDocs' }
String >> asInteger [
"Return the integer present in the receiver, or nil. In case of float, returns the integer part."
"'1' asInteger >>> 1"
"'-1' asInteger >>> -1"
"'10' asInteger >>> 10"
"'a' asInteger >>> nil"
"'1.234' asInteger >>> 1"
^ (self copyWithoutAll: '_') asSignedInteger
]
{ #category : #'*MiniDocs' }
String >> contentsWithoutYAMLMetadata [
| newContents |
self detectYAMLMetadata ifFalse: [ ^ self ].
newContents := '' writeStream.
(self lines copyFrom: self yamlMetadataClosingLineNumber + 2 to: self lines size) do: [ :line |
newContents nextPutAll: line; cr ].
^ newContents contents.
]
{ #category : #'*MiniDocs' }
String >> deleteYAMLMetadata [
| newContents |
self detectYAMLMetadata ifFalse: [ ^ self ].
newContents := '' writeStream.
(self lines copyFrom: self yamlMetadataClosingLineNumber + 1 to: self lines size) do: [ :line |
newContents nextPutAll: line; lf;lf ].
^ newContents contents.
]
{ #category : #'*MiniDocs' }
String >> demoteMarkdownHeaders [
| response |
response := self contents lines.
self markdownHeaders associations allButFirstDo: [ :assoc |
response at: assoc key put: '#', assoc value ].
^ response asStringWithCr withInternetLineEndings
]
{ #category : #'*MiniDocs' }
String >> detectYAMLMetadata [
| lines |
lines := self lines.
^ self startsWithYAMLMetadataDelimiter
and: [ lines allButFirst
detect: [ :currentLine | currentLine beginsWith: self class yamlMetadataDelimiter ]
ifFound: [ ^ true ] ifNone: [ ^ false ] ]
]
{ #category : #'*MiniDocs' }
String >> markdownHeaders [
| response headers |
headers := (LeTextSnippet string: self contents) ast // #LeHeaderNode collect: [ :each | each headerFullName asString ].
response := OrderedDictionary new.
self lines doWithIndex: [:line :index |
(line beginsWithAnyOf: headers)
ifTrue: [ response at: index put: line ]
].
^ response
]
{ #category : #'*MiniDocs' }
String >> promoteMarkdownHeaders [
| response |
response := self contents lines.
self markdownHeaders associationsDo: [ :assoc |
response at: assoc key put: assoc value allButFirst ].
^ response asStringWithCr withInternetLineEndings
]
{ #category : #'*MiniDocs' }
String >> romanizeAccents [
| modified corrections |
corrections := {
'ó' -> 'o' . 'ú' -> 'u' . 'ñ' -> 'n' .
'í' -> 'i' . 'á' -> 'a' . 'é' -> 'e' } asDictionary.
modified := self copy.
corrections keysAndValuesDo: [ :k :v |
modified := modified copyReplaceAll: k with: v
].
^ modified
]
{ #category : #'*MiniDocs' }
String >> startsWithYAMLMetadataDelimiter [
self lines ifEmpty: [^false].
^ self lines first beginsWith: self class yamlMetadataDelimiter
]
{ #category : #'*MiniDocs' }
String >> withoutXMLTagDelimiters [
^ self copyWithoutAll: #($< $>)
]
{ #category : #'*MiniDocs' }
String >> yamlMetadata [
^ (YAML2JSON fromString: self yamlMetadataString)
]
{ #category : #'*MiniDocs' }
String >> yamlMetadataClosingLineNumber [
"I return the line where the closing of the YAML metadata occurs or 0 if no closing is found."
self startsWithYAMLMetadataDelimiter ifFalse: [ ^ self ].
self lines allButFirst doWithIndex: [ :currentLine :i |
(currentLine beginsWith: self class yamlMetadataDelimiter) ifTrue: [ ^ i + 1 ]]
]
{ #category : #'*MiniDocs' }
String class >> yamlMetadataDelimiter [
^ '---'
]
{ #category : #'*MiniDocs' }
String >> yamlMetadataString [
| output yamlLines |
self detectYAMLMetadata ifFalse: [ ^nil ].
self lines ifEmpty: [ ^nil ].
yamlLines := self lines copyFrom: 2 to: self yamlMetadataClosingLineNumber - 1.
output := '' writeStream.
yamlLines do: [ :line |
output
nextPutAll: line;
nextPut: Character lf. ].
^ output contents
]
{ #category : #'*MiniDocs' }
String >> yamlMetadataStringWithDelimiters [
| output |
self yamlMetadataString ifNil: [ ^ nil ].
output := String new writeStream.
output nextPutAll: self class yamlMetadataDelimiter; cr.
output nextPutAll: self yamlMetadataString.
output nextPutAll: self class yamlMetadataDelimiter; cr.
^ output contents.
]