MiniLogger.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 20 Jul 2012 14:32:04 +0100
branchjv
changeset 17954 dc18846aa7b2
parent 17926 2b7976260ae3
child 18011 deb0c3355881
permissions -rw-r--r--
Fixes in log:severity: and log:severity:attachment:

"
 COPYRIGHT (c) 2006 by eXept Software AG
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic' }"

Object subclass:#MiniLogger
	instanceVariableNames:'stream'
	classVariableNames:'Instance'
	poolDictionaries:''
	category:'System-Debugging-Support'
!

!MiniLogger class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2006 by eXept Software AG
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
! !

!MiniLogger class methodsFor:'instance creation'!

instance

    Instance isNil ifTrue:[Instance := self basicNew].
    ^Instance

    "Created: / 14-09-2011 / 21:28:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

new

    Logger log: 'Do not use MiniLogger new, use #instance instead' severity: #warn facility: 'STX'.
    ^self instance

    "Created: / 14-09-2011 / 21:27:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MiniLogger class methodsFor:'class initialization'!

initialize

    (Smalltalk at:#Logger) isNil ifTrue:[Smalltalk at:#Logger put: self instance].

    "Created: / 01-09-2011 / 12:26:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MiniLogger methodsFor:'initialization'!

initializeStream

    Stderr isOpen ifTrue:[
        stream := Stderr.        
        ^self.
    ].
    Stdout isOpen ifTrue:[
        stream := Stdout.
        ^self.
    ].
    stream := 'smalltalkx.log' asFilename writeStream.

    "Created: / 10-12-2011 / 00:11:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MiniLogger methodsFor:'logging'!

facilityOf: originator

    ^originator class 
        perform: #logFacility
        ifNotUnderstood: [
            | pkg |
            pkg := originator class package.
            (pkg startsWith: 'stx') ifTrue:[
                'STX'
            ] ifFalse:[
                pkg copyFrom: ((pkg lastIndexOf: $:) + 1)
            ]
        ]

    "
        Logger facilityOf: Object
        Logger facilityOf: Expecco::Browser
    "

    "Created: / 15-09-2011 / 10:20:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message

    self log: message severity: #debug

    "Created: / 15-09-2011 / 10:27:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message facility: facility

    self log: message severity: #debug facility: facility

    "Created: / 14-09-2011 / 21:22:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message severity: severity

    self log: message severity: severity originator: thisContext sender receiver

    "Created: / 15-09-2011 / 10:25:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message severity: severity attachment: attachment

    | originator |
    originator := thisContext sender receiver.

    self log: message severity: severity facility: (self facilityOf: originator) originator: originator attachment: attachment

    "Created: / 15-09-2011 / 11:47:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message severity: severity facility: facility

    self log: message severity: severity facility: facility originator: thisContext sender receiver

    "Created: / 14-09-2011 / 21:20:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message severity: severity facility: facility originator: originator

    self log: message severity: severity facility: facility originator: originator attachment: nil

    "Created: / 14-09-2011 / 21:20:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message severity: severity facility: facility originator: originator attachment: attachment
    "Pricipal logging method. This mimics VM __stxLog__()"

    | ts |

    stream isNil ifTrue:[self initializeStream].

    stream
        nextPutAll: facility ? 'STX';
        space;
        nextPut:$[;
        nextPutAll: severity;
        nextPut:$];
        space.

    stream nextPut:$(.

    "Ugly code but much faster"
    ts := Timestamp now.
    (ts year - 2000) printOn: stream.
    stream nextPut: $-.
    ts month printOn: stream base: 10 size:2 fill:$0.
    stream nextPut: $-.
    ts day printOn: stream base: 10 size:2 fill:$0.
    stream space.
    ts hour printOn: stream base: 10 size:2 fill:$0.
    stream nextPut: $:.
    ts minute printOn: stream base: 10 size:2 fill:$0.
    stream nextPut: $:.
    ts second printOn: stream base: 10 size:2 fill:$0.
    stream nextPut:$).

    stream space.
    stream nextPutAll: message.
    stream cr.
    stream flush.

    "
        Logger log:'test message' severity: #debug facility: 'TEST'
    "

    "Created: / 14-09-2011 / 21:18:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

log: message severity: severity originator: originator

    self log: message severity: #debug facility: (self facilityOf: originator) originator: originator

    "Created: / 15-09-2011 / 10:26:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MiniLogger class methodsFor:'documentation'!

version_SVN
    ^ '$Id: MiniLogger.st 10827 2012-07-20 13:32:04Z vranyj1 $'
! !

MiniLogger initialize!