1
0
Fork 0

LogManager: Make the LogArea's work across sourcecode updates

Create subclasses of the LogArea for different areas, have a
way of finding these areas and putting them into a local dictionary.

Create the LogEntry class to carry a log entry as proposed by
Paolo.
This commit is contained in:
Holger Hans Peter Freyther 2010-09-07 17:53:28 +08:00
parent ac77538544
commit 57b54630bf
1 changed files with 76 additions and 43 deletions

View File

@ -15,25 +15,73 @@ Object extend [
logDebug: aMessage area: anArea [
<category: '*osmo-logging-core'>
(self logManager)
log: aMessage source: self area: anArea level: LogLevel debug
log: LogEntry withMsg: aMessage level: LogLevel debug area: anArea context: self
]
logInfo: aMessage area: anArea [
<category: '*osmo-logging-core'>
(self logManager)
log: aMessage source: self area: anArea level: LogLevel info
log: LogEntry withMsg: aMessage level: LogLevel info area: anArea context: self
]
logNotice: aMessage area: anArea [
<category: '*osmo-logging-core'>
(self logManager)
log: aMessage source: self area: anArea level: LogLevel notice
log: LogEntry withMsg: aMessage level: LogLevel notice area: anArea context: self
]
logError: aMessage area: anArea [
<category: '*osmo-logging-core'>
(self logManager)
log: aMessage source: self area: anArea level: LogLevel error
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.
]
]
@ -61,25 +109,33 @@ Object subclass: LogLevel [
Object subclass: LogArea [
| name enabled level |
<category: 'osmo-logging-core'>
<comment: 'I represent one LogArea and have status'>
<comment: 'I represent a LogArea'>
LogArea class >> withName: aName enabled: anEnabled minLevel: aLevel [
<category: 'instance'>
^ (LogArea new)
name: aName;
enabled: anEnabled;
level: aLevel;
yourself
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'>
^ name
]
name: aName [
<category: 'accessing'>
name := aName.
^ self subclassResponsibility
]
enabled [
@ -114,19 +170,6 @@ Object subclass: LogConfig [
^ 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 [
@ -142,11 +185,9 @@ Object subclass: LogManager [
log: message source: anObject area: anArea level: anLevel [
<category: 'log'>
| config area |
config := anObject logConfig.
area := config perform: anArea asSymbol.
| area |
area := LogArea findArea: anArea.
(area enabled and: [anLevel >= area minLevel])
ifTrue: [
Transcript show: message; nl.
@ -155,12 +196,4 @@ Object subclass: LogManager [
]
Eval [
| area nothere |
area := LogArea withName: 'Base is for Base' enabled: true minLevel: LogLevel info.
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' logInfo: 'Log Message' area: #base.
'456' logDebug: 'Log Foo' area: #nothere
]