sindre-0.1: A programming language for simple GUIs

Portabilityportable
Stabilityprovisional

Sindre.Sindre

Contents

Description

General definitions for the Sindre programming language. The documentation for this module does not include a description of the language semantics.

Synopsis

Screen layout

data Rectangle Source

A rectangle represented as its upper-left corner, width and height. You should never create rectangles with negative dimensions, and the functions in this module make no guarantee to their behaviour if you do.

Constructors

Rectangle 

data DimNeed Source

A size constraint in one dimension.

Constructors

Min Integer

At minimum this many pixels.

Max Integer

At most this many pixels.

Unlimited

As many or as few pixels as necessary.

Exact Integer

Exactly this many pixels.

type SpaceNeed = (DimNeed, DimNeed)Source

Size constraints in both dimensions.

type SpaceUse = [Rectangle]Source

The amount of space actually used by a widget.

type Constraints = ((Maybe Integer, Maybe Integer), (Maybe Integer, Maybe Integer))Source

Externally-imposed optional minimum and maximum values for width and height.

data Align Source

Instruction on how to align a smaller interval within a larger interval.

Constructors

AlignNeg

Align towards negative infinity.

AlignPos

Align towards positive infinity.

AlignCenter

Align towards the center of the interval.

Instances

Layouting functions

constrainNeed :: SpaceNeed -> Constraints -> SpaceNeedSource

constrainNeed need constraints reduces the space requirement given by need in order to fulfill constraints.

fitRect :: Rectangle -> SpaceNeed -> RectangleSource

fitRect rect need yields a rectangle as large as possible, but no larger than rect, that tries to fulfill the constraints need.

splitHoriz :: Rectangle -> [DimNeed] -> [Rectangle]Source

splitHoriz rect dims splits rect horizontally into a number of non-overlapping equal-width rectangles stacked on top of each other. dims is a list of height requirements that the function will attempt to fulfill as best it is able. The union of the list of returned rectangles will always be equal to rect. No rectangle will ever have negative dimensions.

splitVert :: Rectangle -> [DimNeed] -> [Rectangle]Source

As splitHoriz, but splits vertically instead of horizontally, so the rectangles will be next to each other.

rectTranspose :: Rectangle -> RectangleSource

Flip the x and y coordinates and width and height of a rectangle, in a sense rotating it ninety degrees. Note that rectTranspose . rectTranspose = id.

align :: Integral a => Align -> a -> a -> a -> aSource

align a lower x upper, where lower<=upper, aligns a subinterval of length x in the interval lower to upper, returning the coordinate at which the aligned subinterval starts. For example,

>>> align AlignCenter 2 4 10
4
>>> align AlignNeg 2 4 10
2
>>> align AlignPos 2 4 10
6

adjustRect :: (Align, Align) -> Rectangle -> Rectangle -> RectangleSource

adjustRect (walign, halign) bigrect smallrect returns a rectangle with the same dimensions as smallrect aligned within bigrect in both dimensions.

Keyboard Input

data KeyModifier Source

A keyboard modifier key. The precise meaning (and location) of these is somewhat platform-dependent. Note that the Shift modifier should not be passed along if the associated key is a CharKey, as Shift will already have been handled.

Constructors

Control 
Meta 
Super 
Hyper 
Shift 

data Key Source

Either a key corresponding to a visible character, or a control key not associated with any character.

Constructors

CharKey Char

Unicode character associated with the key.

CtrlKey String

Name of the control key, using X11 key names (for example BackSpace or Return).

Instances

type Chord = (Set KeyModifier, Key)Source

A combination of a set of modifier keys and a primary key, representing a complete piece of keyboard input.

Input positions

data P a Source

Wrap a value with source position information.

Constructors

P 

Fields

sourcePos :: SourcePos
 
unP :: a
 

Instances

Functor P 
Eq a => Eq (P a) 
Ord a => Ord (P a) 
Show a => Show (P a) 

at :: a -> P b -> P aSource

x at y gives a value containing x, but with the same source position as y.

type SourcePos = (String, Int, Int)Source

A position in a source file, consisting of a file name, one-indexed line number, and one-indexed column number.

nowhere :: SourcePosSource

A default position when no other is available.

position :: SourcePos -> StringSource

Prettyprint a source position in a human-readable form.

>>> position ("foobar.sindre", 5, 15)
"foobar.sindre:5:15: "

Abstract syntax tree

type Identifier = StringSource

The type of names (such as variables and classes) in the syntax tree.

data Stmt Source

The syntax of Sindre statements.

Constructors

Print [P Expr] 
Exit (Maybe (P Expr)) 
Return (Maybe (P Expr)) 
Next 
If (P Expr) [P Stmt] [P Stmt] 
While (P Expr) [P Stmt] 
For (P Expr) (P Expr) (P Expr) [P Stmt] 
Do [P Stmt] (P Expr) 
Break 
Continue 
Expr (P Expr) 
Focus (P Expr) 

Instances

type ObjectNum = IntSource

Low-level reference to an object.

type ObjectRef = (ObjectNum, Identifier, Maybe Identifier)Source

High-level reference to an object, containing its class and name (if any) as well. For non-widgets, the object name is the same as the object class.

type WidgetRef = ObjectRefSource

High-level reference to a widget.

Value representation

data Value Source

Dynamically typed run-time value in the Sindre language.

string :: String -> ValueSource

string s returns a Sindre string.

true :: Value -> BoolSource

true v returns True if v is interpreted as a true value in Sindre, False otherwise.

truth, falsity :: ValueSource

Canonical false value, see true.

Canonical true value, see true.

Program structure

data Event Source

Something that happened in the world.

Constructors

KeyPress Chord 
NamedEvent 

Fields

eventName :: Identifier

The name of the event.

eventValue :: [Value]

The payload of the event.

eventSource :: EventSource

Where it's from.

Instances

data EventSource Source

The origin of an event. This is used when determining where to handle it.

Constructors

FieldSrc ObjectRef Identifier

FieldSrc obj f designates that the source of the event is the property f of obj

ObjectSrc ObjectRef

The source is the given object.

BackendSrc

The source is something within the bowels of the active backend, probably from the external world.

Instances

data SourcePat Source

Description of sets of sources, values of this type can be used to pattern-match EventSources.

Constructors

NamedSource Identifier (Maybe Identifier)

For NamedSource k fk, the source must be the object named k. If fk is Just fk', the source must also be the field named fk'.

GenericSource Identifier Identifier (Maybe Identifier)

For GenericSource cn k fk, the source must be of class cn. If fk is Just fk', the source must also be the field named fk'. The variable named k should be bound to the actual object if this pattern matches.

data Pattern Source

A description of an event used to indicate how to handle different events.

Constructors

ChordPattern Chord

Match if the event is a chord.

OrPattern Pattern Pattern

Match if either pattern matches.

SourcedPattern

SourcedPattern src ev vars matches if src matches the event source (see SourcePat) an ev matches the event name. vars should be bound to the values in the payload of the event.

data Action Source

Reaction to an event.

Constructors

StmtAction [P Stmt]

Execute these statements.

Instances

data Function Source

A function consists of lexically bound parameters and a body.

Constructors

Function [Identifier] [P Stmt] 

Instances

data GUI Source

A Sindre GUI is a recursive tree, with each node representing a single widget and consisting of the following fields.

Constructors

GUI 

Fields

widgetName :: Maybe Identifier

Name of the widget, if any.

widgetClass :: P Identifier

Class of the widget.

widgetArgs :: WidgetArgs

The arguments passed to the widget.

widgetChildren :: [(Maybe (P Expr), GUI)]

Children of the widget, if any.

Instances

data Program Source

A complete Sindre program. Note that this is intentionally defined such that some invalid programs, like those with duplicate definitions can be represented - the compiler (see Sindre.Compiler) should detect and handle such errors.

Constructors

Program 

type SindreOption = OptDescr (Arguments -> Arguments)Source

A command line argument.

type Arguments = Map String StringSource

The arguments passed to the Sindre program from the command line.