GnuplotGraphView.st
author Claus Gittinger <cg@exept.de>
Fri, 15 Jun 2018 10:54:35 +0200
changeset 5816 7876c07931a7
parent 5781 38948bac30f3
child 6127 051421a27b60
permissions -rw-r--r--
#DOCUMENTATION by cg class: ComboListView class comment/format in: #documentation

"{ Encoding: utf8 }"

"{ Package: 'stx:libwidg2' }"

"{ NameSpace: Smalltalk }"

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

!GnuplotGraphView class methodsFor:'documentation'!

documentation
"
    displays the graph of the data (in model) using a gnuplot script
    Now also shown in the collection-inspector tab.

    [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 (with a fix script):
                                                        [exBegin]
    GnuplotGraphView new 
        script:(GnuplotGraphView defaultScript);
        model:(ValueHolder with:(Random new next:100));
        adjust:#smoothFit;
        extent:400@300;
        open
                                                        [exEnd]

 trying the widget as standAlone view (with no fix script):
                                                        [exBegin]
    GnuplotGraphView new 
        model:(ValueHolder with:(Random new next:100));
        adjust:#smoothFit;
        extent:300@200;
        open
                                                        [exEnd]

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

    top := StandardSystemView new.
    top extent:300@300.
    v := GnuplotGraphView new.  
    v data:(Random new next:100).
    v origin:0.0@0.0 corner:1.0@1.0.
    top add:v.
    top open
                                                        [exEnd]
 use as inspect tab:
                                                        [exBegin]
    (Random new next:100) inspect.
                                                        [exEnd]
"
! !

!GnuplotGraphView class methodsFor:'defaults'!

defaultScript
    "return a default initial gnuplot script"

    ^ self defaultScriptForHistogram
!

defaultScriptForDots
    "a default initial gnuplot script to show a dots diagram"

    ^ '
set term %(outputFormat) size %(width),%(height)
set output "%(outputFile)"
set title "%(title)"
set nokey
plot [-10:110] ''%(data)''
'

    "Modified: / 31-05-2018 / 11:54:43 / Claus Gittinger"
!

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

    ^ '
set term %(outputFormat) size %(width),%(height) 
set output "%(outputFile)"
set title "%(title)"
set nokey
plot [-10:110] ''%(data)'' with histogram 
'

    "Modified: / 31-05-2018 / 11:54:47 / Claus Gittinger"
!

defaultScriptForLines
    "a default initial gnuplot script to show a line diagram"

    ^ '
set term %(outputFormat) size %(width),%(height) 
set output "%(outputFile)"
set title "%(title)"
set nokey
plot ''%(data)'' with lines 
'

    "Modified: / 31-05-2018 / 11:54:52 / Claus Gittinger"
! !

!GnuplotGraphView class methodsFor:'menu specs'!

middleButtonMenuExtraSlice
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."


    "
     MenuEditor new openOnClass:GnuplotGraphView andSelector:#middleButtonMenuExtraSlice
     (Menu new fromLiteralArrayEncoding:(GnuplotGraphView middleButtonMenuExtraSlice)) startUp
    "

    <resource: #menu>

    ^ 
     #(Menu
        (
         (MenuItem
            label: '-'
          )
         (MenuItem
            enabled: hasNoScript
            label: 'Histogram'
            hideMenuOnActivated: false
            choice: formatHolder
            choiceValue: histogram
          )
         (MenuItem
            enabled: hasNoScript
            label: 'Line Graph'
            hideMenuOnActivated: false
            choice: formatHolder
            choiceValue: lines
          )
         (MenuItem
            enabled: hasNoScript
            label: 'Dots'
            hideMenuOnActivated: false
            choice: formatHolder
            choiceValue: dots
          )
         )
        nil
        nil
      )
! !

!GnuplotGraphView methodsFor:'accessing'!

adjust:layoutSymbol
    image := nil.
    super adjust:layoutSymbol.
    self invalidate
!

data
    ^ data
!

data:something
    data := something.
!

hasNoScript
    ^ [ script isEmptyOrNil ]
!

hasScript
    ^ [ script notEmptyOrNil ]
!

magnificationFactor:aNumber
    image := nil.
    super magnificationFactor:aNumber.
    self invalidate
!

script
    ^ script
!

script:something
    script := something.
!

title
    ^ title
!

title:something
    title := something.
! !

!GnuplotGraphView methodsFor:'aspects'!

formatHolder
    formatHolder isNil ifTrue:[
        formatHolder := #histogram asValue.
        formatHolder onChangeSend:#formatChanged to:self.
    ].
    ^ formatHolder
! !

!GnuplotGraphView methodsFor:'defaults'!

defaultScript
    |format|

    format := self formatHolder value.
    format == #histogram ifTrue:[
        ^ self class defaultScriptForHistogram
    ].
    format == #lines ifTrue:[
        ^ self class defaultScriptForLines
    ].
    format == #dots ifTrue:[
        ^ self class defaultScriptForDots
    ].
    ^ self class defaultScript
! !

!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
    "generates the magnifiedImage right away

     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 defaultScript.
    ].

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

    tmpDir := Filename tempDirectory.
    [
        data notEmptyOrNil ifTrue:[
            dataFilename := self generateDataFileIn:tmpDir.
        ] ifFalse:[
            dataFilename := nil.
        ].

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

        argsDict at:'data' put:(dataFilename isNil ifTrue:[''] ifFalse:[dataFilename baseName]).
        argsDict at:'dataSize' put:(data size).
        argsDict at:'outputFile' put:(outFilename baseName).
        argsDict at:'outputFormat' put:'png'.
        argsDict at:'title' put:(title ? '').
        ((adjustHolder value ? '') includesString:'fit') not
        ifTrue:[
            argsDict at:'width' put:(640 * (self magnificationFactor)).
            argsDict at:'height' put:(400 * (self magnificationFactor)).
        ] ifFalse:[
            argsDict at:'width' put:self width.
            argsDict at:'height' put:self height.
        ].
        expandedScript := scriptUsed bindWithArguments:argsDict.
        scriptFilename := (Filename newTemporaryIn:tmpDir).
        scriptFilename := scriptFilename asFilename withSuffix:'gnuplot'.
        scriptFilename contents:expandedScript.

        command := command bindWith:(scriptFilename baseName).

        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).
            ].
        ] ifTrue:[
            (stdout := outStream contents) notEmpty ifTrue:[
                Transcript showCR:stdout.
            ].
            image := Image fromFile:outFilename.
        ].
    ] ensure:[
        dataFilename notNil ifTrue:[ dataFilename remove ]. 
        outFilename notNil ifTrue:[ outFilename remove ]. 
        scriptFilename notNil ifTrue:[ scriptFilename remove ]. 
    ].
!

generateMagnifiedImage
    image isNil ifTrue:[
        self generateImage  
    ].
    magnifiedImage := smoothMagnifiedImage := image.
"/    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.
!

updateImageAfterSizeChange
    image := nil.
    super updateImageAfterSizeChange
! !

!GnuplotGraphView methodsFor:'menu'!

smoothFitBigMenuItemVisible
    ^ false
!

smoothingMenuItemVisible
    ^ false
! !

!GnuplotGraphView methodsFor:'menu actions'!

formatChanged
    image := magnifiedImage := smoothMagnifiedImage := nil.
    self invalidate
! !

!GnuplotGraphView methodsFor:'mvc'!

updateFromModel
    "the model changes, set my image"

    self data:model value.
! !

!GnuplotGraphView class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !