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

166 lines
3.8 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: aMessage source: self area: anArea level: LogLevel debug
]
logInfo: aMessage area: anArea [
<category: '*osmo-logging-core'>
(self logManager)
log: aMessage source: self area: anArea level: LogLevel info
]
logNotice: aMessage area: anArea [
<category: '*osmo-logging-core'>
(self logManager)
log: aMessage source: self area: anArea level: LogLevel notice
]
logError: aMessage area: anArea [
<category: '*osmo-logging-core'>
(self logManager)
log: aMessage source: self area: anArea level: LogLevel error
]
]
Object subclass: LogLevel [
<category: 'osmo-logging-core'>
<comment: 'I represent the available levels for log messages'>
LogLevel class >> debug [
^ #logDebug
]
LogLevel class >> info [
^ #logInfo
]
LogLevel class >> notice [
^ #logNotice
]
LogLevel class >> error [
^ #logError
]
]
Object subclass: LogArea [
| name enabled level |
<category: 'osmo-logging-core'>
<comment: 'I represent one LogArea and have status'>
LogArea class >> withName: aName enabled: anEnabled minLevel: aLevel [
<category: 'instance'>
^ (LogArea new)
name: aName;
enabled: anEnabled;
level: aLevel;
yourself
]
name [
<category: 'accessing'>
^ name
]
name: aName [
<category: 'accessing'>
name := aName.
]
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
]
addArea: anArea name: aName [
<category: 'management'>
"Add the area to the list of areas"
(self class instVarNames includes: aName asSymbol)
ifFalse: [
self class addInstVarName: aName asSymbol
].
self instVarNamed: aName asSymbol put: anArea.
self class compile: aName, '[ ^ ', aName, ']' classified: 'area-access'.
]
]
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'>
| config area |
config := anObject logConfig.
area := config perform: anArea asSymbol.
area enabled
ifTrue: [
Transcript show: message; nl.
].
]
]
Eval [
area := LogArea withName: 'Base is for Base' enabled: true minLevel: LogLevel debug.
nothere := LogArea withName: 'Base is for Base' enabled: false minLevel: LogLevel debug.
LogConfig default addArea: area name: #base.
LogConfig default addArea: nothere name: #nothere.
'123' logDebug: 'Log Message' area: #base.
'456' logDebug: 'Log Foo' area: #nothere
]