| License | MIT-style (see LICENSE) |
|---|---|
| Stability | provisional |
| Portability | portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Sindre.Sindre
Description
General definitions for the Sindre programming language. The documentation for this module does not include a description of the language semantics.
Synopsis
- data Rectangle = Rectangle {}
- data DimNeed
- type SpaceNeed = (DimNeed, DimNeed)
- type SpaceUse = [Rectangle]
- type Constraints = ((Maybe Integer, Maybe Integer), (Maybe Integer, Maybe Integer))
- data Align
- constrainNeed :: SpaceNeed -> Constraints -> SpaceNeed
- fitRect :: Rectangle -> SpaceNeed -> Rectangle
- splitHoriz :: Rectangle -> [DimNeed] -> [Rectangle]
- splitVert :: Rectangle -> [DimNeed] -> [Rectangle]
- rectTranspose :: Rectangle -> Rectangle
- align :: Integral a => Align -> a -> a -> a -> a
- adjustRect :: (Align, Align) -> Rectangle -> Rectangle -> Rectangle
- data KeyModifier
- data Key
- type Chord = (Set KeyModifier, Key)
- data P a = P {}
- at :: a -> P b -> P a
- type SourcePos = (String, Int, Int)
- nowhere :: SourcePos
- position :: SourcePos -> String
- type Identifier = String
- data Stmt
- data Expr
- = Literal Value
- | Var Identifier
- | FieldOf Identifier (P Expr)
- | Lookup (P Expr) (P Expr)
- | Not (P Expr)
- | LessThan (P Expr) (P Expr)
- | LessEql (P Expr) (P Expr)
- | Equal (P Expr) (P Expr)
- | Assign (P Expr) (P Expr)
- | PostInc (P Expr)
- | PostDec (P Expr)
- | Concat (P Expr) (P Expr)
- | Plus (P Expr) (P Expr)
- | Minus (P Expr) (P Expr)
- | Times (P Expr) (P Expr)
- | Divided (P Expr) (P Expr)
- | Modulo (P Expr) (P Expr)
- | RaisedTo (P Expr) (P Expr)
- | Funcall Identifier [P Expr]
- | Methcall (P Expr) Identifier [P Expr]
- | Cond (P Expr) (P Expr) (P Expr)
- type ObjectNum = Int
- type ObjectRef = (ObjectNum, Identifier, Maybe Identifier)
- type WidgetRef = ObjectRef
- data Value
- string :: String -> Value
- true :: Value -> Bool
- truth :: Value
- falsity :: Value
- data Event
- = KeyPress Chord
- | NamedEvent {
- eventName :: Identifier
- eventValue :: [Value]
- eventSource :: EventSource
- data EventSource
- data SourcePat
- data Pattern
- data Action = StmtAction [P Stmt]
- data Function = Function [Identifier] [P Stmt]
- data GUI = GUI {
- widgetName :: Maybe Identifier
- widgetClass :: P Identifier
- widgetArgs :: WidgetArgs
- widgetChildren :: [(Maybe (P Expr), GUI)]
- data Program = Program {
- programGUI :: (Maybe (P Expr), GUI)
- programActions :: [P (Pattern, Action)]
- programGlobals :: [P (Identifier, P Expr)]
- programOptions :: [P (Identifier, (SindreOption, Maybe Value))]
- programFunctions :: [P (Identifier, Function)]
- programBegin :: [P Stmt]
- type SindreOption = OptDescr (Arguments -> Arguments)
- type Arguments = Map String String
Screen layout
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 | |
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 Constraints = ((Maybe Integer, Maybe Integer), (Maybe Integer, Maybe Integer)) Source #
Externally-imposed optional minimum and maximum values for width and height.
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. |
Layouting functions
constrainNeed :: SpaceNeed -> Constraints -> SpaceNeed Source #
constrainNeed need constraints reduces the space requirement
given by need in order to fulfill constraints.
fitRect :: Rectangle -> SpaceNeed -> Rectangle Source #
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 -> Rectangle Source #
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 -> a Source #
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 104>>>align AlignNeg 2 4 102>>>align AlignPos 2 4 106
adjustRect :: (Align, Align) -> Rectangle -> Rectangle -> Rectangle Source #
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.
Instances
| Eq KeyModifier Source # | |
Defined in Sindre.Sindre | |
| Ord KeyModifier Source # | |
Defined in Sindre.Sindre Methods compare :: KeyModifier -> KeyModifier -> Ordering # (<) :: KeyModifier -> KeyModifier -> Bool # (<=) :: KeyModifier -> KeyModifier -> Bool # (>) :: KeyModifier -> KeyModifier -> Bool # (>=) :: KeyModifier -> KeyModifier -> Bool # max :: KeyModifier -> KeyModifier -> KeyModifier # min :: KeyModifier -> KeyModifier -> KeyModifier # | |
| Show KeyModifier Source # | |
Defined in Sindre.Sindre Methods showsPrec :: Int -> KeyModifier -> ShowS # show :: KeyModifier -> String # showList :: [KeyModifier] -> ShowS # | |
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 |
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
Wrap a value with source position information.
at :: a -> P b -> P a Source #
x gives a value containing at yx, 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.
position :: SourcePos -> String Source #
Prettyprint a source position in a human-readable form.
>>>position ("foobar.sindre", 5, 15)"foobar.sindre:5:15: "
Abstract syntax tree
type Identifier = String Source #
The type of names (such as variables and classes) in the syntax tree.
The syntax of Sindre statements.
The syntax of Sindre expressions.
Constructors
| Literal Value | |
| Var Identifier | |
| FieldOf Identifier (P Expr) | |
| Lookup (P Expr) (P Expr) | |
| Not (P Expr) | |
| LessThan (P Expr) (P Expr) | |
| LessEql (P Expr) (P Expr) | |
| Equal (P Expr) (P Expr) | |
| Assign (P Expr) (P Expr) | |
| PostInc (P Expr) | |
| PostDec (P Expr) | |
| Concat (P Expr) (P Expr) | |
| Plus (P Expr) (P Expr) | |
| Minus (P Expr) (P Expr) | |
| Times (P Expr) (P Expr) | |
| Divided (P Expr) (P Expr) | |
| Modulo (P Expr) (P Expr) | |
| RaisedTo (P Expr) (P Expr) | |
| Funcall Identifier [P Expr] | |
| Methcall (P Expr) Identifier [P Expr] | |
| Cond (P Expr) (P Expr) (P Expr) |
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.
Value representation
Dynamically typed run-time value in the Sindre language.
Instances
| Eq Value Source # | |
| Ord Value Source # | |
| Show Value Source # | |
| Mold Value Source # | |
| MonadState (Map Identifier Value) (ConstructorM m) Source # | |
Defined in Sindre.Compiler Methods get :: ConstructorM m (Map Identifier Value) # put :: Map Identifier Value -> ConstructorM m () # state :: (Map Identifier Value -> (a, Map Identifier Value)) -> ConstructorM m a # | |
Program structure
Something that happened in the world.
Constructors
| KeyPress Chord | |
| NamedEvent | |
Fields
| |
data EventSource Source #
The origin of an event. This is used when determining where to handle it.
Constructors
| FieldSrc ObjectRef Identifier |
|
| 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
| Show EventSource Source # | |
Defined in Sindre.Sindre Methods showsPrec :: Int -> EventSource -> ShowS # show :: EventSource -> String # showList :: [EventSource] -> ShowS # | |
Description of sets of sources, values of this type can be used
to pattern-match EventSources.
Constructors
| NamedSource Identifier (Maybe Identifier) | For |
| GenericSource Identifier Identifier (Maybe Identifier) | For |
Instances
| Eq SourcePat Source # | |
| Ord SourcePat Source # | |
| Show SourcePat 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 |
|
Fields | |
Reaction to an event.
Constructors
| StmtAction [P Stmt] | Execute these statements. |
A function consists of lexically bound parameters and a body.
Constructors
| Function [Identifier] [P Stmt] |
A Sindre GUI is a recursive tree, with each node representing a single widget and consisting of the following fields.
Constructors
| GUI | |
Fields
| |
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 | |
Fields
| |