1
0
Fork 0

Create a LogTarget class, with a Transcript implementation, improve LogArea

Create:
	LogTarget
		LogTargetTranscript

Use LogArea, find area's automatically.
This commit is contained in:
Holger Hans Peter Freyther 2010-09-08 12:58:55 +08:00
parent 57b54630bf
commit d16a9da541
1 changed files with 87 additions and 46 deletions

View File

@ -1,12 +1,6 @@
"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
@ -15,25 +9,25 @@ Object extend [
logDebug: aMessage area: anArea [
<category: '*osmo-logging-core'>
(self logManager)
log: LogEntry withMsg: aMessage level: LogLevel debug area: anArea context: self
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
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
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
log: (LogEntry withMsg: aMessage level: LogLevel error area: anArea context: self)
]
]
@ -65,7 +59,7 @@ Object subclass: LogEntry [
]
level: anLevel [
level := anLevel;
level := anLevel
]
area [
@ -77,11 +71,11 @@ Object subclass: LogEntry [
]
context [
^ context
^ ctx
]
context: aContext [
context := aContext.
ctx := aContext.
]
]
@ -111,29 +105,29 @@ Object subclass: LogArea [
<category: 'osmo-logging-core'>
<comment: 'I represent a LogArea'>
Areas := Dictionary new.
LogArea class >> findArea: aSymbol [
LogArea class >> defaultForArea: aSymbol [
"Find an Area and place the default into our dictionary"
LogArea allSubclassesDo: [ :each |
(each areaName) = aSymbol
ifTrue: [
^ each default.
].
].
^ Areas at: aSymbol ifAbsent: [
LogArea allSubclassesDo: [ :each |
each name = aSymbol
ifTrue: [
| area |
area := each default.
Areas at: aSymbol put: area.
^ area
].
].
]
^ nil
]
LogArea class >> default [
<category: 'accessing'>
^ self subclassResponsibility
]
name [
LogArea class >> areaName [
<category: 'accessing'>
^ self subclassResponsibility
]
LogArea class >> areaDescription [
<category: 'accessing'>
^ self subclassResponsibility
]
@ -159,41 +153,88 @@ Object subclass: LogArea [
]
]
Object subclass: LogConfig [
Object subclass: LogTarget [
| areas |
<category: 'osmo-logging-core'>
<comment: 'I handle the config, the backends, the log areas, the default level'>
<comment: 'I will filter and then output the log message'>
Config := LogConfig new.
LogConfig class >> default [
areas [
<category: 'accessing'>
areas ifNil: [
areas := Dictionary new.
].
^ Config
^ areas
]
findArea: anArea [
<category: 'private'>
"Find anArea, or ask for a default"
^ (self areas) at: anArea ifAbsent: [
| area |
area := LogArea defaultForArea: anArea.
area ifNotNil: [
(self areas) at: anArea put: area.
].
area.
].
]
handle: anEntry ifTrue: aBlock [
<category: 'private'>
| area |
area := self findArea: anEntry area.
(area enabled and: [anEntry level >= area minLevel]) ifTrue: aBlock
]
log: anEntry [
<category: 'log'>
self handle: anEntry ifTrue: [
self print: anEntry.
]
]
print: anEntry [
<category: 'log'>
self subclassResponsibility.
]
]
LogTarget subclass: LogTranscriptTarget [
<category: 'osmo-logging-target'>
<comment: 'I log to the Transcript buffer'>
print: anEntry [
<category: 'log'>
Transcript show: anEntry msg; nl.
]
]
Object subclass: LogManager [
| target |
<category: 'osmo-logging-core'>
<comment: 'I handle the actual log invocation'>
Log := LogManager new.
Log := nil.
LogManager class >> default [
<category: 'instance'>
Log ifNil: [
Log := LogManager new.
Log target: LogTranscriptTarget new.
].
^ Log
]
log: message source: anObject area: anArea level: anLevel [
<category: 'log'>
| area |
log: anEntry [
target log: anEntry.
]
area := LogArea findArea: anArea.
(area enabled and: [anLevel >= area minLevel])
ifTrue: [
Transcript show: message; nl.
].
target: aTarget [
target := aTarget.
]
]
Eval [
]