[Haskell-cafe] Re: ANN: Thingie-0.80

Jeff Heard jefferson.r.heard at gmail.com
Thu Dec 18 17:45:57 EST 2008


Make that version 0.81 -- added in a module that exports all the other
modules except BasicUIState.

On Thu, Dec 18, 2008 at 5:12 PM, Jeff Heard <jefferson.r.heard at gmail.com> wrote:
> I need a better name for this, but I have software, so I shall release
> it with a dumb name.  Thingie has just been uploaded to hackage.  It
> is a library for creating 2D visualizations in a purely functional
> manner.  It supports static visualizations and animation, and like
> most vis libraries, can probably do games as well as simple viz
> graphics.  The backend uses Cairo for rendering, but I'm looking to
> port it to OpenGL/GLUT for systems where Gtk/Cairo is hard to get
> working (i.e. OS/X).  The idea is that you create a graph of objects
> or function that return objects and the library renders them for you
> in 2D.
>
> Right now, there's one thing I would like to add to the system above
> all other things:  The interactive system has the concept of a tracked
> program state that is threaded through the graph.  This state is
> defined by a UIState class, and any state (which is a record object)
> must be an instance of UIState and provide the system with a certain
> number of getters and setters for basic bits of state.  I would like
> to use Template Haskell to help create/derive these structures.  Does
> anyone on the list want to help with that?
>
> Here are two examples.  Each draws a smiley face, and the interactive
> one tracks your mouse with a little red ball.
> First the non-interactive:
>
> module Main where
>
> import Graphics.Rendering.Thingie.Primitives
> import Graphics.Rendering.Thingie.Cairo
> import qualified Graphics.Rendering.Cairo as Cairo
>
> smiley = Context [FillRGBA 0 0 0 0, Operator Cairo.OperatorClear] $
>                 Group [Draw rectangleFilled{ topleft=Point2D 0 0,
> width=200, height=200 }
>                       ,Context [FillRGBA 1 1 0 1, OutlineRGBA 0 0 0
> 1, Translate 100 100, Operator Cairo.OperatorOver] $
>                                Group [Draw arc{ radius=100, filled=True }
>                                      ,Context [FillRGBA 0 0 0 1] $
>                                               Group [Draw arc{
> center=Point2D (-33) (-33), radius=10, filled=True }
>                                                     ,Draw arc{
> center=Point2D   33  (-33), radius=10, filled=True }
>                                                     ,Draw arc{
> angle1=degrees 30, angle2=degrees 150, radius=70 }]]]
>
> main = renderObjectToPNG "smiley.png" 200 200 smiley
>
>
> -----
>
> Now the interactive:
>
>
> import Graphics.Rendering.Thingie.Interactive
> import Graphics.Rendering.Thingie.BasicUIState
> import Graphics.Rendering.Thingie.Cairo
> import Graphics.Rendering.Thingie.Primitives
>
> import qualified Graphics.Rendering.Cairo as Cairo
>
> smiley = Context [FillRGBA 0 0 0 0, Operator Cairo.OperatorClear] $
>                 Group [Draw rectangleFilled{ topleft=Point2D 0 0,
> width=200, height=200 }
>                       ,Context [FillRGBA 1 1 0 1, OutlineRGBA 0 0 0
> 1, Translate 100 100, Operator Cairo.OperatorOver] $
>                                Group [Draw arc{ radius=100, filled=True }
>                                      ,Context [FillRGBA 0 0 0 1] $
>                                               Group [Draw arc{
> center=Point2D (-33) (-33), radius=10, filled=True }
>                                                     ,Draw arc{
> center=Point2D   33  (-33), radius=10, filled=True }
>                                                     ,Draw arc{
> angle1=degrees 30, angle2=degrees 150, radius=70 }]]]
>
> undercursor uistate = Context [FillRGBA 1 0 0 1] $
>                              Draw arcFilled{ center=mousePosition
> uistate, radius=5 }
>
> scene = [StaticElement smiley (Rect2D 0 0 0 0)
>        ,UnboundedElement undercursor]
>
> main = simpleMotionSensitiveGui defaultBasicUIState scene "smiley face"
>


More information about the Haskell-Cafe mailing list