yak-0.2.0.0: A strongly typed IRC library

Safe HaskellNone
LanguageHaskell2010

Network.Yak.Modes

Contents

Description

A small DSL for creating mode strings. The documentation contains parts from https://modern.ircdocs.horse only for quick reference. Please refer to the source for up to date documentation on individual modes!

Synopsis

Documentation

data ModeStr Source #

Instances
Semigroup ModeStr Source # 
Instance details

Defined in Network.Yak.Modes

emitModeStr :: ModeStr -> ByteString Source #

Emit a ModeStr to a ByteString for use in a message.

fetchModeStr :: ServerModes -> ByteString -> Maybe ModeStr Source #

Fetch a ModeStr from a ByteString, given some defined collection of modes in the form of a ServerModes. Will return Nothing if the parsing fails.

data ModeType Source #

Constructors

TypeA 
TypeB 
TypeC 
TypeD 
Instances
Eq ModeType Source # 
Instance details

Defined in Network.Yak.Modes

Ord ModeType Source # 
Instance details

Defined in Network.Yak.Modes

Read ModeType Source # 
Instance details

Defined in Network.Yak.Modes

Show ModeType Source # 
Instance details

Defined in Network.Yak.Modes

Generic ModeType Source # 
Instance details

Defined in Network.Yak.Modes

Associated Types

type Rep ModeType :: Type -> Type #

Methods

from :: ModeType -> Rep ModeType x #

to :: Rep ModeType x -> ModeType #

type Rep ModeType Source # 
Instance details

Defined in Network.Yak.Modes

type Rep ModeType = D1 (MetaData "ModeType" "Network.Yak.Modes" "yak-0.2.0.0-DpGRvARnWRP1pvWDPQg9Pa" False) ((C1 (MetaCons "TypeA" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TypeB" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TypeC" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TypeD" PrefixI False) (U1 :: Type -> Type)))

data Mode :: ModeType -> * -> * where Source #

A mode is defined through a character and its type.

  • TypeA: Modes that add or remove an address to or from a list. These modes MUST always have a parameter when sent from the server to a client. A client MAY issue this type of mode without an argument to obtain the current contents of the list. The numerics used to retrieve contents of Type A modes depends on the specific mode. Also see the EXTBAN parameter.
  • TypeB: Modes that change a setting on a channel. These modes MUST always have a parameter.
  • TypeC: Modes that change a setting on a channel. These modes MUST have a parameter when being set, and MUST NOT have a parameter when being unset.
  • TypeD: Modes that change a setting on a channel. These modes MUST NOT have a parameter.

The final type parameter to Mode determines the parameter type of the defined mode.

Constructors

ModeTypeA :: Char -> Mode TypeA a 
ModeTypeB :: Char -> Mode TypeB a 
ModeTypeC :: Char -> Mode TypeC a 
ModeTypeD :: Char -> Mode TypeD Void 

data OpaqueMode (t :: ModeType) Source #

An existential wrapper around modes that hides the parameter type, such that modes of a similar type can be grouped together in a simple container, such as those in a ServerModes.

Constructors

ModeParameter a => OpaqueMode (Mode t a) 

class ModeParameter a where Source #

Mode Parameters are types that can be used as parameters to some mode.

data ModeOp where Source #

Operations that can be performed with a mode.

Constructors

GetMode :: Mode TypeA a -> ModeOp

Type A modes can be retrieved in list form.

SetMode :: ModeParameter a => Mode t a -> Maybe a -> ModeOp 
UnsetMode :: ModeParameter a => Mode t a -> Maybe a -> ModeOp 

Building Mode Strings

Mode Strings can be built using the following three combinators. The types are polymorphic over different mode types and therefore do not fully reflect their use.

As an example consider

foo :: ModeStr
foo = set ban "foo!bar@quux" <> unset moderated

which translates to

+b+m foo!bar@quux

set :: SetMode m => m -> ModeSetter m Source #

unset :: UnsetMode m => m -> ModeUnsetter m Source #

Common Channel Modes

ban :: Mode TypeA HostMask Source #

This channel mode controls a list of client masks that are ‘banned’ from joining or speaking in the channel. If this mode has values, each of these values should be a client mask.

exception :: Mode TypeA HostMask Source #

This channel mode controls a list of client masks that are exempt from the ‘ban’ channel mode. If this mode has values, each of these values should be a client mask.

clientLimit :: Mode TypeC Int Source #

This channel mode controls whether new users may join based on the number of users who already exist in the channel. If this mode is set, its value is an integer and defines the limit of how many clients may be joined to the channel.

inviteOnly :: Mode TypeD Void Source #

This channel mode controls whether new users need to be invited to the channel before being able to join.

inviteOnlyException :: Mode TypeA HostMask Source #

This channel mode controls a list of channel masks that are exempt from the invite-only channel mode. If this mode has values, each of these values should be a client mask.

key :: Mode TypeB Text Source #

This mode letter sets a ‘key’ that must be supplied in order to join this channel. If this mode is set, its’ value is the key that is required.

secret :: Mode TypeD Void Source #

This channel mode controls whether the channel is ‘secret’, and does not have any value.

moderated :: Mode TypeD Void Source #

This channel mode controls whether users may freely talk on the channel, and does not have any value.

protectedTopic :: Mode TypeD Void Source #

This channel mode controls whether channel privileges are required to set the topic, and does not have any value.

noExternal :: Mode TypeD Void Source #

This channel mode controls whether users who are not joined to the channel can send messages to it, and does not have any value.

Common User Modes

pattern UserMode :: Char -> UserMode Source #

invisible :: UserMode Source #

If a user is set to ‘invisible’, they will not show up in commands such as WHO unless they share a channel with the user that submitted the command. In addition, the only channels that will show up in a WHOIS of an invisible user will be those they share with the user that submitted the command.

oper :: UserMode Source #

If a user has this mode, this indicates that they are a network operator.

localOper :: UserMode Source #

If a user has this mode, this indicates that they are a server operator. A local operator has operator privileges for their server, and not for the rest of the network.

registered :: UserMode Source #

If a user has this mode, this indicates that they have logged into a user account.

wallops :: UserMode Source #

If a user has this mode, this indicates that they will receive WALLOPS messages from the server.

Channel Member Prefix Modes

Server Modes

data ServerModes Source #

ServerModes lets you define a dictionary of modes to be passed to the parser (see fetchModeStr). Modes are very server specific and it is not possible to achieve good coverage/compatibility here, so this needs to be done in user code. See defaultModes for a starting point. Note that ServerModes is a monoid, so you can easily augment the standardized modes with custom server specific ones.

Types