MiniLogger.st
author Claus Gittinger <cg@exept.de>
Thu, 13 Dec 2012 15:29:36 +0100
changeset 14580 b9514d8a5211
parent 13810 ce0b6a1fc5cb
child 14881 28ba52b80aa7
child 18011 deb0c3355881
permissions -rw-r--r--
class: ProjectDefinition class definition moved the loadDirectory to the attributes, to prevent major incompatibilies when loading old class libs

"
 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:''
	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:'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: #debug 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: #debug 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__()"

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

    Stderr nextPut:$(.
    Timestamp now printOn:Stderr format:'%(year)-%(mon)-%(day) %h:%m:%s'.
    Stderr nextPut:$).
    Stderr space.
    Stderr nextPutAll: message.
    Stderr cr.

    "
        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
    ^ '$Header: /cvs/stx/stx/libbasic/MiniLogger.st,v 1.1 2011-10-31 16:06:38 vrany Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic/MiniLogger.st,v 1.1 2011-10-31 16:06:38 vrany Exp $'
!

version_SVN
    ^ '§Id: MiniLogger.st 10688 2011-09-15 11:05:35Z vranyj1 §'
! !

MiniLogger initialize!