1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-logging/LogManager.st

200 lines
4.0 KiB
Smalltalk

"Copyright placeholder"
Object extend [
logConfig [
<category: '*osmo-logging-core'>
"I provide access to the global LogConfig"
^ LogConfig default
]
logManager [
<category: '*osmo-logging-core'>
^ LogManager default
]
logDebug: aMessage area: anArea [
<category: '*osmo-logging-core'>
(self logManager)
log: LogEntry withMsg: aMessage level: LogLevel debug area: anArea context: self
]
logInfo: aMessage area: anArea [
<category: '*osmo-logging-core'>
(self logManager)
log: LogEntry withMsg: aMessage level: LogLevel info area: anArea context: self
]
logNotice: aMessage area: anArea [
<category: '*osmo-logging-core'>
(self logManager)
log: LogEntry withMsg: aMessage level: LogLevel notice area: anArea context: self
]
logError: aMessage area: anArea [
<category: '*osmo-logging-core'>
(self logManager)
log: LogEntry withMsg: aMessage level: LogLevel error area: anArea context: self
]
]
Object subclass: LogEntry [
| level ctx area msg |
<category: 'osmo-logging-core'>
<comment: 'I represent a log entry and hold the text, level, area'>
LogEntry class >> withMsg: aMsg level: anLevel area: anArea context: aContext [
^ self new
msg: aMsg;
level: anLevel;
area: anArea;
context: aContext;
yourself.
]
msg [
^ msg
]
msg: aMsg [
msg := aMsg.
]
level [
^ level
]
level: anLevel [
level := anLevel;
]
area [
^ area
]
area: anArea [
area := anArea.
]
context [
^ context
]
context: aContext [
context := aContext.
]
]
Object subclass: LogLevel [
<category: 'osmo-logging-core'>
<comment: 'I represent the available levels for log messages'>
LogLevel class >> debug [
^ 1
]
LogLevel class >> info [
^ 3
]
LogLevel class >> notice [
^ 5
]
LogLevel class >> error [
^ 7
]
]
Object subclass: LogArea [
| name enabled level |
<category: 'osmo-logging-core'>
<comment: 'I represent a LogArea'>
Areas := Dictionary new.
LogArea class >> findArea: aSymbol [
"Find an Area and place the default into our dictionary"
^ Areas at: aSymbol ifAbsent: [
LogArea allSubclassesDo: [ :each |
each name = aSymbol
ifTrue: [
| area |
area := each default.
Areas at: aSymbol put: area.
^ area
].
].
]
]
LogArea class >> default [
^ self subclassResponsibility
]
name [
<category: 'accessing'>
^ self subclassResponsibility
]
enabled [
<category: 'accessing'>
^ enabled
]
enabled: anEnabled [
<category: 'accessing'>
enabled := anEnabled.
]
minLevel [
<category: 'accessing'>
^ level
]
minLevel: aLevel [
<category: 'accessing'>
level := aLevel
]
]
Object subclass: LogConfig [
<category: 'osmo-logging-core'>
<comment: 'I handle the config, the backends, the log areas, the default level'>
Config := LogConfig new.
LogConfig class >> default [
<category: 'accessing'>
^ Config
]
]
Object subclass: LogManager [
<category: 'osmo-logging-core'>
<comment: 'I handle the actual log invocation'>
Log := LogManager new.
LogManager class >> default [
<category: 'instance'>
^ Log
]
log: message source: anObject area: anArea level: anLevel [
<category: 'log'>
| area |
area := LogArea findArea: anArea.
(area enabled and: [anLevel >= area minLevel])
ifTrue: [
Transcript show: message; nl.
].
]
]
Eval [
]