| Safe Haskell | None |
|---|
LGtk
Contents
Description
Main LGtk interface.
- type Morph m n = forall a. m a -> n a
- class (Monad m, Monad (ReadPart m)) => HasReadPart m where
- type ReadPart m :: * -> *
- liftReadPart :: ReadPart m a -> m a
- class HasReadPart (RefMonad r) => Reference r where
- type RefMonad r :: * -> *
- readRef :: r a -> ReadRefMonad r a
- writeRef :: r a -> a -> RefMonad r ()
- lensMap :: Lens' a b -> r a -> r b
- joinRef :: ReadRefMonad r (r a) -> r a
- unitRef :: r ()
- type ReadRefMonad m = ReadPart (RefMonad m)
- class (Monad m, Reference (Ref m)) => ExtRef m where
- type ReadRef m = ReadRefMonad (Ref m)
- type WriteRef m = RefMonad (Ref m)
- liftReadRef :: ExtRef m => Morph (ReadRef m) m
- modRef :: Reference r => r a -> (a -> a) -> RefMonad r ()
- readRef' :: ExtRef m => Ref m a -> m a
- memoRead :: ExtRef m => m a -> m (m a)
- undoTr :: ExtRef m => (a -> a -> Bool) -> Ref m a -> m (ReadRef m (Maybe (WriteRef m ())), ReadRef m (Maybe (WriteRef m ())))
- class Reference r => EqReference r where
- hasEffect :: r a -> (a -> a) -> ReadRefMonad r Bool
- data EqRef r a
- eqRef :: (Reference r, Eq a) => r a -> EqRef r a
- newEqRef :: (ExtRef m, Eq a) => a -> m (EqRef (Ref m) a)
- toRef :: Reference r => EqRef r a -> r a
- class ExtRef m => EffRef m where
- class Monad m => SafeIO m where
- class (EffRef m, SafeIO m, SafeIO (ReadRef m)) => EffIORef m where
- asyncWrite :: EffIORef m => Int -> (a -> WriteRef m ()) -> a -> m ()
- putStrLn_ :: EffIORef m => String -> m ()
- type Widget m = Widget (EffectM m) m
- runWidget :: (forall m. EffIORef m => Widget m) -> IO ()
- label :: EffRef m => ReadRef m String -> Widget m
- checkbox :: EffRef m => Ref m Bool -> Widget m
- combobox :: EffRef m => [String] -> Ref m Int -> Widget m
- entry :: (EffRef m, Reference r, RefMonad r ~ RefMonad (Ref m)) => r String -> Widget m
- vcat :: [Widget m] -> Widget m
- hcat :: [Widget m] -> Widget m
- button_ :: EffRef m => ReadRef m String -> ReadRef m Bool -> WriteRef m () -> Widget m
- data Color = Color Word16 Word16 Word16
- notebook :: EffRef m => [(String, Widget m)] -> Widget m
- cell_ :: (EffRef m, Eq a) => ReadRef m a -> (forall x. (Widget m -> m x) -> a -> m (m x)) -> Widget m
- action :: EffRef m => m (Widget m) -> Widget m
- canvas :: (EffRef m, Eq b, Eq a, Monoid a) => Int -> Int -> Double -> (MouseEvent a -> WriteRef m ()) -> ReadRef m b -> (b -> Dia a) -> Widget m
- type Dia a = QDiagram Cairo R2 a
- data MouseEvent a
- data MousePos a = MousePos (Double, Double) a
- data Modifier
- type KeyVal = Word32
- keyName :: KeyVal -> String
- keyToChar :: KeyVal -> Maybe Char
- data ScrollDirection
- = ScrollUp
- | ScrollDown
- | ScrollLeft
- | ScrollRight
- hscale :: EffRef m => Double -> Double -> Double -> Ref m Double -> Widget m
- empty :: Widget m
- entryShow :: (EffRef m, Show a, Read a, Reference r, RefMonad r ~ RefMonad (Ref m)) => r a -> Widget m
- button :: EffRef m => ReadRef m String -> ReadRef m (Maybe (WriteRef m ())) -> Widget m
- smartButton :: (EffRef m, EqReference r, RefMonad r ~ RefMonad (Ref m)) => ReadRef m String -> r a -> (a -> a) -> Widget m
- cell :: (EffRef m, Eq a) => ReadRef m a -> (a -> Widget m) -> Widget m
- cellNoMemo :: (EffRef m, Eq a) => ReadRef m a -> (a -> Widget m) -> Widget m
- button__ :: EffRef m => ReadRef m String -> ReadRef m Bool -> ReadRef m Color -> WriteRef m () -> Widget m
Monad morphisms
class (Monad m, Monad (ReadPart m)) => HasReadPart m whereSource
m has a submonad (ReadPart m) which is isomorphic to Reader.
Associated Types
type ReadPart m :: * -> *Source
Law: (ReadPart m) === ( for some Reader x)x.
Alternative laws which ensures this isomorphism (r :: (ReadPart m a) is arbitrary):
-
(r >> return ())===return () -
liftM2 (,) r r===liftM (a -> (a, a)) r
See also http://stackoverflow.com/questions/16123588/what-is-this-special-functor-structure-called
Instances
| Monad m => HasReadPart (StateT s m) | ReadPart (StateT s m) = Reader s |
References
Basic operations
class HasReadPart (RefMonad r) => Reference r whereSource
A reference (r a) is isomorphic to ( for some fixed state Lens s a)s.
r === Lens s
Associated Types
type RefMonad r :: * -> *Source
Refmonad r === State s
Property derived from the HasReadPart instance:
ReadRefMonad r = ReadPart (Refmonad r) === Reader s
Methods
readRef :: r a -> ReadRefMonad r aSource
readRef === reader . getL
Properties derived from the HasReadPart instance:
(readRef r >> return ()) === return ()
writeRef :: r a -> a -> RefMonad r ()Source
writeRef r === modify . setL r
Properties derived from the set-get, get-set and set-set laws for lenses:
-
(readRef r >>= writeRef r)===return () -
(writeRef r a >> readRef r)===return a -
(writeRef r a >> writeRef r a')===writeRef r a'
lensMap :: Lens' a b -> r a -> r bSource
Apply a lens on a reference.
lensMap === (.)
joinRef :: ReadRefMonad r (r a) -> r aSource
joinRef makes possible to define dynamic references, i.e. references which depends on
values of other references.
It is not possible to create new reference dynamically with joinRef; for that, see onChange.
joinRef === Lens . join . (runLens .) . runReader
unitRef === lens (const ()) (const id)
type ReadRefMonad m = ReadPart (RefMonad m)Source
Reference creation
class (Monad m, Reference (Ref m)) => ExtRef m whereSource
Monad for reference creation. Reference creation is not a method
of the Reference type class to make possible to
create the same type of references in multiple monads.
(Extref m) === (StateT s m), where s is an extendible state.
For basic usage examples, look into the source of Control.Monad.ExtRef.Pure.Test.
Methods
extRef :: Ref m b -> Lens' a b -> a -> m (Ref m a)Source
Reference creation by extending the state of an existing reference.
Suppose that r is a reference and k is a lens.
Law 1: extRef applies k on r backwards, i.e.
the result of (extRef r k a0) should behaves exactly as (lensMap k r).
-
(liftM (k .) $ extRef r k a0)===return r
Law 2: extRef does not change the value of r:
-
(extRef r k a0 >> readRef r)===(readRef r)
Law 3: Proper initialization of newly defined reference with a0:
-
(extRef r k a0 >>= readRef)===(readRef r >>= setL k a0)
newRef :: a -> m (Ref m a)Source
newRef extends the state s in an independent way.
newRef === extRef unitRef (lens (const ()) (const id))
Instances
| ExtRef m => ExtRef (IdentityT m) | This instance is used in the implementation, end users do not need it. |
| (ExtRef m, Monoid w) => ExtRef (WriterT w m) | This instance is used in the implementation, end users do not need it. |
| (ExtRef m, Monoid w) => ExtRef (RWST r w s m) | This instance is used in the implementation, end users do not need it. |
type ReadRef m = ReadRefMonad (Ref m)Source
liftReadRef :: ExtRef m => Morph (ReadRef m) mSource
ReadRef lifted to the reference creation class.
Note that we do not lift WriteRef to the reference creation class, which a crucial restriction
in the LGtk interface; this is a feature.
Derived constructs
modRef :: Reference r => r a -> (a -> a) -> RefMonad r ()Source
modRef r f === liftReadPart (readRef r) >>= writeRef r . f
readRef' :: ExtRef m => Ref m a -> m aSource
readRef lifted to the reference creation class.
readRef' === liftReadRef . readRef
memoRead :: ExtRef m => m a -> m (m a)Source
Lazy monadic evaluation.
In case of y <- memoRead x, invoking y will invoke x at most once.
Laws:
-
(memoRead x >> return ())===return () -
(memoRead x >>= id)===x -
(memoRead x >>= y -> liftM2 (,) y y)===liftM (a -> (a, a)) y -
(memoRead x >>= y -> liftM3 (,) y y y)===liftM (a -> (a, a, a)) y - ...
Arguments
| :: ExtRef m | |
| => (a -> a -> Bool) | equality on state |
| -> Ref m a | reference of state |
| -> m (ReadRef m (Maybe (WriteRef m ())), ReadRef m (Maybe (WriteRef m ()))) | undo and redo actions |
Undo-redo state transformation.
class Reference r => EqReference r whereSource
References with inherent equivalence.
Methods
hasEffect :: r a -> (a -> a) -> ReadRefMonad r BoolSource
hasEffect r f returns False iff (modRef m f) === (return ()).
hasEffect is correct only if eqRef is applied on a pure reference (a reference which is a pure lens on the hidden state).
hasEffect makes defining auto-sensitive buttons easier, for example.
Instances
| Reference r => EqReference (EqRef r) |
References with inherent equivalence.
EqRef r a === ReadRefMonad r (exist b . Eq b => (Lens' b a, r b))
As a reference, (m :: EqRef r a) behaves as
joinRef $ liftM (uncurry lensMap) m
toRef :: Reference r => EqRef r a -> r aSource
An EqRef is a normal reference if we forget about the equality.
toRef m === joinRef $ liftM (uncurry lensMap) m
Dynamic networks
class ExtRef m => EffRef m whereSource
Monad for dynamic actions
Methods
onChange :: Eq a => Bool -> ReadRef m a -> (a -> m (m ())) -> m ()Source
Let r be an effectless action (ReadRef guarantees this).
(onChange init r fmm) has the following effect:
Whenever the value of r changes (with respect to the given equality),
fmm is called with the new value a.
The value of the (fmm a) action is memoized,
but the memoized value is run again and again.
The boolean parameter init tells whether the action should
be run in the beginning or not.
For example, let (k :: a -> m b) and (h :: b -> m ()),
and suppose that r will have values a1, a2, a3 = a1, a4 = a2.
onChange True r $ \a -> k a >>= return . h
has the effect
k a1 >>= \b1 -> h b1 >> k a2 >>= \b2 -> h b2 >> h b1 >> h b2
and
onChange False r $ \a -> k a >>= return . h
has the effect
k a2 >>= \b2 -> h b2 >> k a1 >>= \b1 -> h b1 >> h b2
I/O
class Monad m => SafeIO m whereSource
Type class for effectless, synchronous IO actions.
Methods
The program's command line arguments (not including the program name).
getProgName :: m StringSource
The name of the program as it was invoked.
lookupEnv :: String -> m (Maybe String)Source
(lookupEnv var) returns the value of the environment variable var.
Instances
| SafeIO IO | This instance is used in the implementation, the end users do not need it. |
| SafeIO m => SafeIO (IdentityT m) | This instance is used in the implementation, the end users do not need it. |
| (SafeIO m, Monoid w) => SafeIO (RWST r w s m) | This instance is used in the implementation, the end users do not need it. |
class (EffRef m, SafeIO m, SafeIO (ReadRef m)) => EffIORef m whereSource
Type class for IO actions.
Methods
fileRef :: FilePath -> m (Ref m (Maybe String))Source
(fileRef path) returns a reference which holds the actual contents
of the file accessed by path.
When the value of the reference changes, the file changes. When the file changes, the value of the reference changes.
If the reference holds Nothing, the file does not exist.
Note that you delete the file by putting Nothing into the reference.
Implementation note: The references returned by fileRef are not
memoised so currently it is unsafe to call fileRef on the same filepath more than once.
This restriction will be lifted in the future.
putStr_ :: String -> m ()Source
Write a string to the standard output device.
getLine_ :: (String -> WriteRef m ()) -> m ()Source
Read a line from the standard input device.
(getLine_ f) returns immediately. When the line s is read,
f s is called.
asyncWrite :: EffIORef m => Int -> (a -> WriteRef m ()) -> a -> m ()Source
Derived constructs
GUI
Running
type Widget m = Widget (EffectM m) mSource
Gtk widget descriptions.
Construction of a (w :: forall m . EffIORef m => Widget m) value is side-effect free,
side-effects happen at running (.
runWidget w)
Widget should be abstract data type, but it is also safe to keep it as a type synonym because
the operations of the revealed implementation are hidden.
runWidget :: (forall m. EffIORef m => Widget m) -> IO ()Source
Run a Gtk widget description.
The widget is shown in a window and the thread enters into the Gtk event cycle. It leaves the event cycle when the window is closed.
GUI descriptions
entry :: (EffRef m, Reference r, RefMonad r ~ RefMonad (Ref m)) => r String -> Widget mSource
Text entry.
Arguments
| :: EffRef m | |
| => ReadRef m String | dynamic label of the button |
| -> ReadRef m Bool | the button is active when this returns |
| -> WriteRef m () | the action to do when the button is pressed |
| -> Widget m |
Low-level button.
data Color
Color
- Specifies a color with three integer values for red, green and blue. All values range from 0 (least intense) to 65535 (highest intensity).
notebook :: EffRef m => [(String, Widget m)] -> Widget mSource
Notebook (tabs).
The tabs are created lazily.
cell_ :: (EffRef m, Eq a) => ReadRef m a -> (forall x. (Widget m -> m x) -> a -> m (m x)) -> Widget mSource
Dynamic cell.
The monadic action for inner widget creation is memoised in the first monad layer.
action :: EffRef m => m (Widget m) -> Widget mSource
action makes possible to do any EffRef action while creating the widget.
canvas :: (EffRef m, Eq b, Eq a, Monoid a) => Int -> Int -> Double -> (MouseEvent a -> WriteRef m ()) -> ReadRef m b -> (b -> Dia a) -> Widget mSource
data MouseEvent a Source
Constructors
| MoveTo (MousePos a) | |
| MouseEnter (MousePos a) | |
| MouseLeave (MousePos a) | |
| Click (MousePos a) | |
| DragTo (MousePos a) | |
| Release (MousePos a) | |
| ScrollTo ScrollDirection (MousePos a) | |
| KeyPress [Modifier] KeyVal |
Instances
| Eq a => Eq (MouseEvent a) |
data Modifier
Keyboard modifiers that are depressed when the user presses a key or a mouse button.
- This data type is used to build lists of modifers that were active during an event.
- The Apple key on Macintoshs is mapped to
Alt2and theMetakey (if available). - Since Gtk 2.10, there are also
Super,HyperandMetamodifiers which are simply generated fromAlt..Composemodifier keys, depending on the mapping used by the windowing system. Due to one key being mapped to e.g.Alt2andMeta, you shouldn't pattern match directly against a certain key but check whether a key is in the list using theelemfunction, say.
Arguments
| :: KeyVal |
|
| -> Maybe Char | returns the corresponding unicode character, or Nothing if there is no corresponding character. |
Convert from a Gdk key symbol to the corresponding Unicode character.
data ScrollDirection
in which direction was scrolled?
Constructors
| ScrollUp | |
| ScrollDown | |
| ScrollLeft | |
| ScrollRight |
Instances
Derived constructs
entryShow :: (EffRef m, Show a, Read a, Reference r, RefMonad r ~ RefMonad (Ref m)) => r a -> Widget mSource
Text entry.
Arguments
| :: (EffRef m, EqReference r, RefMonad r ~ RefMonad (Ref m)) | |
| => ReadRef m String | dynamic label of the button |
| -> r a | underlying reference |
| -> (a -> a) | The button is active when this function is not identity on value of the reference. When the button is pressed, the value of the reference is modified with this function. |
| -> Widget m |
cell :: (EffRef m, Eq a) => ReadRef m a -> (a -> Widget m) -> Widget mSource
Dynamic cell.
The inner widgets are memoised.
cellNoMemo :: (EffRef m, Eq a) => ReadRef m a -> (a -> Widget m) -> Widget mSource
Dynamic cell.
The inner widgets are not memoised.