euphoria-0.8.0.0: Dynamic network FRP with events and continuous values

Safe HaskellNone
LanguageHaskell98

FRP.Euphoria.Internal.GenericCollection

Contents

Description

Collection signals with incremental updates.

The interface exposed by this module uses Maplike extensively. This allows it to be used in the context of a wider variety of key constrints, at the cost of requiring the caller to provide a Proxy. This is pretty inconvenient, so it's recommended that people use one of the specialised modules:

  • FRP.Euphoria.Collection.Enum
  • FRP.Euphoria.Collection.Hashable

Synopsis

Documentation

data CollectionUpdate k a Source #

Represents an incremental change to a collection of items.

Constructors

AddItem k a 
RemoveItem k 

Instances

Functor (CollectionUpdate k) Source # 

Methods

fmap :: (a -> b) -> CollectionUpdate k a -> CollectionUpdate k b #

(<$) :: a -> CollectionUpdate k b -> CollectionUpdate k a #

Foldable (CollectionUpdate k) Source # 

Methods

fold :: Monoid m => CollectionUpdate k m -> m #

foldMap :: Monoid m => (a -> m) -> CollectionUpdate k a -> m #

foldr :: (a -> b -> b) -> b -> CollectionUpdate k a -> b #

foldr' :: (a -> b -> b) -> b -> CollectionUpdate k a -> b #

foldl :: (b -> a -> b) -> b -> CollectionUpdate k a -> b #

foldl' :: (b -> a -> b) -> b -> CollectionUpdate k a -> b #

foldr1 :: (a -> a -> a) -> CollectionUpdate k a -> a #

foldl1 :: (a -> a -> a) -> CollectionUpdate k a -> a #

toList :: CollectionUpdate k a -> [a] #

null :: CollectionUpdate k a -> Bool #

length :: CollectionUpdate k a -> Int #

elem :: Eq a => a -> CollectionUpdate k a -> Bool #

maximum :: Ord a => CollectionUpdate k a -> a #

minimum :: Ord a => CollectionUpdate k a -> a #

sum :: Num a => CollectionUpdate k a -> a #

product :: Num a => CollectionUpdate k a -> a #

Traversable (CollectionUpdate k) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> CollectionUpdate k a -> f (CollectionUpdate k b) #

sequenceA :: Applicative f => CollectionUpdate k (f a) -> f (CollectionUpdate k a) #

mapM :: Monad m => (a -> m b) -> CollectionUpdate k a -> m (CollectionUpdate k b) #

sequence :: Monad m => CollectionUpdate k (m a) -> m (CollectionUpdate k a) #

(Eq k, Eq a) => Eq (CollectionUpdate k a) Source # 
(Show k, Show a) => Show (CollectionUpdate k a) Source # 
Generic (CollectionUpdate k a) Source # 

Associated Types

type Rep (CollectionUpdate k a) :: * -> * #

(NFData k, NFData v) => NFData (CollectionUpdate k v) Source # 

Methods

rnf :: CollectionUpdate k v -> () #

type Rep (CollectionUpdate k a) Source # 
type Rep (CollectionUpdate k a) = D1 (MetaData "CollectionUpdate" "FRP.Euphoria.Internal.GenericCollection" "euphoria-0.8.0.0-5ZwPaETBJOFK93cHmht9li" False) ((:+:) (C1 (MetaCons "AddItem" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 k)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))) (C1 (MetaCons "RemoveItem" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 k))))

data Collection k a Source #

An FRP interface for representing an incrementally updated collection of items. The items are identified by a unique key. Items may be added or removed from the current collection.

This type is useful because it allows you to manage the incremental state updates to something that needs a collection of items without having to rebuild it completely every time the collection changes. Consider the type Signal [a] -- functionally, it also represents a collection of items that changes over time. However, there is no state carried between changes. If, for example, we have a GUI widget that lists items whose content is represented as a Signal [a], we would have to destroy and rebuild the widget's internal state every time the list contents change. But with the Collection type, we can add or remove from the GUI widget only the necessary items. This is useful both from a performance (most existing GUI toolkits exhibit worse performance when adding and removing all items with every change) and behavior standpoint, because the GUI toolkit can, for example, remember which items the user had selected between list updates.

Usage of Collection implies there could be some caching/state by the consumer of the Events, otherwise one might as well use a Signal [a].

creating collections

simpleCollection Source #

Arguments

:: (Maplike c k, Enum k, MonadSignalGen m) 
=> Proxy (c k) 
-> k

The initial value for the unique keys. succ will be used to get further keys.

-> Event (a, Event ())

An Event that introduces a new item and its subsequent removal Event. The item will be removed from the collection when the Event () fires.

-> m (Collection k a) 

A collection whose items are created by an event, and removed by another event.

accumCollection :: forall m c k a. (Maplike c k, MonadSignalGen m) => Proxy (c k) -> Event (CollectionUpdate k a) -> m (Collection k a) Source #

collectionToUpdates :: forall m k a. MonadSignalGen m => Collection k a -> m (Event (CollectionUpdate k a)) Source #

Create an Event stream of all updates from a collection, including the items currently in it.

emptyCollection :: Collection k a Source #

An empty, unchanging Collection.

collectionFromList :: [(k, a)] -> Collection k a Source #

A pure function to create a Collection from key-value pairs. This collection will never change.

collectionFromDiscreteList :: forall m c k a. (Maplike c k, Enum k, Eq a, MonadSignalGen m) => Proxy (c k) -> k -> Discrete [a] -> m (Collection k a) Source #

A somewhat inefficient but easy-to-use way of turning a list of items into a Collection. Probably should only be used for temporary hacks. Will perform badly with large lists.

makeCollection :: MonadSignalGen m => Discrete [(k, a)] -> Event (CollectionUpdate k a) -> m (Collection k a) Source #

The primitive interface for creating a Collection. The two arguments must be coherent, i.e. the value of the discrete at time t+1 should be obtained by applying the updates at t+1 to the value of the discrete at t. This invariant is not checked.

mapToCollection :: forall c m k a. (Eq k, Eq a, Maplike c k, MonadSignalGen m) => Discrete (c k a) -> m (Collection k (Discrete a)) Source #

Turns mapping of values into a collection of first-class FRP values that are updated. If items are added to the EnumMap, then they will be added to the Collection. Likewise, if they are removed from the mapping, they will be removed from the collection. Keys that are present in both but have new values will have their Discrete value updated, and keys with values that are still present will not have their Discrete values updated.

observing collections

watchCollection :: (Show k, Show a, MonadSignalGen m) => Collection k a -> m (Event (IO ())) Source #

Prints add/remove diagnostics for a Collection. Useful for debugging

followCollectionKey :: forall m k a. (Eq k, MonadSignalGen m) => k -> Collection k a -> m (Discrete (Maybe a)) Source #

Look for a key in a collection, and give its (potentially nonexistant) value over time.

collectionToDiscreteList :: Collection k a -> Discrete [(k, a)] Source #

Extracts a Discrete which represents the current state of a collection.

openCollection :: MonadSignalGen m => Collection k a -> m ([(k, a)], Event (CollectionUpdate k a)) Source #

Extracts a snapshot of the current values in a collection with an Event stream of further updates

other functions

mapCollection :: MonadSignalGen m => (a -> b) -> Collection k a -> m (Collection k b) Source #

Like fmap, but the Collection and interior Event stream are memoized

mapCollectionWithKey :: MonadSignalGen m => (k -> a -> b) -> Collection k a -> m (Collection k b) Source #

A version of mapCollection which provides access to the key

filterCollection :: (Maplike c k, MonadSignalGen m) => Proxy (c k) -> (a -> Bool) -> Collection k a -> m (Collection k a) Source #

filterCollectionWithKey :: (Maplike c k, MonadSignalGen m) => Proxy (c k) -> (k -> a -> Bool) -> Collection k a -> m (Collection k a) Source #

justCollection :: forall m c k a. (Maplike c k, MonadSignalGen m) => Proxy (c k) -> Collection k (Maybe a) -> m (Collection k a) Source #

mapCollectionM :: (Maplike c k, MonadSignalGen m) => Proxy (c k) -> (a -> SignalGen b) -> Collection k a -> m (Collection k b) Source #

mapCollectionM p fn = mapCollection fn >=> sequenceCollection p