GnuplotGraphView.st
author Claus Gittinger <cg@exept.de>
Mon, 30 Apr 2018 23:26:28 +0200
changeset 5750 78ef41988e39
parent 5742 5a4a11ee0b1f
child 5754 e2ff55aff529
permissions -rw-r--r--
#FEATURE by cg class: GnuplotGraphView added: #redrawX:y:width:height: #showWarning #sizeChanged: changed: #generateImage

"{ Encoding: utf8 }"

"{ Package: 'stx:libwidg2' }"

"{ NameSpace: Smalltalk }"

ImageView subclass:#GnuplotGraphView
	instanceVariableNames:'script data title'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Misc'
!

!GnuplotGraphView class methodsFor:'documentation'!

documentation
"
    displays the graph of the data (in model) using a gnuplot script

    [author:]
        cg

    [instance variables:]

    [class variables:]

    [see also:]

"
!

examples
"
 Notice that everything between [exBegin] and [exEnd] is extracted by the html-doc generator
 to create nicely formatted and clickable executable examples in the generated html-doc.
 (see the browsers class-documentation menu items for more)

 trying the widget as standAlone view:
                                                        [exBegin]
    GnuplotGraphView new 
        script:(GnuplotGraphView defaultScript);
        model:(ValueHolder with:(Random new next:100));
        open
                                                        [exEnd]

 embedded in another view:
                                                        [exBegin]
    |top v|

    top := StandardSystemView new.
    top extent:300@300.
    v := GnuplotGraphView new.
    v origin:10@10 corner:150@150.
    top add:v.
    top open
                                                        [exEnd]
"
! !

!GnuplotGraphView class methodsFor:'defaults'!

defaultScript
    "return a default initial gnuplot script"

    ^ self defaultScriptForHistogram
!

defaultScriptForHistogram
    "a default initial gnuplot script to show a histogram"

    ^ '
set term %(outputFormat)
set output "%(outputFile)"
set title "%(title)"
plot [-10:110] ''%(data)'' with histogram 
'
! !

!GnuplotGraphView methodsFor:'accessing'!

data
    ^ data
!

data:something
    data := something.
!

script
    ^ script
!

script:something
    script := something.
!

title
    ^ title
!

title:something
    title := something.
! !

!GnuplotGraphView methodsFor:'drawing'!

generateDataFileIn:aDirectory
    "the format of data expected by gnuplot depends on the type of plot:
        regular plot: a number of values (each in a separate line)
        multiCol plots: a number of lines, each containing a row
     here, handle common situations;
     however, if the data does not match, the program should have prepared the 
     data into a string and present it as such.
     Strings will be sent as-is to the file"

    |dataFilename printRow|

    dataFilename := (Filename newTemporaryIn:aDirectory) pathName.
    dataFilename := dataFilename asFilename withSuffix:'dat'.

    (data isString or:[data isByteArray]) ifTrue:[
        dataFilename contents:data.
        ^ dataFilename.
    ].

    data isCollection ifFalse:[
        dataFilename contents:data printString.
        ^ dataFilename.
    ].

    printRow := 
        [:s :eachValueOrRow |
            eachValueOrRow isString ifTrue:[
                s nextPutAll:eachValueOrRow
            ] ifFalse:[
                eachValueOrRow isAssociation ifTrue:[
                    eachValueOrRow key printOn:s.
                    s space.
                    eachValueOrRow value printOn:s.
                ] ifFalse:[
                    eachValueOrRow isCollection ifTrue:[
                        eachValueOrRow 
                            do:[:element | element printOn:s]
                            separatedBy:[ s space]
                    ] ifFalse:[
                        eachValueOrRow printOn:s
                    ].
                ].
            ].
            s cr.
    ].

    dataFilename writingFileDo:[:s |
        data isSequenceable ifTrue:[
            data do:[:eachValueOrRow |
                printRow value:s value:eachValueOrRow.
            ].
        ] ifFalse:[
            data keysAndValuesDo:[:eachKey :eachValueOrRow |
                eachKey printOn:s.
                s space.
                printRow value:s value:eachValueOrRow.
            ].
        ].
    ].
    ^ dataFilename
!

generateImage
    "
     self new
        script:(GnuplotGraphView defaultScript);
        data:(RandomGenerator new next:50);
        open
    "
    |scriptUsed command tmpDir outStream errorStream statusCode ok
     dataFilename scriptFilename outFilename argsDict expandedScript
     stdout stderr|

    (scriptUsed := script) isNil ifTrue:[
        scriptUsed := self class defaultScript.
    ].

    command := 'gnuplot "%1"'.
    argsDict := Dictionary new.

    tmpDir := Filename tempDirectory.

    data notEmptyOrNil ifTrue:[
        dataFilename := self generateDataFileIn:tmpDir.
    ] ifFalse:[
        dataFilename := ''.
    ].

    outFilename := (Filename newTemporaryIn:tmpDir) withSuffix:'png'.

    argsDict at:'data' put:dataFilename.
    argsDict at:'dataSize' put:(data size).
    argsDict at:'outputFile' put:(outFilename pathName).
    argsDict at:'outputFormat' put:'png'.
    argsDict at:'title' put:(title ? '').

    expandedScript := scriptUsed bindWithArguments:argsDict.
    scriptFilename := (Filename newTemporaryIn:tmpDir).
    scriptFilename := scriptFilename asFilename withSuffix:'gnuplot'.
    scriptFilename contents:expandedScript.

    command := command bindWith:(scriptFilename pathName).

    outStream := '' writeStream.
    errorStream := '' writeStream.

    ok := OperatingSystem 
        executeCommand:command
        inputFrom:Stdin
        outputTo:outStream
        errorTo:errorStream
        environment:nil
        inDirectory:tmpDir
        lineWise:true
        showWindow:false
        onError:[:status | 
            statusCode := status code.
            ok := false.
        ].

    ok ifFalse:[
        (stderr := errorStream contents) notEmptyOrNil ifTrue:[
            Transcript showCR:(stderr withColor:Color red).
        ].
    ].
    (stdout := outStream contents) notEmpty ifTrue:[
        Transcript showCR:stdout.
    ].

    image := Image fromFile:outFilename.
!

generateMagnifiedImage
    image isNil ifTrue:[
        self generateImage  
    ].
    super generateMagnifiedImage.
!

redrawX:x y:y width:w height:h
    (OperatingSystem canExecuteCommand:'gnuplot') ifFalse:[
        self clearRectangleX:x y:y width:w height:h.
        self showWarning.
        ^ self.
    ].
    super redrawX:x y:y width:w height:h.
!

showWarning
    |infoMsg wString|

    infoMsg := resources string:'No gnuplot command found'.
    wString := gc font widthOf:infoMsg.
    gc displayString:infoMsg x:(self width - wString) // 2 y:(self height // 2).
!

sizeChanged:how
    super sizeChanged:how.
    self invalidate.
! !

!GnuplotGraphView class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !