Shpadoinkle-widgets-0.0.0.2: A collection of common reusable types and components.

Safe HaskellNone
LanguageHaskell2010

Shpadoinkle.Widgets.Types.Choice

Documentation

data Pick Source #

Constructors

One 
AtleastOne 
Many 

type family Selected (p :: Pick) (a :: Type) :: Type where ... Source #

Equations

Selected One a = Maybe a 
Selected AtleastOne a = a 
Selected Many a = Set a 

data Choice (p :: Pick) a Source #

Constructors

Choice 

Fields

Instances
Deselection Choice One Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

noselection :: (Foldable g, Ord a) => g a -> Choice One a Source #

deselect :: Ord a => Choice One a -> Choice One a Source #

Deselection Choice Many Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

noselection :: (Foldable g, Ord a) => g a -> Choice Many a Source #

deselect :: Ord a => Choice Many a -> Choice Many a Source #

Selection Choice One Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

select :: Ord a => Choice One a -> Selected One a -> Choice One a Source #

select' :: Ord a => Choice One a -> a -> Choice One a Source #

unselected :: Ord a => Choice One a -> Set a Source #

selected :: Ord a => Choice One a -> Selected One a Source #

withOptions :: (Foldable g, Ord a) => Selected One a -> g a -> Choice One a Source #

withOptions' :: (Foldable g, Ord a) => a -> g a -> Choice One a Source #

Selection Choice AtleastOne Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Selection Choice Many Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

select :: Ord a => Choice Many a -> Selected Many a -> Choice Many a Source #

select' :: Ord a => Choice Many a -> a -> Choice Many a Source #

unselected :: Ord a => Choice Many a -> Set a Source #

selected :: Ord a => Choice Many a -> Selected Many a Source #

withOptions :: (Foldable g, Ord a) => Selected Many a -> g a -> Choice Many a Source #

withOptions' :: (Foldable g, Ord a) => a -> g a -> Choice Many a Source #

Foldable (Choice One) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

fold :: Monoid m => Choice One m -> m #

foldMap :: Monoid m => (a -> m) -> Choice One a -> m #

foldr :: (a -> b -> b) -> b -> Choice One a -> b #

foldr' :: (a -> b -> b) -> b -> Choice One a -> b #

foldl :: (b -> a -> b) -> b -> Choice One a -> b #

foldl' :: (b -> a -> b) -> b -> Choice One a -> b #

foldr1 :: (a -> a -> a) -> Choice One a -> a #

foldl1 :: (a -> a -> a) -> Choice One a -> a #

toList :: Choice One a -> [a] #

null :: Choice One a -> Bool #

length :: Choice One a -> Int #

elem :: Eq a => a -> Choice One a -> Bool #

maximum :: Ord a => Choice One a -> a #

minimum :: Ord a => Choice One a -> a #

sum :: Num a => Choice One a -> a #

product :: Num a => Choice One a -> a #

Foldable (Choice AtleastOne) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

fold :: Monoid m => Choice AtleastOne m -> m #

foldMap :: Monoid m => (a -> m) -> Choice AtleastOne a -> m #

foldr :: (a -> b -> b) -> b -> Choice AtleastOne a -> b #

foldr' :: (a -> b -> b) -> b -> Choice AtleastOne a -> b #

foldl :: (b -> a -> b) -> b -> Choice AtleastOne a -> b #

foldl' :: (b -> a -> b) -> b -> Choice AtleastOne a -> b #

foldr1 :: (a -> a -> a) -> Choice AtleastOne a -> a #

foldl1 :: (a -> a -> a) -> Choice AtleastOne a -> a #

toList :: Choice AtleastOne a -> [a] #

null :: Choice AtleastOne a -> Bool #

length :: Choice AtleastOne a -> Int #

elem :: Eq a => a -> Choice AtleastOne a -> Bool #

maximum :: Ord a => Choice AtleastOne a -> a #

minimum :: Ord a => Choice AtleastOne a -> a #

sum :: Num a => Choice AtleastOne a -> a #

product :: Num a => Choice AtleastOne a -> a #

Foldable (Choice Many) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

fold :: Monoid m => Choice Many m -> m #

foldMap :: Monoid m => (a -> m) -> Choice Many a -> m #

foldr :: (a -> b -> b) -> b -> Choice Many a -> b #

foldr' :: (a -> b -> b) -> b -> Choice Many a -> b #

foldl :: (b -> a -> b) -> b -> Choice Many a -> b #

foldl' :: (b -> a -> b) -> b -> Choice Many a -> b #

foldr1 :: (a -> a -> a) -> Choice Many a -> a #

foldl1 :: (a -> a -> a) -> Choice Many a -> a #

toList :: Choice Many a -> [a] #

null :: Choice Many a -> Bool #

length :: Choice Many a -> Int #

elem :: Eq a => a -> Choice Many a -> Bool #

maximum :: Ord a => Choice Many a -> a #

minimum :: Ord a => Choice Many a -> a #

sum :: Num a => Choice Many a -> a #

product :: Num a => Choice Many a -> a #

Compactable (Choice One) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

compact :: Choice One (Maybe a) -> Choice One a #

separate :: Choice One (Either l r) -> (Choice One l, Choice One r) #

filter :: (a -> Bool) -> Choice One a -> Choice One a #

partition :: (a -> Bool) -> Choice One a -> (Choice One a, Choice One a) #

fmapMaybe :: Functor (Choice One) => (a -> Maybe b) -> Choice One a -> Choice One b #

fmapEither :: Functor (Choice One) => (a -> Either l r) -> Choice One a -> (Choice One l, Choice One r) #

applyMaybe :: Applicative (Choice One) => Choice One (a -> Maybe b) -> Choice One a -> Choice One b #

applyEither :: Applicative (Choice One) => Choice One (a -> Either l r) -> Choice One a -> (Choice One l, Choice One r) #

bindMaybe :: Monad (Choice One) => Choice One a -> (a -> Choice One (Maybe b)) -> Choice One b #

bindEither :: Monad (Choice One) => Choice One a -> (a -> Choice One (Either l r)) -> (Choice One l, Choice One r) #

traverseMaybe :: (Applicative g, Traversable (Choice One)) => (a -> g (Maybe b)) -> Choice One a -> g (Choice One b) #

traverseEither :: (Applicative g, Traversable (Choice One)) => (a -> g (Either l r)) -> Choice One a -> g (Choice One l, Choice One r) #

Compactable (Choice Many) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

compact :: Choice Many (Maybe a) -> Choice Many a #

separate :: Choice Many (Either l r) -> (Choice Many l, Choice Many r) #

filter :: (a -> Bool) -> Choice Many a -> Choice Many a #

partition :: (a -> Bool) -> Choice Many a -> (Choice Many a, Choice Many a) #

fmapMaybe :: Functor (Choice Many) => (a -> Maybe b) -> Choice Many a -> Choice Many b #

fmapEither :: Functor (Choice Many) => (a -> Either l r) -> Choice Many a -> (Choice Many l, Choice Many r) #

applyMaybe :: Applicative (Choice Many) => Choice Many (a -> Maybe b) -> Choice Many a -> Choice Many b #

applyEither :: Applicative (Choice Many) => Choice Many (a -> Either l r) -> Choice Many a -> (Choice Many l, Choice Many r) #

bindMaybe :: Monad (Choice Many) => Choice Many a -> (a -> Choice Many (Maybe b)) -> Choice Many b #

bindEither :: Monad (Choice Many) => Choice Many a -> (a -> Choice Many (Either l r)) -> (Choice Many l, Choice Many r) #

traverseMaybe :: (Applicative g, Traversable (Choice Many)) => (a -> g (Maybe b)) -> Choice Many a -> g (Choice Many b) #

traverseEither :: (Applicative g, Traversable (Choice Many)) => (a -> g (Either l r)) -> Choice Many a -> g (Choice Many l, Choice Many r) #

SetLike (Choice One) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

toSet :: Ord a => Choice One a -> Set a Source #

smap :: Ord b => (a -> b) -> Choice One a -> Choice One b Source #

valid :: Ord a => Choice One a -> Bool Source #

SetLike (Choice AtleastOne) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

toSet :: Ord a => Choice AtleastOne a -> Set a Source #

smap :: Ord b => (a -> b) -> Choice AtleastOne a -> Choice AtleastOne b Source #

valid :: Ord a => Choice AtleastOne a -> Bool Source #

SetLike (Choice Many) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

toSet :: Ord a => Choice Many a -> Set a Source #

smap :: Ord b => (a -> b) -> Choice Many a -> Choice Many b Source #

valid :: Ord a => Choice Many a -> Bool Source #

(Bounded a, Enum a) => Bounded (Choice AtleastOne a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

(Bounded a, Enum a) => Enum (Choice AtleastOne a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

(Eq (Selected p a), Eq a) => Eq (Choice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

(==) :: Choice p a -> Choice p a -> Bool #

(/=) :: Choice p a -> Choice p a -> Bool #

(Ord (Selected p a), Ord a) => Ord (Choice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

compare :: Choice p a -> Choice p a -> Ordering #

(<) :: Choice p a -> Choice p a -> Bool #

(<=) :: Choice p a -> Choice p a -> Bool #

(>) :: Choice p a -> Choice p a -> Bool #

(>=) :: Choice p a -> Choice p a -> Bool #

max :: Choice p a -> Choice p a -> Choice p a #

min :: Choice p a -> Choice p a -> Choice p a #

(Read (Selected p a), Read a, Ord a) => Read (Choice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

(Show (Selected p a), Show a) => Show (Choice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

showsPrec :: Int -> Choice p a -> ShowS #

show :: Choice p a -> String #

showList :: [Choice p a] -> ShowS #

Generic (Choice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Associated Types

type Rep (Choice p a) :: Type -> Type #

Methods

from :: Choice p a -> Rep (Choice p a) x #

to :: Rep (Choice p a) x -> Choice p a #

Ord a => Semigroup (Choice One a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

(<>) :: Choice One a -> Choice One a -> Choice One a #

sconcat :: NonEmpty (Choice One a) -> Choice One a #

stimes :: Integral b => b -> Choice One a -> Choice One a #

Ord a => Semigroup (Choice AtleastOne a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Ord a => Semigroup (Choice Many a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

(<>) :: Choice Many a -> Choice Many a -> Choice Many a #

sconcat :: NonEmpty (Choice Many a) -> Choice Many a #

stimes :: Integral b => b -> Choice Many a -> Choice Many a #

Ord a => Monoid (Choice One a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

mempty :: Choice One a #

mappend :: Choice One a -> Choice One a -> Choice One a #

mconcat :: [Choice One a] -> Choice One a #

Ord a => Monoid (Choice Many a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

(ToJSON (Selected p a), ToJSON a) => ToJSON (Choice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

toJSON :: Choice p a -> Value #

toEncoding :: Choice p a -> Encoding #

toJSONList :: [Choice p a] -> Value #

toEncodingList :: [Choice p a] -> Encoding #

(FromJSON (Selected p a), FromJSON a, Ord a) => FromJSON (Choice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

parseJSON :: Value -> Parser (Choice p a) #

parseJSONList :: Value -> Parser [Choice p a] #

type Rep (Choice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

type Rep (Choice p a) = D1 (MetaData "Choice" "Shpadoinkle.Widgets.Types.Choice" "Shpadoinkle-widgets-0.0.0.2-inplace" False) (C1 (MetaCons "Choice" PrefixI True) (S1 (MetaSel (Just "_selected") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Selected p a)) :*: S1 (MetaSel (Just "_options") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set a))))

class SetLike f where Source #

Methods

toSet :: Ord a => f a -> Set a Source #

smap :: Ord b => (a -> b) -> f a -> f b Source #

valid :: Ord a => f a -> Bool Source #

Instances
SetLike Maybe Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

toSet :: Ord a => Maybe a -> Set a Source #

smap :: Ord b => (a -> b) -> Maybe a -> Maybe b Source #

valid :: Ord a => Maybe a -> Bool Source #

SetLike Set Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

toSet :: Ord a => Set a -> Set a Source #

smap :: Ord b => (a -> b) -> Set a -> Set b Source #

valid :: Ord a => Set a -> Bool Source #

(Considered p ~ Maybe, SetLike (Choice p)) => SetLike (ConsideredChoice p) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

toSet :: Ord a => ConsideredChoice p a -> Set a Source #

smap :: Ord b => (a -> b) -> ConsideredChoice p a -> ConsideredChoice p b Source #

valid :: Ord a => ConsideredChoice p a -> Bool Source #

SetLike (ConsideredChoice Many) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

SetLike (Choice One) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

toSet :: Ord a => Choice One a -> Set a Source #

smap :: Ord b => (a -> b) -> Choice One a -> Choice One b Source #

valid :: Ord a => Choice One a -> Bool Source #

SetLike (Choice AtleastOne) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

toSet :: Ord a => Choice AtleastOne a -> Set a Source #

smap :: Ord b => (a -> b) -> Choice AtleastOne a -> Choice AtleastOne b Source #

valid :: Ord a => Choice AtleastOne a -> Bool Source #

SetLike (Choice Many) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

toSet :: Ord a => Choice Many a -> Set a Source #

smap :: Ord b => (a -> b) -> Choice Many a -> Choice Many b Source #

valid :: Ord a => Choice Many a -> Bool Source #

SetLike (ConsideredChoice p) => SetLike (Dropdown p) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Form.Dropdown

Methods

toSet :: Ord a => Dropdown p a -> Set a Source #

smap :: Ord b => (a -> b) -> Dropdown p a -> Dropdown p b Source #

valid :: Ord a => Dropdown p a -> Bool Source #

ftoSet :: (Ord a, Foldable g) => g a -> Set a Source #

class SetLike (f p) => Selection f (p :: Pick) where Source #

Methods

select :: Ord a => f p a -> Selected p a -> f p a Source #

select' :: Ord a => f p a -> a -> f p a Source #

unselected :: Ord a => f p a -> Set a Source #

selected :: Ord a => f p a -> Selected p a Source #

withOptions :: (Foldable g, Ord a) => Selected p a -> g a -> f p a Source #

withOptions' :: (Foldable g, Ord a) => a -> g a -> f p a Source #

Instances
(Considered p ~ Maybe, SetLike (ConsideredChoice p), Selection Choice p) => Selection ConsideredChoice p Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

SetLike (ConsideredChoice Many) => Selection ConsideredChoice Many Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Selection Choice One Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

select :: Ord a => Choice One a -> Selected One a -> Choice One a Source #

select' :: Ord a => Choice One a -> a -> Choice One a Source #

unselected :: Ord a => Choice One a -> Set a Source #

selected :: Ord a => Choice One a -> Selected One a Source #

withOptions :: (Foldable g, Ord a) => Selected One a -> g a -> Choice One a Source #

withOptions' :: (Foldable g, Ord a) => a -> g a -> Choice One a Source #

Selection Choice AtleastOne Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Selection Choice Many Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

select :: Ord a => Choice Many a -> Selected Many a -> Choice Many a Source #

select' :: Ord a => Choice Many a -> a -> Choice Many a Source #

unselected :: Ord a => Choice Many a -> Set a Source #

selected :: Ord a => Choice Many a -> Selected Many a Source #

withOptions :: (Foldable g, Ord a) => Selected Many a -> g a -> Choice Many a Source #

withOptions' :: (Foldable g, Ord a) => a -> g a -> Choice Many a Source #

Consideration ConsideredChoice p => Selection Dropdown p Source # 
Instance details

Defined in Shpadoinkle.Widgets.Form.Dropdown

Methods

select :: Ord a => Dropdown p a -> Selected p a -> Dropdown p a Source #

select' :: Ord a => Dropdown p a -> a -> Dropdown p a Source #

unselected :: Ord a => Dropdown p a -> Set a Source #

selected :: Ord a => Dropdown p a -> Selected p a Source #

withOptions :: (Foldable g, Ord a) => Selected p a -> g a -> Dropdown p a Source #

withOptions' :: (Foldable g, Ord a) => a -> g a -> Dropdown p a Source #

class Selection f p => Deselection f (p :: Pick) where Source #

Methods

noselection :: (Foldable g, Ord a) => g a -> f p a Source #

deselect :: Ord a => f p a -> f p a Source #

unsafeSelectFirst :: (Selection f p, Ord a) => f p a -> f p a Source #

unsafeSelectLast :: (Selection f p, Ord a) => f p a -> f p a Source #

selectFirst :: (Selection f p, Ord a) => f p a -> Maybe (f p a) Source #

selectLast :: (Selection f p, Ord a) => f p a -> Maybe (f p a) Source #

fullset :: (Bounded a, Enum a) => Set a Source #

fullOptions :: (Deselection f p, Bounded a, Enum a, Ord a) => f p a Source #

fullOptionsMin :: (Selection f p, Bounded a, Enum a, Ord a) => f p a Source #

fullOptionsMax :: (Selection f p, Bounded a, Enum a, Ord a) => f p a Source #

fromNonEmpty :: (Selection f p, Ord a) => NonEmpty a -> f p a Source #

selectWhen :: (SetLike g, Selection f Many, Ord a) => (a -> Bool) -> g a -> Maybe (f Many a) Source #

selectFirstWhen :: (SetLike g, Deselection f p, Ord a) => (a -> Bool) -> g a -> Maybe (f p a) Source #

selectLastWhen :: (SetLike g, Deselection f p, Ord a) => (a -> Bool) -> g a -> Maybe (f p a) Source #

toList :: (SetLike f, Ord a) => f a -> [a] Source #

singleton :: (Selection f p, Ord a) => a -> f p a Source #

size :: (SetLike g, Ord a) => g a -> Int Source #

insert :: (Selection f p, Ord a) => a -> f p a -> f p a Source #

delete :: (Compactable (f p), Ord a) => a -> f p a -> f p a Source #

addSelection :: (Selection f Many, Ord a) => a -> f Many a -> f Many a Source #

deselectMany :: (Compactable (f p), Ord a) => Set a -> f p a -> f p a Source #

data ConsideredChoice p a Source #

Constructors

ConsideredChoice 

Fields

Instances
Consideration ConsideredChoice One Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Consideration ConsideredChoice AtleastOne Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Selection ConsideredChoice Many => Consideration ConsideredChoice Many Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Selection ConsideredChoice One => Deselection ConsideredChoice One Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Selection ConsideredChoice Many => Deselection ConsideredChoice Many Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

(Considered p ~ Maybe, SetLike (ConsideredChoice p), Selection Choice p) => Selection ConsideredChoice p Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

SetLike (ConsideredChoice Many) => Selection ConsideredChoice Many Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

(Compactable (Choice p), Compactable (Considered p)) => Compactable (ConsideredChoice p) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

(Considered p ~ Maybe, SetLike (Choice p)) => SetLike (ConsideredChoice p) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Methods

toSet :: Ord a => ConsideredChoice p a -> Set a Source #

smap :: Ord b => (a -> b) -> ConsideredChoice p a -> ConsideredChoice p b Source #

valid :: Ord a => ConsideredChoice p a -> Bool Source #

SetLike (ConsideredChoice Many) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

(Eq (Selected p a), Eq (Considered p a), Eq a) => Eq (ConsideredChoice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

(Ord (Selected p a), Ord (Considered p a), Ord a) => Ord (ConsideredChoice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

(Read (Selected p a), Read (Considered p a), Read a, Ord a) => Read (ConsideredChoice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

(Show (Selected p a), Show (Considered p a), Show a) => Show (ConsideredChoice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Generic (ConsideredChoice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Associated Types

type Rep (ConsideredChoice p a) :: Type -> Type #

(Ord a, Considered p ~ Maybe, Semigroup (Choice p a)) => Semigroup (ConsideredChoice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Ord a => Semigroup (ConsideredChoice Many a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

(ToJSON a, ToJSON (Considered p a), ToJSON (Selected p a)) => ToJSON (ConsideredChoice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

(FromJSON a, FromJSON (Considered p a), FromJSON (Selected p a), Ord a) => FromJSON (ConsideredChoice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

type Rep (ConsideredChoice p a) Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

type Rep (ConsideredChoice p a) = D1 (MetaData "ConsideredChoice" "Shpadoinkle.Widgets.Types.Choice" "Shpadoinkle-widgets-0.0.0.2-inplace" False) (C1 (MetaCons "ConsideredChoice" PrefixI True) (S1 (MetaSel (Just "_consideration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Considered p a)) :*: S1 (MetaSel (Just "_choice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Choice p a))))

type family Considered (p :: Pick) :: Type -> Type where ... Source #

class Selection f p => Consideration f (p :: Pick) where Source #

Methods

consider :: Ord a => Considered p a -> f p a -> f p a Source #

consider' :: Ord a => a -> f p a -> f p a Source #

choose :: Ord a => f p a -> f p a Source #

choice :: Ord a => f p a -> Choice p a Source #

considered :: Ord a => f p a -> Considered p a Source #

shrug :: Ord a => f p a -> f p a Source #

Instances
Consideration ConsideredChoice One Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Consideration ConsideredChoice AtleastOne Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Selection ConsideredChoice Many => Consideration ConsideredChoice Many Source # 
Instance details

Defined in Shpadoinkle.Widgets.Types.Choice

Consideration ConsideredChoice p => Consideration Dropdown p Source # 
Instance details

Defined in Shpadoinkle.Widgets.Form.Dropdown

Methods

consider :: Ord a => Considered p a -> Dropdown p a -> Dropdown p a Source #

consider' :: Ord a => a -> Dropdown p a -> Dropdown p a Source #

choose :: Ord a => Dropdown p a -> Dropdown p a Source #

choice :: Ord a => Dropdown p a -> Choice p a Source #

considered :: Ord a => Dropdown p a -> Considered p a Source #

shrug :: Ord a => Dropdown p a -> Dropdown p a Source #

unsafeConsiderFirst :: (Consideration f p, Ord a) => f p a -> f p a Source #

unsafeConsiderLast :: (Consideration f p, Ord a) => f p a -> f p a Source #

considerNext :: (Considered p a ~ Maybe a, Consideration f p, Ord a) => f p a -> f p a Source #

considerPrev :: (Considered p a ~ Maybe a, Consideration f p, Ord a) => f p a -> f p a Source #