yak-0.2.0.0: A strongly typed IRC library

Safe HaskellNone
LanguageHaskell2010

Network.Yak.Types

Synopsis

Documentation

data Prefix Source #

Instances
Eq Prefix Source # 
Instance details

Defined in Network.Yak.Types

Methods

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

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

Ord Prefix Source # 
Instance details

Defined in Network.Yak.Types

Read Prefix Source # 
Instance details

Defined in Network.Yak.Types

Show Prefix Source # 
Instance details

Defined in Network.Yak.Types

Generic Prefix Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Rep Prefix :: Type -> Type #

Methods

from :: Prefix -> Rep Prefix x #

to :: Rep Prefix x -> Prefix #

type Rep Prefix Source # 
Instance details

Defined in Network.Yak.Types

type Rep Prefix = D1 (MetaData "Prefix" "Network.Yak.Types" "yak-0.2.0.0-DpGRvARnWRP1pvWDPQg9Pa" False) (C1 (MetaCons "PrefixServer" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "PrefixUser" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Host)))

data Host Source #

Instances
Eq Host Source # 
Instance details

Defined in Network.Yak.Types

Methods

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

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

Ord Host Source # 
Instance details

Defined in Network.Yak.Types

Methods

compare :: Host -> Host -> Ordering #

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

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

(>) :: Host -> Host -> Bool #

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

max :: Host -> Host -> Host #

min :: Host -> Host -> Host #

Read Host Source # 
Instance details

Defined in Network.Yak.Types

Show Host Source # 
Instance details

Defined in Network.Yak.Types

Methods

showsPrec :: Int -> Host -> ShowS #

show :: Host -> String #

showList :: [Host] -> ShowS #

Generic Host Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Rep Host :: Type -> Type #

Methods

from :: Host -> Rep Host x #

to :: Rep Host x -> Host #

Parameter Host Source # 
Instance details

Defined in Network.Yak.Types

type Rep Host Source # 
Instance details

Defined in Network.Yak.Types

data Msg command params Source #

Proxy type for holding IRC messages

Constructors

Msg 

Fields

Instances
HasHostname Motd Source # 
Instance details

Defined in Network.Yak.Client

HasHostname Lusers Source # 
Instance details

Defined in Network.Yak.Client

HasHostname Version Source # 
Instance details

Defined in Network.Yak.Client

HasHostname Admin Source # 
Instance details

Defined in Network.Yak.Client

HasHostname Time Source # 
Instance details

Defined in Network.Yak.Client

HasHostname Stats Source # 
Instance details

Defined in Network.Yak.Client

HasHostname Info Source # 
Instance details

Defined in Network.Yak.Client

HasHostname WhoIs Source # 
Instance details

Defined in Network.Yak.Client

HasHostname WhoWas Source # 
Instance details

Defined in Network.Yak.Client

HasNick Nick Source # 
Instance details

Defined in Network.Yak.Client

HasNick Oper Source # 
Instance details

Defined in Network.Yak.Client

HasNick Mode Source # 
Instance details

Defined in Network.Yak.Client

HasNick Privmsg Source # 
Instance details

Defined in Network.Yak.Client

HasNick Notice Source # 
Instance details

Defined in Network.Yak.Client

HasNick WhoWas Source # 
Instance details

Defined in Network.Yak.Client

HasNick Kill Source # 
Instance details

Defined in Network.Yak.Client

HasNick Kick Source # 
Instance details

Defined in Network.Yak.Client

HasNick Invite Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Join Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Part Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Topic Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Names Source # 
Instance details

Defined in Network.Yak.Client

HasChannel List Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Mode Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Privmsg Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Notice Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Kick Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Invite Source # 
Instance details

Defined in Network.Yak.Client

Eq (PList params) => Eq (Msg command params) Source # 
Instance details

Defined in Network.Yak.Types

Methods

(==) :: Msg command params -> Msg command params -> Bool #

(/=) :: Msg command params -> Msg command params -> Bool #

Show (PList params) => Show (Msg command params) Source # 
Instance details

Defined in Network.Yak.Types

Methods

showsPrec :: Int -> Msg command params -> ShowS #

show :: Msg command params -> String #

showList :: [Msg command params] -> ShowS #

(Parameter (PList p), KnownSymbol c) => Fetch (Msg c p) Source # 
Instance details

Defined in Network.Yak

Methods

fetch :: ByteString -> Maybe (Msg c p) Source #

build :: Build '[] f => f Source #

Generalized constructor function for the creation of Msg values. The types here may seem opaque, but essentially this is a variadic type-safe constructor.

build "hunter2" :: Pass
build [Channel "#haskell"] (Message "hello world!") :: PrivMsg

The type annotations may or may not be necessary, depending on the information available to the compiler at the use site.

buildPrefix :: Build '[] f => Prefix -> f Source #

Like build but takes a Prefix that will be added to the message.

vacant :: Msg c '[] Source #

(<:>) :: x -> Msg c xs -> Msg c (x ': xs) infixr 5 Source #

castMsg :: (KnownSymbol c1, KnownSymbol c2) => Msg c1 p -> Msg c2 p Source #

Safely cast one message to another. Equality of parameter lists is statically enforced.

data SomeMsg where Source #

Constructors

SomeMsg :: (KnownSymbol c, Parameter (PList p)) => Msg c p -> SomeMsg 

data Unused (a :: Symbol) Source #

Proxy type for inserting special syntax

Constructors

Unused 
Instances
Eq (Unused a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

(==) :: Unused a -> Unused a -> Bool #

(/=) :: Unused a -> Unused a -> Bool #

Ord (Unused a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

compare :: Unused a -> Unused a -> Ordering #

(<) :: Unused a -> Unused a -> Bool #

(<=) :: Unused a -> Unused a -> Bool #

(>) :: Unused a -> Unused a -> Bool #

(>=) :: Unused a -> Unused a -> Bool #

max :: Unused a -> Unused a -> Unused a #

min :: Unused a -> Unused a -> Unused a #

Read (Unused a) Source # 
Instance details

Defined in Network.Yak.Types

Show (Unused a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

showsPrec :: Int -> Unused a -> ShowS #

show :: Unused a -> String #

showList :: [Unused a] -> ShowS #

Generic (Unused a) Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Rep (Unused a) :: Type -> Type #

Methods

from :: Unused a -> Rep (Unused a) x #

to :: Rep (Unused a) x -> Unused a #

KnownSymbol a => Parameter (Unused a) Source # 
Instance details

Defined in Network.Yak.Types

type Rep (Unused a) Source # 
Instance details

Defined in Network.Yak.Types

type Rep (Unused a) = D1 (MetaData "Unused" "Network.Yak.Types" "yak-0.2.0.0-DpGRvARnWRP1pvWDPQg9Pa" False) (C1 (MetaCons "Unused" PrefixI False) (U1 :: Type -> Type))

data Flag a Source #

Type for expressing possibly missing flags.

Constructors

Set 
Unset 
Instances
Eq (Flag a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

(==) :: Flag a -> Flag a -> Bool #

(/=) :: Flag a -> Flag a -> Bool #

Ord (Flag a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

compare :: Flag a -> Flag a -> Ordering #

(<) :: Flag a -> Flag a -> Bool #

(<=) :: Flag a -> Flag a -> Bool #

(>) :: Flag a -> Flag a -> Bool #

(>=) :: Flag a -> Flag a -> Bool #

max :: Flag a -> Flag a -> Flag a #

min :: Flag a -> Flag a -> Flag a #

Read (Flag a) Source # 
Instance details

Defined in Network.Yak.Types

Show (Flag a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

showsPrec :: Int -> Flag a -> ShowS #

show :: Flag a -> String #

showList :: [Flag a] -> ShowS #

Generic (Flag a) Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Rep (Flag a) :: Type -> Type #

Methods

from :: Flag a -> Rep (Flag a) x #

to :: Rep (Flag a) x -> Flag a #

KnownSymbol a => Parameter (Flag a) Source # 
Instance details

Defined in Network.Yak.Types

type Rep (Flag a) Source # 
Instance details

Defined in Network.Yak.Types

type Rep (Flag a) = D1 (MetaData "Flag" "Network.Yak.Types" "yak-0.2.0.0-DpGRvARnWRP1pvWDPQg9Pa" False) (C1 (MetaCons "Set" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Unset" PrefixI False) (U1 :: Type -> Type))

newtype SList a Source #

Space separated lists. Use with caution, since spaces are also the separator for PList!

Constructors

SList 

Fields

Instances
Monad SList Source # 
Instance details

Defined in Network.Yak.Types

Methods

(>>=) :: SList a -> (a -> SList b) -> SList b #

(>>) :: SList a -> SList b -> SList b #

return :: a -> SList a #

fail :: String -> SList a #

Functor SList Source # 
Instance details

Defined in Network.Yak.Types

Methods

fmap :: (a -> b) -> SList a -> SList b #

(<$) :: a -> SList b -> SList a #

Applicative SList Source # 
Instance details

Defined in Network.Yak.Types

Methods

pure :: a -> SList a #

(<*>) :: SList (a -> b) -> SList a -> SList b #

liftA2 :: (a -> b -> c) -> SList a -> SList b -> SList c #

(*>) :: SList a -> SList b -> SList b #

(<*) :: SList a -> SList b -> SList a #

Foldable SList Source # 
Instance details

Defined in Network.Yak.Types

Methods

fold :: Monoid m => SList m -> m #

foldMap :: Monoid m => (a -> m) -> SList a -> m #

foldr :: (a -> b -> b) -> b -> SList a -> b #

foldr' :: (a -> b -> b) -> b -> SList a -> b #

foldl :: (b -> a -> b) -> b -> SList a -> b #

foldl' :: (b -> a -> b) -> b -> SList a -> b #

foldr1 :: (a -> a -> a) -> SList a -> a #

foldl1 :: (a -> a -> a) -> SList a -> a #

toList :: SList a -> [a] #

null :: SList a -> Bool #

length :: SList a -> Int #

elem :: Eq a => a -> SList a -> Bool #

maximum :: Ord a => SList a -> a #

minimum :: Ord a => SList a -> a #

sum :: Num a => SList a -> a #

product :: Num a => SList a -> a #

Traversable SList Source # 
Instance details

Defined in Network.Yak.Types

Methods

traverse :: Applicative f => (a -> f b) -> SList a -> f (SList b) #

sequenceA :: Applicative f => SList (f a) -> f (SList a) #

mapM :: Monad m => (a -> m b) -> SList a -> m (SList b) #

sequence :: Monad m => SList (m a) -> m (SList a) #

Alternative SList Source # 
Instance details

Defined in Network.Yak.Types

Methods

empty :: SList a #

(<|>) :: SList a -> SList a -> SList a #

some :: SList a -> SList [a] #

many :: SList a -> SList [a] #

IsList (SList a) Source #

Syntactic sugar for construction

Instance details

Defined in Network.Yak.Types

Associated Types

type Item (SList a) :: Type #

Methods

fromList :: [Item (SList a)] -> SList a #

fromListN :: Int -> [Item (SList a)] -> SList a #

toList :: SList a -> [Item (SList a)] #

Eq a => Eq (SList a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

(==) :: SList a -> SList a -> Bool #

(/=) :: SList a -> SList a -> Bool #

Ord a => Ord (SList a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

compare :: SList a -> SList a -> Ordering #

(<) :: SList a -> SList a -> Bool #

(<=) :: SList a -> SList a -> Bool #

(>) :: SList a -> SList a -> Bool #

(>=) :: SList a -> SList a -> Bool #

max :: SList a -> SList a -> SList a #

min :: SList a -> SList a -> SList a #

Read a => Read (SList a) Source # 
Instance details

Defined in Network.Yak.Types

Show a => Show (SList a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

showsPrec :: Int -> SList a -> ShowS #

show :: SList a -> String #

showList :: [SList a] -> ShowS #

Generic (SList a) Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Rep (SList a) :: Type -> Type #

Methods

from :: SList a -> Rep (SList a) x #

to :: Rep (SList a) x -> SList a #

Semigroup (SList a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

(<>) :: SList a -> SList a -> SList a #

sconcat :: NonEmpty (SList a) -> SList a #

stimes :: Integral b => b -> SList a -> SList a #

Monoid (SList a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

mempty :: SList a #

mappend :: SList a -> SList a -> SList a #

mconcat :: [SList a] -> SList a #

Wrapped (SList a) Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Unwrapped (SList a) :: Type #

Methods

_Wrapped' :: Iso' (SList a) (Unwrapped (SList a)) #

Parameter a => Parameter (SList a) Source # 
Instance details

Defined in Network.Yak.Types

t ~ SList b => Rewrapped (SList a) t Source # 
Instance details

Defined in Network.Yak.Types

type Rep (SList a) Source # 
Instance details

Defined in Network.Yak.Types

type Rep (SList a) = D1 (MetaData "SList" "Network.Yak.Types" "yak-0.2.0.0-DpGRvARnWRP1pvWDPQg9Pa" True) (C1 (MetaCons "SList" PrefixI True) (S1 (MetaSel (Just "getSList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [a])))
type Item (SList a) Source # 
Instance details

Defined in Network.Yak.Types

type Item (SList a) = a
type Unwrapped (SList a) Source # 
Instance details

Defined in Network.Yak.Types

type Unwrapped (SList a) = [a]

newtype CList a Source #

Space separated lists after colon. Used in some numeric replies

Constructors

CList 

Fields

Instances
Monad CList Source # 
Instance details

Defined in Network.Yak.Types

Methods

(>>=) :: CList a -> (a -> CList b) -> CList b #

(>>) :: CList a -> CList b -> CList b #

return :: a -> CList a #

fail :: String -> CList a #

Functor CList Source # 
Instance details

Defined in Network.Yak.Types

Methods

fmap :: (a -> b) -> CList a -> CList b #

(<$) :: a -> CList b -> CList a #

Applicative CList Source # 
Instance details

Defined in Network.Yak.Types

Methods

pure :: a -> CList a #

(<*>) :: CList (a -> b) -> CList a -> CList b #

liftA2 :: (a -> b -> c) -> CList a -> CList b -> CList c #

(*>) :: CList a -> CList b -> CList b #

(<*) :: CList a -> CList b -> CList a #

Foldable CList Source # 
Instance details

Defined in Network.Yak.Types

Methods

fold :: Monoid m => CList m -> m #

foldMap :: Monoid m => (a -> m) -> CList a -> m #

foldr :: (a -> b -> b) -> b -> CList a -> b #

foldr' :: (a -> b -> b) -> b -> CList a -> b #

foldl :: (b -> a -> b) -> b -> CList a -> b #

foldl' :: (b -> a -> b) -> b -> CList a -> b #

foldr1 :: (a -> a -> a) -> CList a -> a #

foldl1 :: (a -> a -> a) -> CList a -> a #

toList :: CList a -> [a] #

null :: CList a -> Bool #

length :: CList a -> Int #

elem :: Eq a => a -> CList a -> Bool #

maximum :: Ord a => CList a -> a #

minimum :: Ord a => CList a -> a #

sum :: Num a => CList a -> a #

product :: Num a => CList a -> a #

Traversable CList Source # 
Instance details

Defined in Network.Yak.Types

Methods

traverse :: Applicative f => (a -> f b) -> CList a -> f (CList b) #

sequenceA :: Applicative f => CList (f a) -> f (CList a) #

mapM :: Monad m => (a -> m b) -> CList a -> m (CList b) #

sequence :: Monad m => CList (m a) -> m (CList a) #

Alternative CList Source # 
Instance details

Defined in Network.Yak.Types

Methods

empty :: CList a #

(<|>) :: CList a -> CList a -> CList a #

some :: CList a -> CList [a] #

many :: CList a -> CList [a] #

IsList (CList a) Source #

Syntactic sugar for construction

Instance details

Defined in Network.Yak.Types

Associated Types

type Item (CList a) :: Type #

Methods

fromList :: [Item (CList a)] -> CList a #

fromListN :: Int -> [Item (CList a)] -> CList a #

toList :: CList a -> [Item (CList a)] #

Eq a => Eq (CList a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

(==) :: CList a -> CList a -> Bool #

(/=) :: CList a -> CList a -> Bool #

Ord a => Ord (CList a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

compare :: CList a -> CList a -> Ordering #

(<) :: CList a -> CList a -> Bool #

(<=) :: CList a -> CList a -> Bool #

(>) :: CList a -> CList a -> Bool #

(>=) :: CList a -> CList a -> Bool #

max :: CList a -> CList a -> CList a #

min :: CList a -> CList a -> CList a #

Read a => Read (CList a) Source # 
Instance details

Defined in Network.Yak.Types

Show a => Show (CList a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

showsPrec :: Int -> CList a -> ShowS #

show :: CList a -> String #

showList :: [CList a] -> ShowS #

Generic (CList a) Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Rep (CList a) :: Type -> Type #

Methods

from :: CList a -> Rep (CList a) x #

to :: Rep (CList a) x -> CList a #

Semigroup (CList a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

(<>) :: CList a -> CList a -> CList a #

sconcat :: NonEmpty (CList a) -> CList a #

stimes :: Integral b => b -> CList a -> CList a #

Monoid (CList a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

mempty :: CList a #

mappend :: CList a -> CList a -> CList a #

mconcat :: [CList a] -> CList a #

Wrapped (CList a) Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Unwrapped (CList a) :: Type #

Methods

_Wrapped' :: Iso' (CList a) (Unwrapped (CList a)) #

Parameter a => Parameter (CList a) Source # 
Instance details

Defined in Network.Yak.Types

t ~ CList b => Rewrapped (CList a) t Source # 
Instance details

Defined in Network.Yak.Types

type Rep (CList a) Source # 
Instance details

Defined in Network.Yak.Types

type Rep (CList a) = D1 (MetaData "CList" "Network.Yak.Types" "yak-0.2.0.0-DpGRvARnWRP1pvWDPQg9Pa" True) (C1 (MetaCons "CList" PrefixI True) (S1 (MetaSel (Just "getCList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [a])))
type Item (CList a) Source # 
Instance details

Defined in Network.Yak.Types

type Item (CList a) = a
type Unwrapped (CList a) Source # 
Instance details

Defined in Network.Yak.Types

type Unwrapped (CList a) = [a]

class Parameter a where Source #

Class for any kind of IRC parameter that can be rendered to ByteString and read from a ByteString

Instances
Parameter Char Source # 
Instance details

Defined in Network.Yak.Types

Parameter Int Source #

Only positive

Instance details

Defined in Network.Yak.Types

Parameter Word Source # 
Instance details

Defined in Network.Yak.Types

Parameter Host Source # 
Instance details

Defined in Network.Yak.Types

Parameter UReply Source # 
Instance details

Defined in Network.Yak.Types

Parameter Capability Source # 
Instance details

Defined in Network.Yak.Capabilities

Parameter ByteString Source # 
Instance details

Defined in Network.Yak.Types

Parameter Text Source #

Text is encoded as UTF-8. Pieces of Text are space normally separated. Text parsing enforces the text to be non-empty, and commas are disallowed.

Instance details

Defined in Network.Yak.Types

(TypeError (Text "Illegal IRC Parameter") :: Constraint) => Parameter Void Source #

For illegal parameters

Instance details

Defined in Network.Yak.Types

Parameter POSIXTime Source # 
Instance details

Defined in Network.Yak.Types

Parameter Channel Source # 
Instance details

Defined in Network.Yak.Types

Parameter Message Source # 
Instance details

Defined in Network.Yak.Types

Parameter Modes Source # 
Instance details

Defined in Network.Yak.Types

Parameter Token Source # 
Instance details

Defined in Network.Yak.Types

Parameter ReqAnswer Source # 
Instance details

Defined in Network.Yak.Capabilities

Parameter a => Parameter [a] Source #

Lists are comma separated

Instance details

Defined in Network.Yak.Types

Methods

render :: [a] -> ByteString Source #

seize :: Parser [a] Source #

Parameter a => Parameter (Maybe a) Source #

A Maybe parameter can be totally absent

Instance details

Defined in Network.Yak.Types

Parameter a => Parameter (Member a) Source # 
Instance details

Defined in Network.Yak.Types

Parameter a => Parameter (NonEmpty a) Source #

Like lists but non-empty

Instance details

Defined in Network.Yak.Types

(Parameter x, Parameter (PList xs)) => Parameter (PList (x ': xs)) Source # 
Instance details

Defined in Network.Yak.Types

Methods

render :: PList (x ': xs) -> ByteString Source #

seize :: Parser (PList (x ': xs)) Source #

Parameter (PList ([] :: [Type])) Source # 
Instance details

Defined in Network.Yak.Types

Parameter a => Parameter (CList a) Source # 
Instance details

Defined in Network.Yak.Types

Parameter a => Parameter (SList a) Source # 
Instance details

Defined in Network.Yak.Types

KnownSymbol a => Parameter (Unused a) Source # 
Instance details

Defined in Network.Yak.Types

(Parameter a, Parameter b) => Parameter (Either a b) Source # 
Instance details

Defined in Network.Yak.Types

(Parameter a, Parameter b) => Parameter (a, b) Source # 
Instance details

Defined in Network.Yak.Types

Methods

render :: (a, b) -> ByteString Source #

seize :: Parser (a, b) Source #

KnownSymbol a => Parameter (Flag a) Source # 
Instance details

Defined in Network.Yak.Types

data PList a where Source #

Heterogeneous list of parameters.

Constructors

PNil :: PList '[] 
PCons :: forall x xs. x -> PList xs -> PList (x ': xs) 
Instances
(Eq x, Eq (PList xs)) => Eq (PList (x ': xs)) Source # 
Instance details

Defined in Network.Yak.Types

Methods

(==) :: PList (x ': xs) -> PList (x ': xs) -> Bool #

(/=) :: PList (x ': xs) -> PList (x ': xs) -> Bool #

Eq (PList ([] :: [Type])) Source # 
Instance details

Defined in Network.Yak.Types

Methods

(==) :: PList [] -> PList [] -> Bool #

(/=) :: PList [] -> PList [] -> Bool #

(Show x, Show (PList xs)) => Show (PList (x ': xs)) Source # 
Instance details

Defined in Network.Yak.Types

Methods

showsPrec :: Int -> PList (x ': xs) -> ShowS #

show :: PList (x ': xs) -> String #

showList :: [PList (x ': xs)] -> ShowS #

Show (PList ([] :: [Type])) Source # 
Instance details

Defined in Network.Yak.Types

Methods

showsPrec :: Int -> PList [] -> ShowS #

show :: PList [] -> String #

showList :: [PList []] -> ShowS #

(Parameter x, Parameter (PList xs)) => Parameter (PList (x ': xs)) Source # 
Instance details

Defined in Network.Yak.Types

Methods

render :: PList (x ': xs) -> ByteString Source #

seize :: Parser (PList (x ': xs)) Source #

Parameter (PList ([] :: [Type])) Source # 
Instance details

Defined in Network.Yak.Types

(Parameter x, Parameter x') => Field1 (PList (x ': xs)) (PList (x' ': xs)) x x' Source # 
Instance details

Defined in Network.Yak.Types

Methods

_1 :: Lens (PList (x ': xs)) (PList (x' ': xs)) x x' #

(Parameter x, Parameter x') => Field2 (PList (a ': (x ': xs))) (PList (a ': (x' ': xs))) x x' Source # 
Instance details

Defined in Network.Yak.Types

Methods

_2 :: Lens (PList (a ': (x ': xs))) (PList (a ': (x' ': xs))) x x' #

(Parameter x, Parameter x') => Field3 (PList (a ': (b ': (x ': xs)))) (PList (a ': (b ': (x' ': xs)))) x x' Source # 
Instance details

Defined in Network.Yak.Types

Methods

_3 :: Lens (PList (a ': (b ': (x ': xs)))) (PList (a ': (b ': (x' ': xs)))) x x' #

(Parameter x, Parameter x') => Field4 (PList (a ': (b ': (c ': (x ': xs))))) (PList (a ': (b ': (c ': (x' ': xs))))) x x' Source # 
Instance details

Defined in Network.Yak.Types

Methods

_4 :: Lens (PList (a ': (b ': (c ': (x ': xs))))) (PList (a ': (b ': (c ': (x' ': xs))))) x x' #

(Parameter x, Parameter x') => Field5 (PList (a ': (b ': (c ': (d ': (x ': xs)))))) (PList (a ': (b ': (c ': (d ': (x' ': xs)))))) x x' Source # 
Instance details

Defined in Network.Yak.Types

Methods

_5 :: Lens (PList (a ': (b ': (c ': (d ': (x ': xs)))))) (PList (a ': (b ': (c ': (d ': (x' ': xs)))))) x x' #

(Parameter x, Parameter x') => Field6 (PList (a ': (b ': (c ': (d ': (e ': (x ': xs))))))) (PList (a ': (b ': (c ': (d ': (e ': (x' ': xs))))))) x x' Source # 
Instance details

Defined in Network.Yak.Types

Methods

_6 :: Lens (PList (a ': (b ': (c ': (d ': (e ': (x ': xs))))))) (PList (a ': (b ': (c ': (d ': (e ': (x' ': xs))))))) x x' #

(Parameter x, Parameter x') => Field7 (PList (a ': (b ': (c ': (d ': (e ': (f ': (x ': xs)))))))) (PList (a ': (b ': (c ': (d ': (e ': (f ': (x' ': xs)))))))) x x' Source # 
Instance details

Defined in Network.Yak.Types

Methods

_7 :: Lens (PList (a ': (b ': (c ': (d ': (e ': (f ': (x ': xs)))))))) (PList (a ': (b ': (c ': (d ': (e ': (f ': (x' ': xs)))))))) x x' #

(Parameter x, Parameter x') => Field8 (PList (a ': (b ': (c ': (d ': (e ': (f ': (g ': (x ': xs))))))))) (PList (a ': (b ': (c ': (d ': (e ': (f ': (g ': (x' ': xs))))))))) x x' Source # 
Instance details

Defined in Network.Yak.Types

Methods

_8 :: Lens (PList (a ': (b ': (c ': (d ': (e ': (f ': (g ': (x ': xs))))))))) (PList (a ': (b ': (c ': (d ': (e ': (f ': (g ': (x' ': xs))))))))) x x' #

(Parameter x, Parameter x') => Field9 (PList (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (x ': xs)))))))))) (PList (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (x' ': xs)))))))))) x x' Source # 
Instance details

Defined in Network.Yak.Types

Methods

_9 :: Lens (PList (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (x ': xs)))))))))) (PList (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (x' ': xs)))))))))) x x' #

phead :: Parameter x' => Lens (PList (x ': xs)) (PList (x' ': xs)) x x' Source #

ptail :: Lens (PList (x ': xs)) (PList (x ': xs')) (PList xs) (PList xs') Source #

params :: forall command params command params. Lens (Msg command params) (Msg command params) (PList params) (PList params) Source #

prefix :: forall command params command. Lens (Msg command params) (Msg command params) (Maybe Prefix) (Maybe Prefix) Source #

newtype Channel Source #

Constructors

Channel 

Fields

Instances
Eq Channel Source # 
Instance details

Defined in Network.Yak.Types

Methods

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

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

Ord Channel Source # 
Instance details

Defined in Network.Yak.Types

Read Channel Source # 
Instance details

Defined in Network.Yak.Types

Show Channel Source # 
Instance details

Defined in Network.Yak.Types

IsString Channel Source # 
Instance details

Defined in Network.Yak.Types

Methods

fromString :: String -> Channel #

Generic Channel Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Rep Channel :: Type -> Type #

Methods

from :: Channel -> Rep Channel x #

to :: Rep Channel x -> Channel #

Semigroup Channel Source # 
Instance details

Defined in Network.Yak.Types

Monoid Channel Source # 
Instance details

Defined in Network.Yak.Types

Wrapped Channel Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Unwrapped Channel :: Type #

Parameter Channel Source # 
Instance details

Defined in Network.Yak.Types

HasNick Mode Source # 
Instance details

Defined in Network.Yak.Client

HasNick Privmsg Source # 
Instance details

Defined in Network.Yak.Client

HasNick Notice Source # 
Instance details

Defined in Network.Yak.Client

HasNick Kick Source # 
Instance details

Defined in Network.Yak.Client

HasNick Invite Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Join Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Part Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Topic Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Names Source # 
Instance details

Defined in Network.Yak.Client

HasChannel List Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Mode Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Privmsg Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Notice Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Kick Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Invite Source # 
Instance details

Defined in Network.Yak.Client

Channel ~ t => Rewrapped Channel t Source # 
Instance details

Defined in Network.Yak.Types

type Rep Channel Source # 
Instance details

Defined in Network.Yak.Types

type Rep Channel = D1 (MetaData "Channel" "Network.Yak.Types" "yak-0.2.0.0-DpGRvARnWRP1pvWDPQg9Pa" True) (C1 (MetaCons "Channel" PrefixI True) (S1 (MetaSel (Just "getChannel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))
type Unwrapped Channel Source # 
Instance details

Defined in Network.Yak.Types

newtype Message Source #

Constructors

Message 

Fields

Instances
Eq Message Source # 
Instance details

Defined in Network.Yak.Types

Methods

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

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

Ord Message Source # 
Instance details

Defined in Network.Yak.Types

Read Message Source # 
Instance details

Defined in Network.Yak.Types

Show Message Source # 
Instance details

Defined in Network.Yak.Types

IsString Message Source # 
Instance details

Defined in Network.Yak.Types

Methods

fromString :: String -> Message #

Generic Message Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Rep Message :: Type -> Type #

Methods

from :: Message -> Rep Message x #

to :: Rep Message x -> Message #

Semigroup Message Source # 
Instance details

Defined in Network.Yak.Types

Monoid Message Source # 
Instance details

Defined in Network.Yak.Types

Wrapped Message Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Unwrapped Message :: Type #

Parameter Message Source # 
Instance details

Defined in Network.Yak.Types

HasNick Privmsg Source # 
Instance details

Defined in Network.Yak.Client

HasNick Notice Source # 
Instance details

Defined in Network.Yak.Client

HasNick Kill Source # 
Instance details

Defined in Network.Yak.Client

HasNick Kick Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Part Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Topic Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Privmsg Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Notice Source # 
Instance details

Defined in Network.Yak.Client

HasChannel Kick Source # 
Instance details

Defined in Network.Yak.Client

Message ~ t => Rewrapped Message t Source # 
Instance details

Defined in Network.Yak.Types

type Rep Message Source # 
Instance details

Defined in Network.Yak.Types

type Rep Message = D1 (MetaData "Message" "Network.Yak.Types" "yak-0.2.0.0-DpGRvARnWRP1pvWDPQg9Pa" True) (C1 (MetaCons "Message" PrefixI True) (S1 (MetaSel (Just "getMessage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))
type Unwrapped Message Source # 
Instance details

Defined in Network.Yak.Types

type Mask = Text Source #

newtype Modes Source #

Constructors

Modes 

Fields

Instances
Generic Modes Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Rep Modes :: Type -> Type #

Methods

from :: Modes -> Rep Modes x #

to :: Rep Modes x -> Modes #

Wrapped Modes Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Unwrapped Modes :: Type #

Parameter Modes Source # 
Instance details

Defined in Network.Yak.Types

Modes ~ t => Rewrapped Modes t Source # 
Instance details

Defined in Network.Yak.Types

type Rep Modes Source # 
Instance details

Defined in Network.Yak.Types

type Rep Modes = D1 (MetaData "Modes" "Network.Yak.Types" "yak-0.2.0.0-DpGRvARnWRP1pvWDPQg9Pa" True) (C1 (MetaCons "Modes" PrefixI True) (S1 (MetaSel (Just "getModes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Char])))
type Unwrapped Modes Source # 
Instance details

Defined in Network.Yak.Types

data Token Source #

Instances
Eq Token Source # 
Instance details

Defined in Network.Yak.Types

Methods

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

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

Ord Token Source # 
Instance details

Defined in Network.Yak.Types

Methods

compare :: Token -> Token -> Ordering #

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

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

(>) :: Token -> Token -> Bool #

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

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

Read Token Source # 
Instance details

Defined in Network.Yak.Types

Show Token Source # 
Instance details

Defined in Network.Yak.Types

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Generic Token Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Rep Token :: Type -> Type #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

Parameter Token Source # 
Instance details

Defined in Network.Yak.Types

type Rep Token Source # 
Instance details

Defined in Network.Yak.Types

data UReply Source #

Replies to Userhost queries.

Instances
Eq UReply Source # 
Instance details

Defined in Network.Yak.Types

Methods

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

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

Ord UReply Source # 
Instance details

Defined in Network.Yak.Types

Read UReply Source # 
Instance details

Defined in Network.Yak.Types

Show UReply Source # 
Instance details

Defined in Network.Yak.Types

Generic UReply Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Rep UReply :: Type -> Type #

Methods

from :: UReply -> Rep UReply x #

to :: Rep UReply x -> UReply #

Parameter UReply Source # 
Instance details

Defined in Network.Yak.Types

type Rep UReply Source # 
Instance details

Defined in Network.Yak.Types

data Member a Source #

Constructors

Member (Maybe Char) a 
Instances
Eq a => Eq (Member a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

(==) :: Member a -> Member a -> Bool #

(/=) :: Member a -> Member a -> Bool #

Ord a => Ord (Member a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

compare :: Member a -> Member a -> Ordering #

(<) :: Member a -> Member a -> Bool #

(<=) :: Member a -> Member a -> Bool #

(>) :: Member a -> Member a -> Bool #

(>=) :: Member a -> Member a -> Bool #

max :: Member a -> Member a -> Member a #

min :: Member a -> Member a -> Member a #

Read a => Read (Member a) Source # 
Instance details

Defined in Network.Yak.Types

Show a => Show (Member a) Source # 
Instance details

Defined in Network.Yak.Types

Methods

showsPrec :: Int -> Member a -> ShowS #

show :: Member a -> String #

showList :: [Member a] -> ShowS #

Generic (Member a) Source # 
Instance details

Defined in Network.Yak.Types

Associated Types

type Rep (Member a) :: Type -> Type #

Methods

from :: Member a -> Rep (Member a) x #

to :: Rep (Member a) x -> Member a #

Parameter a => Parameter (Member a) Source # 
Instance details

Defined in Network.Yak.Types

type Rep (Member a) Source # 
Instance details

Defined in Network.Yak.Types

memberData :: forall a a. Lens (Member a) (Member a) a a Source #