periodic-common-1.1.7.0: Periodic task system common.
Safe HaskellSafe
LanguageHaskell2010

Periodic.Types.Internal

Documentation

class FromBS a where Source #

Methods

fromBS :: ByteString -> a Source #

Instances

Instances details
FromBS ByteString Source # 
Instance details

Defined in Periodic.Types.Internal

FromBS ByteString Source # 
Instance details

Defined in Periodic.Types.Internal

FromBS Text Source # 
Instance details

Defined in Periodic.Types.Internal

FromBS Text Source # 
Instance details

Defined in Periodic.Types.Internal

FromBS Workload Source # 
Instance details

Defined in Periodic.Types.Job

FromBS JobName Source # 
Instance details

Defined in Periodic.Types.Job

FromBS FuncName Source # 
Instance details

Defined in Periodic.Types.Job

FromBS [Char] Source # 
Instance details

Defined in Periodic.Types.Internal

Methods

fromBS :: ByteString -> [Char] Source #

newtype ConfigKey Source #

Constructors

ConfigKey String 

Instances

Instances details
Show ConfigKey Source # 
Instance details

Defined in Periodic.Types.Internal

Binary ConfigKey Source # 
Instance details

Defined in Periodic.Types.Internal

Validatable ConfigKey Source # 
Instance details

Defined in Periodic.Types.Internal

newtype LockName Source #

Constructors

LockName ByteString 

Instances

Instances details
Eq LockName Source # 
Instance details

Defined in Periodic.Types.Internal

Ord LockName Source # 
Instance details

Defined in Periodic.Types.Internal

Show LockName Source # 
Instance details

Defined in Periodic.Types.Internal

IsString LockName Source # 
Instance details

Defined in Periodic.Types.Internal

Generic LockName Source # 
Instance details

Defined in Periodic.Types.Internal

Associated Types

type Rep LockName :: Type -> Type #

Methods

from :: LockName -> Rep LockName x #

to :: Rep LockName x -> LockName #

Binary LockName Source # 
Instance details

Defined in Periodic.Types.Internal

Methods

put :: LockName -> Put #

get :: Get LockName #

putList :: [LockName] -> Put #

Hashable LockName Source # 
Instance details

Defined in Periodic.Types.Internal

Methods

hashWithSalt :: Int -> LockName -> Int #

hash :: LockName -> Int #

Validatable LockName Source # 
Instance details

Defined in Periodic.Types.Internal

type Rep LockName Source # 
Instance details

Defined in Periodic.Types.Internal

type Rep LockName = D1 ('MetaData "LockName" "Periodic.Types.Internal" "periodic-common-1.1.7.0-inplace" 'True) (C1 ('MetaCons "LockName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

class Validatable a where Source #

Methods

validate :: a -> Either String () Source #

Instances

Instances details
Validatable ByteString Source # 
Instance details

Defined in Periodic.Types.Internal

Validatable LockName Source # 
Instance details

Defined in Periodic.Types.Internal

Validatable ConfigKey Source # 
Instance details

Defined in Periodic.Types.Internal

Validatable Job Source # 
Instance details

Defined in Periodic.Types.Job

Methods

validate :: Job -> Either String () Source #

Validatable Workload Source # 
Instance details

Defined in Periodic.Types.Job

Validatable JobHandle Source # 
Instance details

Defined in Periodic.Types.Job

Validatable JobName Source # 
Instance details

Defined in Periodic.Types.Job

Validatable FuncName Source # 
Instance details

Defined in Periodic.Types.Job

Validatable ClientCommand Source # 
Instance details

Defined in Periodic.Types.ClientCommand

Validatable ServerCommand Source # 
Instance details

Defined in Periodic.Types.ServerCommand

Validatable WorkerCommand Source # 
Instance details

Defined in Periodic.Types.WorkerCommand

Validatable a => Validatable [a] Source # 
Instance details

Defined in Periodic.Types.Internal

Methods

validate :: [a] -> Either String () Source #

validateNum :: Ord a => String -> a -> a -> a -> Either String () Source #

newtype Nid Source #

Constructors

Nid ByteString 

Instances

Instances details
Eq Nid Source # 
Instance details

Defined in Periodic.Types.Internal

Methods

(==) :: Nid -> Nid -> Bool #

(/=) :: Nid -> Nid -> Bool #

Ord Nid Source # 
Instance details

Defined in Periodic.Types.Internal

Methods

compare :: Nid -> Nid -> Ordering #

(<) :: Nid -> Nid -> Bool #

(<=) :: Nid -> Nid -> Bool #

(>) :: Nid -> Nid -> Bool #

(>=) :: Nid -> Nid -> Bool #

max :: Nid -> Nid -> Nid #

min :: Nid -> Nid -> Nid #

Show Nid Source # 
Instance details

Defined in Periodic.Types.Internal

Methods

showsPrec :: Int -> Nid -> ShowS #

show :: Nid -> String #

showList :: [Nid] -> ShowS #

Generic Nid Source # 
Instance details

Defined in Periodic.Types.Internal

Associated Types

type Rep Nid :: Type -> Type #

Methods

from :: Nid -> Rep Nid x #

to :: Rep Nid x -> Nid #

Hashable Nid Source # 
Instance details

Defined in Periodic.Types.Internal

Methods

hashWithSalt :: Int -> Nid -> Int #

hash :: Nid -> Int #

type Rep Nid Source # 
Instance details

Defined in Periodic.Types.Internal

type Rep Nid = D1 ('MetaData "Nid" "Periodic.Types.Internal" "periodic-common-1.1.7.0-inplace" 'True) (C1 ('MetaCons "Nid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype Msgid Source #

Constructors

Msgid ByteString 

Instances

Instances details
Eq Msgid Source # 
Instance details

Defined in Periodic.Types.Internal

Methods

(==) :: Msgid -> Msgid -> Bool #

(/=) :: Msgid -> Msgid -> Bool #

Ord Msgid Source # 
Instance details

Defined in Periodic.Types.Internal

Methods

compare :: Msgid -> Msgid -> Ordering #

(<) :: Msgid -> Msgid -> Bool #

(<=) :: Msgid -> Msgid -> Bool #

(>) :: Msgid -> Msgid -> Bool #

(>=) :: Msgid -> Msgid -> Bool #

max :: Msgid -> Msgid -> Msgid #

min :: Msgid -> Msgid -> Msgid #

Show Msgid Source # 
Instance details

Defined in Periodic.Types.Internal

Methods

showsPrec :: Int -> Msgid -> ShowS #

show :: Msgid -> String #

showList :: [Msgid] -> ShowS #

Generic Msgid Source # 
Instance details

Defined in Periodic.Types.Internal

Associated Types

type Rep Msgid :: Type -> Type #

Methods

from :: Msgid -> Rep Msgid x #

to :: Rep Msgid x -> Msgid #

Hashable Msgid Source # 
Instance details

Defined in Periodic.Types.Internal

Methods

hashWithSalt :: Int -> Msgid -> Int #

hash :: Msgid -> Int #

SetPacketId Msgid (Packet a) Source # 
Instance details

Defined in Periodic.Types.Packet

Methods

setPacketId :: Msgid -> Packet a -> Packet a #

GetPacketId Msgid (Packet a) Source # 
Instance details

Defined in Periodic.Types.Packet

Methods

getPacketId :: Packet a -> Msgid #

type Rep Msgid Source # 
Instance details

Defined in Periodic.Types.Internal

type Rep Msgid = D1 ('MetaData "Msgid" "Periodic.Types.Internal" "periodic-common-1.1.7.0-inplace" 'True) (C1 ('MetaCons "Msgid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))