MiniLogger.st
branchjv
changeset 20579 9add81aadb7a
parent 20578 39641ba8d6e0
parent 20529 e026fd505d16
child 20727 fb8c5591428b
--- a/MiniLogger.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/MiniLogger.st	Sun Oct 09 21:28:18 2016 +0100
@@ -16,7 +16,8 @@
 Object subclass:#MiniLogger
 	instanceVariableNames:''
 	classVariableNames:'ALL DEBUG ENTER ERROR FATAL INFO Instance LEAVE NONE Severities
-		TRACE TRACE0 TRACE1 TRACE2 TRACE3 Threshold WARN WARNING'
+		TRACE TRACE0 TRACE1 TRACE2 TRACE3 Threshold WARN WARNING
+		LogOnTranscript LogOnStderr LogFormat TimestampFormat'
 	poolDictionaries:''
 	category:'System-Debugging-Support'
 !
@@ -47,13 +48,27 @@
 documentation
 "   
     A very simple logger for Smalltalk/X. This one is always present.
-    All `Transcript show: 'Processor [info]: xxx' should be rewritten
-    using Logger.
+    It mimics the protocol of the loggers found in stx:goodies/loggia,
+    which can be activated by setting the global 'Logger' to an instance of
+    on of them.
+    
+    All 
+        `Transcript show: 'Processor [info]: xxx' 
+    should be rewritten over time to use the Logger.
 
+    'Object infoPrint' and 'Object debugPrint' have been changed to
+    forward their message to the global 'Logger' unless nil.
+    
     Usage:
+        Logger info: 'Hello world'.
+        Logger debug: 'Hello world'.
+        Logger warning: 'Hello world'.
+        Logger error: 'Hello world'.
 
-        Logger info: 'Hello worlds'.
-
+    to disable logging:
+        MiniLogger logOnTranscript:false.
+        MiniLogger logOnStderr:false.
+        
     For more examples, see #examples.
 
     [author:]
@@ -143,6 +158,100 @@
     "Modified: / 13-08-2014 / 14:36:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!MiniLogger class methodsFor:'accessing-log format'!
+
+logFormat
+    "will be used for the log message as:
+        %1 [%2] (%3): %4
+    with %1: facility (area)
+    with %2: secerity (area)
+    with %3: timestamp 
+    with %4: caller/originator 
+    with %5: message"
+    
+    ^ LogFormat ? '%1 [%2] (%3): %5'
+
+    "
+     MiniLogger logFormat:'%1 [%2]: %5'.
+     'hello' errorPrintCR.
+     MiniLogger logFormat:'%3 %1 [%2]: %5'.
+     'hello' errorPrintCR.
+     MiniLogger logFormat:nil.
+     'hello' errorPrintCR.
+    "
+!
+
+logFormat:aFormatString
+    "will be used for the log message as:
+        %1 [%2] (%3): %4
+            with %1: facility (area)
+            with %2: secerity (area)
+            with %3: timestamp 
+            with %4: caller/originator 
+            with %5: message.
+     Pass anil argument to return to the default format.        
+    "
+    
+    LogFormat := aFormatString
+
+    "
+     MiniLogger logFormat:'%1 [%2]: %5'.
+     'hello' errorPrintCR.
+     MiniLogger logFormat:'%3 %1 [%2]: %5'.
+     'hello' errorPrintCR.
+     MiniLogger logFormat:nil.
+     'hello' errorPrintCR.
+    "
+!
+
+logOnStderr 
+    ^ LogOnStderr ? true
+!
+
+logOnStderr:aBoolean
+    "enable/disable loggin on stderr"
+    
+    LogOnStderr := aBoolean
+
+    "
+     MiniLogger logOnStderr:false
+     MiniLogger logOnTranscript:false
+
+     MiniLogger logOnStderr:true
+     MiniLogger logOnTranscript:true
+    "
+!
+
+logOnTranscript
+    ^ LogOnTranscript ? true
+!
+
+logOnTranscript:aBoolean
+    "enable/disable loggin on the Transcript"
+
+    LogOnTranscript := aBoolean
+
+    "
+     MiniLogger logOnStderr:false
+     MiniLogger logOnTranscript:false
+
+     MiniLogger logOnStderr:true
+     MiniLogger logOnTranscript:true
+    "
+!
+
+timestampFormat
+    "will be used for the log message"
+    
+    ^ TimestampFormat ? '%(year)-%(mon)-%(day) %h:%m:%s.%i'.
+!
+
+timestampFormat:aTimestampFormatString
+    "will be used for the log message"
+    
+    TimestampFormat := aTimestampFormatString
+! !
+
 !MiniLogger class methodsFor:'accessing-severities'!
 
 severityDEBUG
@@ -317,6 +426,8 @@
 
     | severityXlated messageXlated |
 
+    (self logOnStderr or:[self logOnTranscript]) ifFalse:[^ self].
+
     severityXlated := severity.
 
     "/ Be backward compatible, allow for symbolic severities
@@ -362,9 +473,13 @@
     severityXlated value < Threshold value ifTrue:[ ^ self ].
     messageXlated := message value asString.
 
-    self log: messageXlated severity: severityXlated facility: facility originator: originator attachment: attachment on:Stderr.
-    (Transcript isView) ifTrue:[ 
-        self log: messageXlated severity: severityXlated facility: facility originator: originator attachment: attachment on:Transcript
+    self logOnStderr ifTrue:[
+        self log: messageXlated severity: severityXlated facility: facility originator: originator attachment: attachment on:Stderr.
+    ].
+    self logOnTranscript ifTrue:[
+        (Transcript isView) ifTrue:[ 
+            self log: messageXlated severity: severityXlated facility: facility originator: originator attachment: attachment on:Transcript
+        ].
     ].
 
     "
@@ -747,15 +862,15 @@
 log: message severity: severity facility: facilityArg originator: originator attachment: attachment on:aStream
     "Pricipal logging method. This mimics VM __stxLog__()"
 
-    | facility severityName messageProperlyEncoded words|
+    |facility severityName messageProperlyEncoded words messageAsSent|
 
     facility := facilityArg.
     messageProperlyEncoded := message.
     severityName := severity name.
-    
+
     "/ If the message is Unicode 16/32 string and stream is external,
-    "/ we have to recode the message using locale-specific encoding 
-    (message isWideString and:[ aStream isExternalStream ]) ifTrue:[ 
+    "/ we have to recode the message using locale-specific encoding
+    (message isWideString and:[ aStream isExternalStream ]) ifTrue:[
         OperatingSystem isMSWINDOWSlike ifTrue:[
             messageProperlyEncoded := message utf8Encoded.
         ] ifFalse:[
@@ -763,7 +878,7 @@
         ]
     ].
     messageProperlyEncoded := messageProperlyEncoded withoutSeparators.
-    
+
     "/ hack to allow calls from infPrint/errorPrint.
     "/ if this is an oldStyle infoPrint or errorPrint, do not append another facility and severity
     words := message asCollectionOfWords.
@@ -780,23 +895,23 @@
             messageProperlyEncoded := (messageProperlyEncoded copyFrom:2) withoutSeparators.
         ].
     ].
-    
+    messageAsSent := (self logFormat
+                bindWith:(facility ? 'STX')
+                with:severityName
+                with:(Timestamp now printStringFormat:(self timestampFormat))
+                with:originator printString
+                with:messageProperlyEncoded).
+    aStream isView ifFalse:[
+        messageAsSent := messageAsSent string utf8Encoded
+    ].
+
     "/ Timestamp now printOn:aStream format:'%(year)-%(mon)-%(day) %h:%m:%s.%i'.
     "/ aStream space.
-    aStream
-        nextPutAll: facility ? 'STX';
-        nextPutAll:' [';
-        nextPutAll: severityName;
-        nextPutAll:']'.
-
-    aStream nextPutAll:' ('.
-    Timestamp now printOn:aStream format:'%(year)-%(mon)-%(day) %h:%m:%s.%i'.
-    aStream nextPutAll:'): '.
-
-    aStream nextPutAll: messageProperlyEncoded.
-    aStream cr.
+    aStream nextPutLine: messageAsSent
 
     "
+     'hello' infoPrintCR.
+
      Logger log:'test message' severity: #debug facility: 'TEST'
      Logger log:'test message' severity: #info facility: 'TEST'
      Logger log:'test message' severity: #warning facility: 'TEST'