WidgetRattus-0.4: An asynchronous modal FRP language for GUI programming
Safe HaskellSafe-Inferred
LanguageHaskell2010

WidgetRattus.Strict

Description

This module contains strict versions of some standard data structures.

Synopsis

Documentation

data List a Source #

Strict list type.

Constructors

Nil 
!a :! !(List a) infixr 8 

Instances

Instances details
Foldable List Source # 
Instance details

Defined in WidgetRattus.Strict

Methods

fold :: Monoid m => List m -> m #

foldMap :: Monoid m => (a -> m) -> List a -> m #

foldMap' :: Monoid m => (a -> m) -> List a -> m #

foldr :: (a -> b -> b) -> b -> List a -> b #

foldr' :: (a -> b -> b) -> b -> List a -> b #

foldl :: (b -> a -> b) -> b -> List a -> b #

foldl' :: (b -> a -> b) -> b -> List a -> b #

foldr1 :: (a -> a -> a) -> List a -> a #

foldl1 :: (a -> a -> a) -> List a -> a #

toList :: List a -> [a] #

null :: List a -> Bool #

length :: List a -> Int #

elem :: Eq a => a -> List a -> Bool #

maximum :: Ord a => List a -> a #

minimum :: Ord a => List a -> a #

sum :: Num a => List a -> a #

product :: Num a => List a -> a #

Traversable List Source # 
Instance details

Defined in WidgetRattus.Strict

Methods

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

sequenceA :: Applicative f => List (f a) -> f (List a) #

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

sequence :: Monad m => List (m a) -> m (List a) #

Functor List Source # 
Instance details

Defined in WidgetRattus.Strict

Methods

fmap :: (a -> b) -> List a -> List b #

(<$) :: a -> List b -> List a #

Continuous a => Continuous (List a) Source # 
Instance details

Defined in WidgetRattus.Strict

Widgets w => Widgets (List w) Source # 
Instance details

Defined in WidgetRattus.Widgets

IsList (List a) Source # 
Instance details

Defined in WidgetRattus.Strict

Associated Types

type Item (List a) #

Methods

fromList :: [Item (List a)] -> List a #

fromListN :: Int -> [Item (List a)] -> List a #

toList :: List a -> [Item (List a)] #

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

Defined in WidgetRattus.Strict

Methods

showsPrec :: Int -> List a -> ShowS #

show :: List a -> String #

showList :: [List a] -> ShowS #

Eq a => Eq (List a) Source # 
Instance details

Defined in WidgetRattus.Strict

Methods

(==) :: List a -> List a -> Bool #

(/=) :: List a -> List a -> Bool #

type Item (List a) Source # 
Instance details

Defined in WidgetRattus.Strict

type Item (List a) = a

class IsList l where #

The IsList class and its methods are intended to be used in conjunction with the OverloadedLists extension.

Since: base-4.7.0.0

Minimal complete definition

fromList, toList

Associated Types

type Item l #

The Item type function returns the type of items of the structure l.

Methods

fromList :: [Item l] -> l #

The fromList function constructs the structure l from the given list of Item l

fromListN :: Int -> [Item l] -> l #

The fromListN function takes the input list's length and potentially uses it to construct the structure l more efficiently compared to fromList. If the given number does not equal to the input list's length the behaviour of fromListN is not specified.

fromListN (length xs) xs == fromList xs

toList :: l -> [Item l] #

The toList function extracts a list of Item l from the structure l. It should satisfy fromList . toList = id.

Instances

Instances details
IsList ByteArray

Since: base-4.17.0.0

Instance details

Defined in Data.Array.Byte

Associated Types

type Item ByteArray #

IsList Version

Since: base-4.8.0.0

Instance details

Defined in GHC.IsList

Associated Types

type Item Version #

IsList CallStack

Be aware that 'fromList . toList = id' only for unfrozen CallStacks, since toList removes frozenness information.

Since: base-4.9.0.0

Instance details

Defined in GHC.IsList

Associated Types

type Item CallStack #

IsList String 
Instance details

Defined in Basement.UTF8.Base

Associated Types

type Item String #

IsList ByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Internal.Type

Associated Types

type Item ByteString #

IsList ByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Lazy.Internal

Associated Types

type Item ByteString #

IsList ShortByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Short.Internal

Associated Types

type Item ShortByteString #

IsList ByteArray 
Instance details

Defined in Codec.CBOR.ByteArray

Associated Types

type Item ByteArray #

IsList SlicedByteArray 
Instance details

Defined in Codec.CBOR.ByteArray.Sliced

Associated Types

type Item SlicedByteArray #

IsList IntSet

Since: containers-0.5.6.2

Instance details

Defined in Data.IntSet.Internal

Associated Types

type Item IntSet #

IsList ShortText

Note: Surrogate pairs ([U+D800 .. U+DFFF]) character literals are replaced by U+FFFD.

Since: text-short-0.1.2

Instance details

Defined in Data.Text.Short.Internal

Associated Types

type Item ShortText #

IsList (List a) Source # 
Instance details

Defined in WidgetRattus.Strict

Associated Types

type Item (List a) #

Methods

fromList :: [Item (List a)] -> List a #

fromListN :: Int -> [Item (List a)] -> List a #

toList :: List a -> [Item (List a)] #

IsList (ZipList a)

Since: base-4.15.0.0

Instance details

Defined in GHC.IsList

Associated Types

type Item (ZipList a) #

Methods

fromList :: [Item (ZipList a)] -> ZipList a #

fromListN :: Int -> [Item (ZipList a)] -> ZipList a #

toList :: ZipList a -> [Item (ZipList a)] #

IsList (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.IsList

Associated Types

type Item (NonEmpty a) #

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a #

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a #

toList :: NonEmpty a -> [Item (NonEmpty a)] #

PrimType ty => IsList (Block ty) 
Instance details

Defined in Basement.Block.Base

Associated Types

type Item (Block ty) #

Methods

fromList :: [Item (Block ty)] -> Block ty #

fromListN :: Int -> [Item (Block ty)] -> Block ty #

toList :: Block ty -> [Item (Block ty)] #

IsList c => IsList (NonEmpty c) 
Instance details

Defined in Basement.NonEmpty

Associated Types

type Item (NonEmpty c) #

Methods

fromList :: [Item (NonEmpty c)] -> NonEmpty c #

fromListN :: Int -> [Item (NonEmpty c)] -> NonEmpty c #

toList :: NonEmpty c -> [Item (NonEmpty c)] #

PrimType ty => IsList (UArray ty) 
Instance details

Defined in Basement.UArray.Base

Associated Types

type Item (UArray ty) #

Methods

fromList :: [Item (UArray ty)] -> UArray ty #

fromListN :: Int -> [Item (UArray ty)] -> UArray ty #

toList :: UArray ty -> [Item (UArray ty)] #

IsList (IntMap a)

Since: containers-0.5.6.2

Instance details

Defined in Data.IntMap.Internal

Associated Types

type Item (IntMap a) #

Methods

fromList :: [Item (IntMap a)] -> IntMap a #

fromListN :: Int -> [Item (IntMap a)] -> IntMap a #

toList :: IntMap a -> [Item (IntMap a)] #

IsList (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Item (Seq a) #

Methods

fromList :: [Item (Seq a)] -> Seq a #

fromListN :: Int -> [Item (Seq a)] -> Seq a #

toList :: Seq a -> [Item (Seq a)] #

Ord a => IsList (Set a)

Since: containers-0.5.6.2

Instance details

Defined in Data.Set.Internal

Associated Types

type Item (Set a) #

Methods

fromList :: [Item (Set a)] -> Set a #

fromListN :: Int -> [Item (Set a)] -> Set a #

toList :: Set a -> [Item (Set a)] #

IsList (DNonEmpty a) 
Instance details

Defined in Data.DList.DNonEmpty.Internal

Associated Types

type Item (DNonEmpty a) #

Methods

fromList :: [Item (DNonEmpty a)] -> DNonEmpty a #

fromListN :: Int -> [Item (DNonEmpty a)] -> DNonEmpty a #

toList :: DNonEmpty a -> [Item (DNonEmpty a)] #

IsList (DList a) 
Instance details

Defined in Data.DList.Internal

Associated Types

type Item (DList a) #

Methods

fromList :: [Item (DList a)] -> DList a #

fromListN :: Int -> [Item (DList a)] -> DList a #

toList :: DList a -> [Item (DList a)] #

IsList (Bag a) 
Instance details

Defined in GHC.Data.Bag

Associated Types

type Item (Bag a) #

Methods

fromList :: [Item (Bag a)] -> Bag a #

fromListN :: Int -> [Item (Bag a)] -> Bag a #

toList :: Bag a -> [Item (Bag a)] #

(Eq a, Hashable a) => IsList (HashSet a) 
Instance details

Defined in Data.HashSet.Internal

Associated Types

type Item (HashSet a) #

Methods

fromList :: [Item (HashSet a)] -> HashSet a #

fromListN :: Int -> [Item (HashSet a)] -> HashSet a #

toList :: HashSet a -> [Item (HashSet a)] #

IsList (Array a) 
Instance details

Defined in Data.Primitive.Array

Associated Types

type Item (Array a) #

Methods

fromList :: [Item (Array a)] -> Array a #

fromListN :: Int -> [Item (Array a)] -> Array a #

toList :: Array a -> [Item (Array a)] #

Prim a => IsList (PrimArray a)

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.PrimArray

Associated Types

type Item (PrimArray a) #

Methods

fromList :: [Item (PrimArray a)] -> PrimArray a #

fromListN :: Int -> [Item (PrimArray a)] -> PrimArray a #

toList :: PrimArray a -> [Item (PrimArray a)] #

IsList (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Associated Types

type Item (SmallArray a) #

IsList (KeyMap v)

Since: aeson-2.0.2.0

Instance details

Defined in Data.Aeson.KeyMap

Associated Types

type Item (KeyMap v) #

Methods

fromList :: [Item (KeyMap v)] -> KeyMap v #

fromListN :: Int -> [Item (KeyMap v)] -> KeyMap v #

toList :: KeyMap v -> [Item (KeyMap v)] #

IsList (Vector a) 
Instance details

Defined in Data.Vector

Associated Types

type Item (Vector a) #

Methods

fromList :: [Item (Vector a)] -> Vector a #

fromListN :: Int -> [Item (Vector a)] -> Vector a #

toList :: Vector a -> [Item (Vector a)] #

Prim a => IsList (Vector a) 
Instance details

Defined in Data.Vector.Primitive

Associated Types

type Item (Vector a) #

Methods

fromList :: [Item (Vector a)] -> Vector a #

fromListN :: Int -> [Item (Vector a)] -> Vector a #

toList :: Vector a -> [Item (Vector a)] #

Storable a => IsList (Vector a) 
Instance details

Defined in Data.Vector.Storable

Associated Types

type Item (Vector a) #

Methods

fromList :: [Item (Vector a)] -> Vector a #

fromListN :: Int -> [Item (Vector a)] -> Vector a #

toList :: Vector a -> [Item (Vector a)] #

IsList (Vector a) 
Instance details

Defined in Data.Vector.Strict

Associated Types

type Item (Vector a) #

Methods

fromList :: [Item (Vector a)] -> Vector a #

fromListN :: Int -> [Item (Vector a)] -> Vector a #

toList :: Vector a -> [Item (Vector a)] #

IsList [a]

Since: base-4.7.0.0

Instance details

Defined in GHC.IsList

Associated Types

type Item [a] #

Methods

fromList :: [Item [a]] -> [a] #

fromListN :: Int -> [Item [a]] -> [a] #

toList :: [a] -> [Item [a]] #

Ord k => IsList (Map k v)

Since: containers-0.5.6.2

Instance details

Defined in Data.Map.Internal

Associated Types

type Item (Map k v) #

Methods

fromList :: [Item (Map k v)] -> Map k v #

fromListN :: Int -> [Item (Map k v)] -> Map k v #

toList :: Map k v -> [Item (Map k v)] #

(Eq k, Hashable k) => IsList (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

Associated Types

type Item (HashMap k v) #

Methods

fromList :: [Item (HashMap k v)] -> HashMap k v #

fromListN :: Int -> [Item (HashMap k v)] -> HashMap k v #

toList :: HashMap k v -> [Item (HashMap k v)] #

init' :: List a -> List a Source #

Remove the last element from a list if there is one, otherwise return Nil.

reverse' :: List a -> List a Source #

Reverse a list.

union' :: Eq a => List a -> List a -> List a Source #

unionBy' :: (a -> a -> Bool) -> List a -> List a -> List a Source #

nub' :: Eq a => List a -> List a Source #

nubBy' :: (a -> a -> Bool) -> List a -> List a Source #

filter' :: (a -> Bool) -> List a -> List a Source #

delete' :: Eq a => a -> List a -> List a Source #

deleteBy' :: (a -> a -> Bool) -> a -> List a -> List a Source #

(+++) :: List a -> List a -> List a Source #

Append two lists.

listToMaybe' :: List a -> Maybe' a Source #

Returns Nothing' on an empty list or Just' a where a is the first element of the list.

map' :: (a -> b) -> List a -> List b Source #

zip' :: List a -> List b -> List (a :* b) Source #

zipWith' :: (a -> b -> c) -> List a -> List b -> List c Source #

mapMaybe' :: (a -> Maybe' b) -> List a -> List b Source #

A version of map which can throw out elements. In particular, the function argument returns something of type Maybe' b. If this is Nothing', no element is added on to the result list. If it is Just' b, then b is included in the result list.

concatMap' :: (a -> List b) -> List a -> List b Source #

data a :* b infixr 2 Source #

Strict pair type.

Constructors

!a :* !b infixr 2 

Instances

Instances details
Functor ((:*) a) Source # 
Instance details

Defined in WidgetRattus.Strict

Methods

fmap :: (a0 -> b) -> (a :* a0) -> a :* b #

(<$) :: a0 -> (a :* b) -> a :* a0 #

(Continuous a, Continuous b) => Continuous (a :* b) Source # 
Instance details

Defined in WidgetRattus.Strict

Methods

progressAndNext :: InputValue -> (a :* b) -> (a :* b, Clock) Source #

progressInternal :: InputValue -> (a :* b) -> a :* b Source #

nextProgress :: (a :* b) -> Clock Source #

promoteInternal :: (a :* b) -> Box (a :* b) Source #

(Widgets w, Widgets v) => Widgets (w :* v) Source # 
Instance details

Defined in WidgetRattus.Widgets

Methods

toWidgetList :: (w :* v) -> List Widget Source #

(Show a, Show b) => Show (a :* b) Source # 
Instance details

Defined in WidgetRattus.Strict

Methods

showsPrec :: Int -> (a :* b) -> ShowS #

show :: (a :* b) -> String #

showList :: [a :* b] -> ShowS #

(Eq a, Eq b) => Eq (a :* b) Source # 
Instance details

Defined in WidgetRattus.Strict

Methods

(==) :: (a :* b) -> (a :* b) -> Bool #

(/=) :: (a :* b) -> (a :* b) -> Bool #

(VectorSpace v a, VectorSpace w a, Floating a, Eq a) => VectorSpace (v :* w) a Source # 
Instance details

Defined in WidgetRattus.Strict

Methods

zeroVector :: v :* w #

(*^) :: a -> (v :* w) -> v :* w #

(^/) :: (v :* w) -> a -> v :* w #

(^+^) :: (v :* w) -> (v :* w) -> v :* w #

(^-^) :: (v :* w) -> (v :* w) -> v :* w #

negateVector :: (v :* w) -> v :* w #

dot :: (v :* w) -> (v :* w) -> a #

norm :: (v :* w) -> a #

normalize :: (v :* w) -> v :* w #

data Maybe' a Source #

Strict variant of Maybe.

Constructors

Just' !a 
Nothing' 

Instances

Instances details
Continuous a => Continuous (Maybe' a) Source # 
Instance details

Defined in WidgetRattus.Strict

Show a => Show (Maybe' a) Source # 
Instance details

Defined in WidgetRattus.Strict

Methods

showsPrec :: Int -> Maybe' a -> ShowS #

show :: Maybe' a -> String #

showList :: [Maybe' a] -> ShowS #

Eq a => Eq (Maybe' a) Source # 
Instance details

Defined in WidgetRattus.Strict

Methods

(==) :: Maybe' a -> Maybe' a -> Bool #

(/=) :: Maybe' a -> Maybe' a -> Bool #

Ord a => Ord (Maybe' a) Source # 
Instance details

Defined in WidgetRattus.Strict

Methods

compare :: Maybe' a -> Maybe' a -> Ordering #

(<) :: Maybe' a -> Maybe' a -> Bool #

(<=) :: Maybe' a -> Maybe' a -> Bool #

(>) :: Maybe' a -> Maybe' a -> Bool #

(>=) :: Maybe' a -> Maybe' a -> Bool #

max :: Maybe' a -> Maybe' a -> Maybe' a #

min :: Maybe' a -> Maybe' a -> Maybe' a #

maybe' :: b -> (a -> b) -> Maybe' a -> b Source #

takes a default value, a function, and a Maybe' value. If the Maybe' value is Nothing', the function returns the default value. Otherwise, it applies the function to the value inside the Just' and returns the result.

fromMaybe' :: a -> Maybe' a -> a Source #

fst' :: (a :* b) -> a Source #

First projection function.

snd' :: (a :* b) -> b Source #

Second projection function.

curry' :: ((a :* b) -> c) -> a -> b -> c Source #

uncurry' :: (a -> b -> c) -> (a :* b) -> c Source #

toText :: Show a => a -> Text Source #