haskell-halogen-core
Safe HaskellNone
LanguageGHC2021

Halogen.Data.Slot

Documentation

data VoidF (p :: k) Source #

data Slot (query :: Type -> Type) output slotType Source #

data SlotElem (slots :: Row Type) (slot :: (Type -> Type) -> Type -> Type) where Source #

Constructors

SlotElem :: forall (sym' :: Symbol) (query :: Type -> Type) output s (slots :: Row Type) (slot :: (Type -> Type) -> Type -> Type). (HasType sym' (Slot query output s) slots, KnownSymbol sym', Ord s) => Proxy sym' -> s -> ~(slot query output) -> SlotElem slots slot 

Instances

Instances details
Eq (SlotElem slots' slot) Source # 
Instance details

Defined in Halogen.Data.Slot

Methods

(==) :: SlotElem slots' slot -> SlotElem slots' slot -> Bool #

(/=) :: SlotElem slots' slot -> SlotElem slots' slot -> Bool #

Ord (SlotElem slots' slot) Source # 
Instance details

Defined in Halogen.Data.Slot

Methods

compare :: SlotElem slots' slot -> SlotElem slots' slot -> Ordering #

(<) :: SlotElem slots' slot -> SlotElem slots' slot -> Bool #

(<=) :: SlotElem slots' slot -> SlotElem slots' slot -> Bool #

(>) :: SlotElem slots' slot -> SlotElem slots' slot -> Bool #

(>=) :: SlotElem slots' slot -> SlotElem slots' slot -> Bool #

max :: SlotElem slots' slot -> SlotElem slots' slot -> SlotElem slots' slot #

min :: SlotElem slots' slot -> SlotElem slots' slot -> SlotElem slots' slot #

newtype SlotStorage (slots :: Row Type) (slot :: (Type -> Type) -> Type -> Type) Source #

Constructors

SlotStorage (Set (SlotElem slots slot)) 

lookup :: forall (query :: Type -> Type) output s (slots' :: Row Type) slot. forall (symb :: Symbol) -> (HasType symb (Slot query output s) slots', KnownSymbol symb, Ord s) => s -> SlotStorage slots' slot -> Maybe (slot query output) Source #

empty :: forall (slots' :: Row Type) (slot :: (Type -> Type) -> Type -> Type). SlotStorage slots' slot Source #

pop :: forall (query :: Type -> Type) output s (slots' :: Row Type) slot. forall (symb :: Symbol) -> (HasType symb (Slot query output s) slots', KnownSymbol symb, Ord s) => s -> SlotStorage slots' slot -> Maybe (slot query output, SlotStorage slots' slot) Source #

insert :: forall (query :: Type -> Type) output s (slots' :: Row Type) slot. forall (symb :: Symbol) -> (HasType symb (Slot query output s) slots', KnownSymbol symb, Ord s) => s -> slot query output -> SlotStorage slots' slot -> SlotStorage slots' slot Source #

slots :: forall (query :: Type -> Type) output s (slots' :: Row Type) slot. forall (symb :: Symbol) -> (HasType symb (Slot query output s) slots', KnownSymbol symb, Ord s) => SlotStorage slots' slot -> Map s (slot query output) Source #

foreachSlot :: forall m (slots' :: Row Type) slot. Applicative m => SlotStorage slots' slot -> (forall (query :: Type -> Type) output. slot query output -> m ()) -> m () Source #