uni-util-2.3.0.2: Utilities for the uniform workbench

Safe HaskellNone
LanguageHaskell98

Util.Registry

Description

A Registry is a mapping from ordered values. For the Registry type itself, all target values have the same type. For the UntypedRegistry type, the values can have any Typeable type.

Synopsis

Documentation

data Ord from => Registry from to Source #

Instances
Ord from => ListRegistryContents Registry from to Source # 
Instance details

Defined in Util.Registry

Methods

listRegistryContents :: Registry from to -> IO [(from, to)] Source #

listRegistryContentsAndEmptyRegistry :: Registry from to -> IO [(from, to)] Source #

listToNewRegistry :: [(from, to)] -> IO (Registry from to) Source #

Ord from => NewRegistry (Registry from to) Source # 
Instance details

Defined in Util.Registry

Methods

newRegistry :: IO (Registry from to) Source #

emptyRegistry :: Registry from to -> IO () Source #

(HasBinary (from, to) m, Ord from, MonadIO m) => HasBinary (Registry from to) m Source # 
Instance details

Defined in Util.Registry

Methods

writeBin :: WriteBinary m -> Registry from to -> m () Source #

readBin :: ReadBinary m -> m (Registry from to) Source #

Ord from => KeyOpsRegistry (Registry from to) from Source # 
Instance details

Defined in Util.Registry

Methods

deleteFromRegistryBool :: Registry from to -> from -> IO Bool Source #

deleteFromRegistry :: Registry from to -> from -> IO () Source #

listKeys :: Registry from to -> IO [from] Source #

Ord from => GetSetRegistry (Registry from to) from to Source # 
Instance details

Defined in Util.Registry

Methods

transformValue :: Registry from to -> from -> (Maybe to -> IO (Maybe to, extra)) -> IO extra Source #

getValueOpt :: Registry from to -> from -> IO (Maybe to) Source #

getValue :: Registry from to -> from -> IO to Source #

setValue :: Registry from to -> from -> to -> IO () Source #

data LockedRegistry from to Source #

Instances
Ord from => NewRegistry (LockedRegistry from to) Source # 
Instance details

Defined in Util.Registry

Ord from => KeyOpsRegistry (LockedRegistry from to) from Source # 
Instance details

Defined in Util.Registry

Methods

deleteFromRegistryBool :: LockedRegistry from to -> from -> IO Bool Source #

deleteFromRegistry :: LockedRegistry from to -> from -> IO () Source #

listKeys :: LockedRegistry from to -> IO [from] Source #

Ord from => GetSetRegistry (LockedRegistry from to) from to Source # 
Instance details

Defined in Util.Registry

Methods

transformValue :: LockedRegistry from to -> from -> (Maybe to -> IO (Maybe to, extra)) -> IO extra Source #

getValueOpt :: LockedRegistry from to -> from -> IO (Maybe to) Source #

getValue :: LockedRegistry from to -> from -> IO to Source #

setValue :: LockedRegistry from to -> from -> to -> IO () Source #

data Untyped registry from Source #

Instances
NewRegistry (registry from Dyn) => NewRegistry (Untyped registry from) Source # 
Instance details

Defined in Util.Registry

Methods

newRegistry :: IO (Untyped registry from) Source #

emptyRegistry :: Untyped registry from -> IO () Source #

GetSetRegistry (registry from Dyn) from Dyn => GetSetRegistryDyn (Untyped registry from) from Source # 
Instance details

Defined in Util.Registry

Methods

setValueAsDyn :: Untyped registry from -> from -> Dyn -> IO () Source #

getValueAsDyn :: Untyped registry from -> from -> IO Dyn Source #

KeyOpsRegistry (registry from Dyn) from => KeyOpsRegistry (Untyped registry from) from Source # 
Instance details

Defined in Util.Registry

Methods

deleteFromRegistryBool :: Untyped registry from -> from -> IO Bool Source #

deleteFromRegistry :: Untyped registry from -> from -> IO () Source #

listKeys :: Untyped registry from -> IO [from] Source #

(Typeable to, GetSetRegistry (registry from Dyn) from Dyn) => GetSetRegistry (Untyped registry from) from to Source # 
Instance details

Defined in Util.Registry

Methods

transformValue :: Untyped registry from -> from -> (Maybe to -> IO (Maybe to, extra)) -> IO extra Source #

getValueOpt :: Untyped registry from -> from -> IO (Maybe to) Source #

getValue :: Untyped registry from -> from -> IO to Source #

setValue :: Untyped registry from -> from -> to -> IO () Source #

data Unsafe registry from Source #

Instances
NewRegistry (registry from Obj) => NewRegistry (Unsafe registry from) Source # 
Instance details

Defined in Util.Registry

Methods

newRegistry :: IO (Unsafe registry from) Source #

emptyRegistry :: Unsafe registry from -> IO () Source #

KeyOpsRegistry (registry from Obj) from => KeyOpsRegistry (Unsafe registry from) from Source # 
Instance details

Defined in Util.Registry

Methods

deleteFromRegistryBool :: Unsafe registry from -> from -> IO Bool Source #

deleteFromRegistry :: Unsafe registry from -> from -> IO () Source #

listKeys :: Unsafe registry from -> IO [from] Source #

GetSetRegistry (registry from Obj) from Obj => GetSetRegistry (Unsafe registry from) from to Source # 
Instance details

Defined in Util.Registry

Methods

transformValue :: Unsafe registry from -> from -> (Maybe to -> IO (Maybe to, extra)) -> IO extra Source #

getValueOpt :: Unsafe registry from -> from -> IO (Maybe to) Source #

getValue :: Unsafe registry from -> from -> IO to Source #

setValue :: Unsafe registry from -> from -> to -> IO () Source #

class NewRegistry registry where Source #

Minimal complete definition

newRegistry, emptyRegistry

Methods

newRegistry :: IO registry Source #

emptyRegistry :: registry -> IO () Source #

Instances
Ord from => NewRegistry (LockedRegistry from to) Source # 
Instance details

Defined in Util.Registry

NewRegistry (registry from Obj) => NewRegistry (Unsafe registry from) Source # 
Instance details

Defined in Util.Registry

Methods

newRegistry :: IO (Unsafe registry from) Source #

emptyRegistry :: Unsafe registry from -> IO () Source #

NewRegistry (registry from Dyn) => NewRegistry (Untyped registry from) Source # 
Instance details

Defined in Util.Registry

Methods

newRegistry :: IO (Untyped registry from) Source #

emptyRegistry :: Untyped registry from -> IO () Source #

Ord from => NewRegistry (Registry from to) Source # 
Instance details

Defined in Util.Registry

Methods

newRegistry :: IO (Registry from to) Source #

emptyRegistry :: Registry from to -> IO () Source #

class GetSetRegistry registry from to where Source #

Minimal complete definition

transformValue

Methods

transformValue :: registry -> from -> (Maybe to -> IO (Maybe to, extra)) -> IO extra Source #

getValueOpt :: registry -> from -> IO (Maybe to) Source #

getValue :: registry -> from -> IO to Source #

setValue :: registry -> from -> to -> IO () Source #

Instances
Ord from => GetSetRegistry (LockedRegistry from to) from to Source # 
Instance details

Defined in Util.Registry

Methods

transformValue :: LockedRegistry from to -> from -> (Maybe to -> IO (Maybe to, extra)) -> IO extra Source #

getValueOpt :: LockedRegistry from to -> from -> IO (Maybe to) Source #

getValue :: LockedRegistry from to -> from -> IO to Source #

setValue :: LockedRegistry from to -> from -> to -> IO () Source #

GetSetRegistry (registry from Obj) from Obj => GetSetRegistry (Unsafe registry from) from to Source # 
Instance details

Defined in Util.Registry

Methods

transformValue :: Unsafe registry from -> from -> (Maybe to -> IO (Maybe to, extra)) -> IO extra Source #

getValueOpt :: Unsafe registry from -> from -> IO (Maybe to) Source #

getValue :: Unsafe registry from -> from -> IO to Source #

setValue :: Unsafe registry from -> from -> to -> IO () Source #

(Typeable to, GetSetRegistry (registry from Dyn) from Dyn) => GetSetRegistry (Untyped registry from) from to Source # 
Instance details

Defined in Util.Registry

Methods

transformValue :: Untyped registry from -> from -> (Maybe to -> IO (Maybe to, extra)) -> IO extra Source #

getValueOpt :: Untyped registry from -> from -> IO (Maybe to) Source #

getValue :: Untyped registry from -> from -> IO to Source #

setValue :: Untyped registry from -> from -> to -> IO () Source #

Ord from => GetSetRegistry (Registry from to) from to Source # 
Instance details

Defined in Util.Registry

Methods

transformValue :: Registry from to -> from -> (Maybe to -> IO (Maybe to, extra)) -> IO extra Source #

getValueOpt :: Registry from to -> from -> IO (Maybe to) Source #

getValue :: Registry from to -> from -> IO to Source #

setValue :: Registry from to -> from -> to -> IO () Source #

class GetSetRegistryDyn registry from where Source #

Minimal complete definition

setValueAsDyn, getValueAsDyn

Methods

setValueAsDyn :: registry -> from -> Dyn -> IO () Source #

getValueAsDyn :: registry -> from -> IO Dyn Source #

Instances
GetSetRegistry (registry from Dyn) from Dyn => GetSetRegistryDyn (Untyped registry from) from Source # 
Instance details

Defined in Util.Registry

Methods

setValueAsDyn :: Untyped registry from -> from -> Dyn -> IO () Source #

getValueAsDyn :: Untyped registry from -> from -> IO Dyn Source #

class KeyOpsRegistry registry from where Source #

Minimal complete definition

deleteFromRegistryBool, listKeys

Methods

deleteFromRegistryBool :: registry -> from -> IO Bool Source #

deleteFromRegistry :: registry -> from -> IO () Source #

listKeys :: registry -> IO [from] Source #

Instances
Ord from => KeyOpsRegistry (LockedRegistry from to) from Source # 
Instance details

Defined in Util.Registry

Methods

deleteFromRegistryBool :: LockedRegistry from to -> from -> IO Bool Source #

deleteFromRegistry :: LockedRegistry from to -> from -> IO () Source #

listKeys :: LockedRegistry from to -> IO [from] Source #

KeyOpsRegistry (registry from Obj) from => KeyOpsRegistry (Unsafe registry from) from Source # 
Instance details

Defined in Util.Registry

Methods

deleteFromRegistryBool :: Unsafe registry from -> from -> IO Bool Source #

deleteFromRegistry :: Unsafe registry from -> from -> IO () Source #

listKeys :: Unsafe registry from -> IO [from] Source #

KeyOpsRegistry (registry from Dyn) from => KeyOpsRegistry (Untyped registry from) from Source # 
Instance details

Defined in Util.Registry

Methods

deleteFromRegistryBool :: Untyped registry from -> from -> IO Bool Source #

deleteFromRegistry :: Untyped registry from -> from -> IO () Source #

listKeys :: Untyped registry from -> IO [from] Source #

Ord from => KeyOpsRegistry (Registry from to) from Source # 
Instance details

Defined in Util.Registry

Methods

deleteFromRegistryBool :: Registry from to -> from -> IO Bool Source #

deleteFromRegistry :: Registry from to -> from -> IO () Source #

listKeys :: Registry from to -> IO [from] Source #

class ListRegistryContents registry from to where Source #

ListRegistryContents will not be implemented for the untyped registries.

Methods

listRegistryContents :: registry from to -> IO [(from, to)] Source #

listRegistryContentsAndEmptyRegistry Source #

Arguments

:: registry from to 
-> IO [(from, to)]

this is atomic.

listToNewRegistry :: [(from, to)] -> IO (registry from to) Source #

Instances
Ord from => ListRegistryContents Registry from to Source # 
Instance details

Defined in Util.Registry

Methods

listRegistryContents :: Registry from to -> IO [(from, to)] Source #

listRegistryContentsAndEmptyRegistry :: Registry from to -> IO [(from, to)] Source #

listToNewRegistry :: [(from, to)] -> IO (Registry from to) Source #

changeKey :: Ord from => Registry from to -> from -> from -> IO () Source #

look up the element given by the first key, and if it exists delete it, replacing it with the element given by the second key.

getRegistryValue :: Ord from => Registry from to -> from -> IO to Source #

getValueDefault :: GetSetRegistry registry from to => to -> registry -> from -> IO to Source #

getValue' :: GetSetRegistry registry from to => String -> registry -> from -> IO to Source #

getValueSafe :: GetSetRegistry registry from to => String -> registry -> from -> IO to Source #

getRegistryValueSafe :: Ord from => String -> Registry from to -> from -> IO to Source #