reflex-vty-0.3.1.1: Reflex FRP host and widgets for VTY applications
Safe HaskellSafe-Inferred
LanguageHaskell2010

Reflex.Vty.Widget.Layout

Description

 
Synopsis

Focus

The focus monad tracks which element is currently focused and processes requests to change focus. Focusable elements are assigned a FocusId and can manually request focus or receive focus due to some other action (e.g., a tab press in a sibling element, a click event).

Focusable elements will usually be created via tile, but can also be constructed via makeFocus in HasFocus. The latter option allows for more find-grained control of focus behavior.

Storing focus state

newtype FocusId Source #

Identifies an element that is focusable. Can be created using makeFocus.

Constructors

FocusId NodeId 

Instances

Instances details
Eq FocusId Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

(==) :: FocusId -> FocusId -> Bool #

(/=) :: FocusId -> FocusId -> Bool #

Ord FocusId Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

newtype FocusSet Source #

An ordered set of focus identifiers. The order here determines the order in which focus cycles between focusable elements.

Constructors

FocusSet 

Instances

Instances details
Monoid FocusSet Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Semigroup FocusSet Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

singletonFS :: FocusId -> FocusSet Source #

Produces a FocusSet with a single element

Changing focus state

data Refocus Source #

Operations that change the currently focused element.

Constructors

Refocus_Shift Int

Shift the focus by a certain number of positions (see shiftFS)

Refocus_Id FocusId

Focus a particular element

Refocus_Clear

Remove focus from all elements

shiftFS :: FocusSet -> Maybe FocusId -> Int -> Maybe FocusId Source #

Given a FocusSet, a currently focused element, and a number of positions to move by, determine the newly focused element.

The focus management monad

class (Monad m, Reflex t) => HasFocus t m | m -> t where Source #

A class for things that can produce focusable elements.

Methods

makeFocus :: m FocusId Source #

Create a focusable element.

requestFocus :: Event t Refocus -> m () Source #

Emit an Event of requests to change the focus.

isFocused :: FocusId -> m (Dynamic t Bool) Source #

Produce a Dynamic that indicates whether the given FocusId is focused.

subFoci :: m a -> m (a, Dynamic t FocusSet) Source #

Run an action, additionally returning the focusable elements it produced.

focusedId :: m (Dynamic t (Maybe FocusId)) Source #

Get a Dynamic of the currently focused element identifier.

Instances

Instances details
(Reflex t, MonadFix m, MonadNodeId m) => HasFocus (t :: Type) (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

(MonadFix m, HasFocus t m) => HasFocus (t :: Type) (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

newtype Focus t m a Source #

A monad transformer that keeps track of the set of focusable elements and which, if any, are currently focused, and allows focus requests.

Instances

Instances details
MonadHold t m => MonadHold (t :: Type) (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

hold :: a -> Event t a -> Focus t m (Behavior t a) #

holdDyn :: a -> Event t a -> Focus t m (Dynamic t a) #

holdIncremental :: Patch p => PatchTarget p -> Event t p -> Focus t m (Incremental t p) #

buildDynamic :: PushM t a -> Event t a -> Focus t m (Dynamic t a) #

headE :: Event t a -> Focus t m (Event t a) #

now :: Focus t m (Event t ()) #

MonadSample t m => MonadSample (t :: Type) (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

sample :: Behavior t a -> Focus t m a #

HasDisplayRegion t m => HasDisplayRegion (t :: Type) (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

askRegion :: Focus t m (Dynamic t Region) Source #

localRegion :: (Dynamic t Region -> Dynamic t Region) -> Focus t m a -> Focus t m a Source #

(HasFocusReader t m, Monad m) => HasFocusReader (t :: Type) (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

focus :: Focus t m (Dynamic t Bool) Source #

localFocus :: (Dynamic t Bool -> Dynamic t Bool) -> Focus t m a -> Focus t m a Source #

(HasImageWriter t m, MonadFix m) => HasImageWriter (t :: Type) (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

tellImages :: Behavior t [Image] -> Focus t m () Source #

mapImages :: (Behavior t [Image] -> Behavior t [Image]) -> Focus t m a -> Focus t m a Source #

(Reflex t, MonadFix m, HasInput t m) => HasInput (t :: Type) (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

input :: Focus t m (Event t VtyEvent) Source #

localInput :: (Event t VtyEvent -> Event t VtyEvent) -> Focus t m a -> Focus t m a Source #

(HasTheme t m, Monad m) => HasTheme (t :: Type) (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

theme :: Focus t m (Behavior t Attr) Source #

localTheme :: (Behavior t Attr -> Behavior t Attr) -> Focus t m a -> Focus t m a Source #

(Reflex t, MonadFix m, MonadNodeId m) => HasFocus (t :: Type) (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

MFunctor (Focus t :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> Focus t m b -> Focus t n b #

(Adjustable t m, MonadHold t m, MonadFix m) => Adjustable t (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

runWithReplace :: Focus t m a -> Event t (Focus t m b) -> Focus t m (a, Event t b) #

traverseIntMapWithKeyWithAdjust :: (Key -> v -> Focus t m v') -> IntMap v -> Event t (PatchIntMap v) -> Focus t m (IntMap v', Event t (PatchIntMap v')) #

traverseDMapWithKeyWithAdjust :: GCompare k => (forall a. k a -> v a -> Focus t m (v' a)) -> DMap k v -> Event t (PatchDMap k v) -> Focus t m (DMap k v', Event t (PatchDMap k v')) #

traverseDMapWithKeyWithAdjustWithMove :: GCompare k => (forall a. k a -> v a -> Focus t m (v' a)) -> DMap k v -> Event t (PatchDMapWithMove k v) -> Focus t m (DMap k v', Event t (PatchDMapWithMove k v')) #

MonadReflexCreateTrigger t m => MonadReflexCreateTrigger t (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

newEventWithTrigger :: (EventTrigger t a -> IO (IO ())) -> Focus t m (Event t a) #

newFanEventWithTrigger :: GCompare k => (forall a. k a -> EventTrigger t a -> IO (IO ())) -> Focus t m (EventSelector t k) #

NotReady t m => NotReady t (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

notReadyUntil :: Event t a -> Focus t m () #

notReady :: Focus t m () #

PerformEvent t m => PerformEvent t (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Associated Types

type Performable (Focus t m) :: Type -> Type #

Methods

performEvent :: Event t (Performable (Focus t m) a) -> Focus t m (Event t a) #

performEvent_ :: Event t (Performable (Focus t m) ()) -> Focus t m () #

PostBuild t m => PostBuild t (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

getPostBuild :: Focus t m (Event t ()) #

TriggerEvent t m => TriggerEvent t (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

newTriggerEvent :: Focus t m (Event t a, a -> IO ()) #

newTriggerEventWithOnComplete :: Focus t m (Event t a, a -> IO () -> IO ()) #

newEventWithLazyTriggerWithOnComplete :: ((a -> IO () -> IO ()) -> IO (IO ())) -> Focus t m (Event t a) #

MonadTrans (Focus t) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

lift :: Monad m => m a -> Focus t m a #

MonadFix m => MonadFix (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

mfix :: (a -> Focus t m a) -> Focus t m a #

MonadIO m => MonadIO (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

liftIO :: IO a -> Focus t m a #

Monad m => Applicative (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

pure :: a -> Focus t m a #

(<*>) :: Focus t m (a -> b) -> Focus t m a -> Focus t m b #

liftA2 :: (a -> b -> c) -> Focus t m a -> Focus t m b -> Focus t m c #

(*>) :: Focus t m a -> Focus t m b -> Focus t m b #

(<*) :: Focus t m a -> Focus t m b -> Focus t m a #

Functor m => Functor (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

fmap :: (a -> b) -> Focus t m a -> Focus t m b #

(<$) :: a -> Focus t m b -> Focus t m a #

Monad m => Monad (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

(>>=) :: Focus t m a -> (a -> Focus t m b) -> Focus t m b #

(>>) :: Focus t m a -> Focus t m b -> Focus t m b #

return :: a -> Focus t m a #

MonadNodeId m => MonadNodeId (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

type Performable (Focus t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

runFocus :: (MonadFix m, MonadHold t m, Reflex t) => Focus t m a -> m (a, Dynamic t FocusSet) Source #

Runs a Focus action, maintaining the selection state internally.

anyChildFocused :: (HasFocus t m, MonadFix m) => (Dynamic t Bool -> m a) -> m a Source #

Runs an action in the focus monad, providing it with information about whether any of the foci created within it are focused.

Focus controls

tabNavigation :: (Reflex t, HasInput t m, HasFocus t m) => m () Source #

Request focus be shifted backward and forward based on tab presses. Tab shifts focus forward and Shift+Tab shifts focus backward.

Layout

The layout monad keeps track of a tree of elements, each having its own layout constraints and orientation. Given the available rendering space, it computes a layout solution and provides child elements with their particular layout solution (the width and height of their rendering space).

Complex layouts are built up though some combination of:

  • axis, which lays out its children in a particular orientation, and
  • region, which "claims" some part of the screen according to its constraints

Layout restrictions

Constraints

data Constraint Source #

Datatype representing constraints on a widget's size along the main axis (see Orientation)

fixed :: Reflex t => Dynamic t Int -> Dynamic t Constraint Source #

Shorthand for constructing a fixed constraint

stretch :: Reflex t => Dynamic t Int -> Dynamic t Constraint Source #

Shorthand for constructing a minimum size constraint

flex :: Reflex t => Dynamic t Constraint Source #

Shorthand for constructing a constraint of no minimum size

Orientation

row :: (Reflex t, MonadFix m, HasLayout t m) => m a -> m a Source #

Create a row-oriented axis

col :: (Reflex t, MonadFix m, HasLayout t m) => m a -> m a Source #

Create a column-oriented axis

Layout management data

data LayoutTree a Source #

A collection of information related to the layout of the screen. The root node is a "parent" widget, and the contents of the LayoutForest are its children.

Constructors

LayoutTree a (LayoutForest a) 

Instances

Instances details
Show a => Show (LayoutTree a) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

newtype LayoutForest a Source #

An ordered, indexed collection of LayoutTrees representing information about the children of some widget.

Constructors

LayoutForest 

Instances

Instances details
Monoid (LayoutForest a) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Semigroup (LayoutForest a) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Show a => Show (LayoutForest a) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

lookupLF :: NodeId -> LayoutForest a -> Maybe (LayoutTree a) Source #

Perform a lookup by NodeId in a LayoutForest

singletonLF :: NodeId -> LayoutTree a -> LayoutForest a Source #

Create a LayoutForest with one element

fromListLF :: [(NodeId, LayoutTree a)] -> LayoutForest a Source #

Produce a LayoutForest from a list. The order of the list is preserved.

rootLT :: LayoutTree a -> a Source #

Extract the information at the root of a LayoutTree

childrenLT :: LayoutTree a -> LayoutForest a Source #

Extract the child nodes of a LayoutTree

solve :: Orientation -> Region -> LayoutForest (Constraint, Orientation) -> LayoutTree (Region, Orientation) Source #

Produce a layout solution given a starting orientation, the overall screen size, and a set of constraints.

chunk :: Orientation -> Region -> (Int, Int) -> Region Source #

Produce a Region given a starting orientation and region, and the offset and main-axis size of the chunk.

The layout monad

class Monad m => HasLayout t m | m -> t where Source #

A class of operations for creating screen layouts.

Methods

axis :: Dynamic t Orientation -> Dynamic t Constraint -> m a -> m a Source #

Starts a parent element in the current layout with the given size constraint, which lays out its children according to the provided orientation.

region :: Dynamic t Constraint -> m (Dynamic t Region) Source #

Creates a child element in the current layout with the given size constraint, returning the Region that the child element is allocated.

askOrientation :: m (Dynamic t Orientation) Source #

Returns the orientation of the containing axis.

Instances

Instances details
(Monad m, MonadNodeId m, Reflex t, MonadFix m) => HasLayout (t :: Type) (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

newtype Layout t m a Source #

A monad transformer that collects layout constraints and provides a layout solution that satisfies those constraints.

Instances

Instances details
MonadHold t m => MonadHold (t :: Type) (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

hold :: a -> Event t a -> Layout t m (Behavior t a) #

holdDyn :: a -> Event t a -> Layout t m (Dynamic t a) #

holdIncremental :: Patch p => PatchTarget p -> Event t p -> Layout t m (Incremental t p) #

buildDynamic :: PushM t a -> Event t a -> Layout t m (Dynamic t a) #

headE :: Event t a -> Layout t m (Event t a) #

now :: Layout t m (Event t ()) #

MonadSample t m => MonadSample (t :: Type) (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

sample :: Behavior t a -> Layout t m a #

HasDisplayRegion t m => HasDisplayRegion (t :: Type) (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

askRegion :: Layout t m (Dynamic t Region) Source #

localRegion :: (Dynamic t Region -> Dynamic t Region) -> Layout t m a -> Layout t m a Source #

(HasFocusReader t m, Monad m) => HasFocusReader (t :: Type) (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

focus :: Layout t m (Dynamic t Bool) Source #

localFocus :: (Dynamic t Bool -> Dynamic t Bool) -> Layout t m a -> Layout t m a Source #

(HasDisplayRegion t m, HasImageWriter t m, MonadFix m) => HasImageWriter (t :: Type) (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

tellImages :: Behavior t [Image] -> Layout t m () Source #

mapImages :: (Behavior t [Image] -> Behavior t [Image]) -> Layout t m a -> Layout t m a Source #

(HasInput t m, HasDisplayRegion t m, MonadFix m, Reflex t) => HasInput (t :: Type) (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

input :: Layout t m (Event t VtyEvent) Source #

localInput :: (Event t VtyEvent -> Event t VtyEvent) -> Layout t m a -> Layout t m a Source #

(HasTheme t m, Monad m) => HasTheme (t :: Type) (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

theme :: Layout t m (Behavior t Attr) Source #

localTheme :: (Behavior t Attr -> Behavior t Attr) -> Layout t m a -> Layout t m a Source #

(MonadFix m, HasFocus t m) => HasFocus (t :: Type) (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

(Monad m, MonadNodeId m, Reflex t, MonadFix m) => HasLayout (t :: Type) (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

MFunctor (Layout t :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> Layout t m b -> Layout t n b #

(Adjustable t m, MonadFix m, MonadHold t m) => Adjustable t (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

runWithReplace :: Layout t m a -> Event t (Layout t m b) -> Layout t m (a, Event t b) #

traverseIntMapWithKeyWithAdjust :: (Key -> v -> Layout t m v') -> IntMap v -> Event t (PatchIntMap v) -> Layout t m (IntMap v', Event t (PatchIntMap v')) #

traverseDMapWithKeyWithAdjust :: GCompare k => (forall a. k a -> v a -> Layout t m (v' a)) -> DMap k v -> Event t (PatchDMap k v) -> Layout t m (DMap k v', Event t (PatchDMap k v')) #

traverseDMapWithKeyWithAdjustWithMove :: GCompare k => (forall a. k a -> v a -> Layout t m (v' a)) -> DMap k v -> Event t (PatchDMapWithMove k v) -> Layout t m (DMap k v', Event t (PatchDMapWithMove k v')) #

MonadReflexCreateTrigger t m => MonadReflexCreateTrigger t (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

newEventWithTrigger :: (EventTrigger t a -> IO (IO ())) -> Layout t m (Event t a) #

newFanEventWithTrigger :: GCompare k => (forall a. k a -> EventTrigger t a -> IO (IO ())) -> Layout t m (EventSelector t k) #

NotReady t m => NotReady t (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

notReadyUntil :: Event t a -> Layout t m () #

notReady :: Layout t m () #

PerformEvent t m => PerformEvent t (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Associated Types

type Performable (Layout t m) :: Type -> Type #

Methods

performEvent :: Event t (Performable (Layout t m) a) -> Layout t m (Event t a) #

performEvent_ :: Event t (Performable (Layout t m) ()) -> Layout t m () #

PostBuild t m => PostBuild t (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

getPostBuild :: Layout t m (Event t ()) #

TriggerEvent t m => TriggerEvent t (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

newTriggerEvent :: Layout t m (Event t a, a -> IO ()) #

newTriggerEventWithOnComplete :: Layout t m (Event t a, a -> IO () -> IO ()) #

newEventWithLazyTriggerWithOnComplete :: ((a -> IO () -> IO ()) -> IO (IO ())) -> Layout t m (Event t a) #

MonadTrans (Layout t) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

lift :: Monad m => m a -> Layout t m a #

MonadFix m => MonadFix (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

mfix :: (a -> Layout t m a) -> Layout t m a #

MonadIO m => MonadIO (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

liftIO :: IO a -> Layout t m a #

Monad m => Applicative (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

pure :: a -> Layout t m a #

(<*>) :: Layout t m (a -> b) -> Layout t m a -> Layout t m b #

liftA2 :: (a -> b -> c) -> Layout t m a -> Layout t m b -> Layout t m c #

(*>) :: Layout t m a -> Layout t m b -> Layout t m b #

(<*) :: Layout t m a -> Layout t m b -> Layout t m a #

Functor m => Functor (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

fmap :: (a -> b) -> Layout t m a -> Layout t m b #

(<$) :: a -> Layout t m b -> Layout t m a #

Monad m => Monad (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

(>>=) :: Layout t m a -> (a -> Layout t m b) -> Layout t m b #

(>>) :: Layout t m a -> Layout t m b -> Layout t m b #

return :: a -> Layout t m a #

MonadNodeId m => MonadNodeId (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

type Performable (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

hoistRunLayout :: (HasDisplayRegion t m, MonadFix m, Monad n) => (m a -> n b) -> Layout t m a -> Layout t n b Source #

Apply a transformation to the context of a child Layout action and run that action

runLayout :: (MonadFix m, Reflex t) => Dynamic t Orientation -> Dynamic t Region -> Layout t m a -> m a Source #

Runs a Layout action, using the given orientation and region to calculate layout solutions.

initLayout :: (HasDisplayRegion t m, MonadFix m) => Layout t m a -> m a Source #

Initialize and run the layout monad, using all of the available screen space.

The tile "window manager"

Generally HasLayout and HasFocus are used together to build a user interface. These functions check the available screen size and initialize the layout monad with that information, and also initialize the focus monad.

initManager :: (HasDisplayRegion t m, Reflex t, MonadHold t m, MonadFix m) => Layout t (Focus t m) a -> m (a, Dynamic t FocusSet) Source #

Initialize a Layout and Focus management context, returning the produced FocusSet.

initManager_ :: (HasDisplayRegion t m, Reflex t, MonadHold t m, MonadFix m) => Layout t (Focus t m) a -> m a Source #

Initialize a Layout and Focus management context.

Layout tiles

Focusable

tile' :: (MonadFix m, Reflex t, HasInput t m, HasFocus t m, HasLayout t m, HasImageWriter t m, HasDisplayRegion t m, HasFocusReader t m) => Dynamic t Constraint -> m a -> m (FocusId, a) Source #

A widget that is focusable and occupies a layout region based on the provided constraint. Returns the FocusId allowing for manual focus management.

tile :: (MonadFix m, Reflex t, HasInput t m, HasFocus t m, HasLayout t m, HasImageWriter t m, HasDisplayRegion t m, HasFocusReader t m) => Dynamic t Constraint -> m a -> m a Source #

A widget that is focusable and occupies a layout region based on the provided constraint.

Unfocusable

grout :: (Reflex t, HasLayout t m, HasInput t m, HasImageWriter t m, HasDisplayRegion t m, HasFocusReader t m) => Dynamic t Constraint -> m a -> m a Source #

A widget that is not focusable and occupies a layout region based on the provided constraint.