top-0.2.4: Top (typed oriented protocol) API

Safe HaskellNone
LanguageHaskell2010

Data.Pattern.Types

Contents

Description

Pattern related types

Synopsis

Documentation

type Matcher = ByteString -> Bool Source #

A matcher is a predicate defined over the binary representation of a value

Top patterns

newtype ByPattern a Source #

A routing protocol specified by a pattern and a type.

Once a connection is established, clients:

  • can send messages of the given type
  • will receive all messages of the same type, that match the given pattern, sent by other agents

Constructors

ByPattern Pattern 

Instances

Eq (ByPattern a) Source # 

Methods

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

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

Ord (ByPattern a) Source # 
Show (ByPattern a) Source # 
Generic (ByPattern a) Source # 

Associated Types

type Rep (ByPattern a) :: * -> * #

Methods

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

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

Flat (ByPattern a) Source # 
Model a => Model (ByPattern a) Source # 

Methods

envType :: Proxy * (ByPattern a) -> State Env HType #

type Rep (ByPattern a) Source # 
type Rep (ByPattern a) = D1 (MetaData "ByPattern" "Data.Pattern.Types" "top-0.2.4-7a1nh8xG3Hf47wJEwYUttt" True) (C1 (MetaCons "ByPattern" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pattern)))

type Pattern = [Match [Bit]] Source #

A Pattern is just a list of matches, values are represented by their Flat binary serialisation

data Match v Source #

Match either a flattened value of any value of a given type

Constructors

MatchValue v

Match the specified value

MatchAny (Type AbsRef)

Match any value of the given type (wildcard)

Instances

Functor Match Source # 

Methods

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

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

Eq v => Eq (Match v) Source # 

Methods

(==) :: Match v -> Match v -> Bool #

(/=) :: Match v -> Match v -> Bool #

Ord v => Ord (Match v) Source # 

Methods

compare :: Match v -> Match v -> Ordering #

(<) :: Match v -> Match v -> Bool #

(<=) :: Match v -> Match v -> Bool #

(>) :: Match v -> Match v -> Bool #

(>=) :: Match v -> Match v -> Bool #

max :: Match v -> Match v -> Match v #

min :: Match v -> Match v -> Match v #

Show v => Show (Match v) Source # 

Methods

showsPrec :: Int -> Match v -> ShowS #

show :: Match v -> String #

showList :: [Match v] -> ShowS #

Generic (Match v) Source # 

Associated Types

type Rep (Match v) :: * -> * #

Methods

from :: Match v -> Rep (Match v) x #

to :: Rep (Match v) x -> Match v #

Flat v => Flat (Match v) Source # 

Methods

encode :: Match v -> Encoding #

decode :: Get (Match v) #

size :: Match v -> NumBits -> NumBits #

Model v => Model (Match v) Source # 

Methods

envType :: Proxy * (Match v) -> State Env HType #

type Rep (Match v) Source # 
type Rep (Match v) = D1 (MetaData "Match" "Data.Pattern.Types" "top-0.2.4-7a1nh8xG3Hf47wJEwYUttt" False) ((:+:) (C1 (MetaCons "MatchValue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 v))) (C1 (MetaCons "MatchAny" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type AbsRef)))))

data Bit :: * #

A Bit

Constructors

V0 
V1 

Instances

Eq Bit 

Methods

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

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

Ord Bit 

Methods

compare :: Bit -> Bit -> Ordering #

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

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

(>) :: Bit -> Bit -> Bool #

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

max :: Bit -> Bit -> Bit #

min :: Bit -> Bit -> Bit #

Show Bit 

Methods

showsPrec :: Int -> Bit -> ShowS #

show :: Bit -> String #

showList :: [Bit] -> ShowS #

Generic Bit 

Associated Types

type Rep Bit :: * -> * #

Methods

from :: Bit -> Rep Bit x #

to :: Rep Bit x -> Bit #

Flat Bit 
Model Bit 

Methods

envType :: Proxy * Bit -> State Env HType #

type Rep Bit 
type Rep Bit = D1 (MetaData "Bit" "ZM.Type.Bit" "zm-0.3.2-9EffK4RA8nV74pYjwjqtDn" False) ((:+:) (C1 (MetaCons "V0" PrefixI False) U1) (C1 (MetaCons "V1" PrefixI False) U1))

optPattern :: Pattern -> Pattern Source #

Optimise a Pattern by concatenating adjacent value matches

Internal patterns

type IPattern = Pat PRef Source #

Internal pattern representation

data Pat v Source #

Pattern representation used for internal processing

Constructors

PCon

A constructor

Fields

PName v

A primitive value (for example PRef)

Instances

Eq v => Eq (Pat v) Source # 

Methods

(==) :: Pat v -> Pat v -> Bool #

(/=) :: Pat v -> Pat v -> Bool #

Ord v => Ord (Pat v) Source # 

Methods

compare :: Pat v -> Pat v -> Ordering #

(<) :: Pat v -> Pat v -> Bool #

(<=) :: Pat v -> Pat v -> Bool #

(>) :: Pat v -> Pat v -> Bool #

(>=) :: Pat v -> Pat v -> Bool #

max :: Pat v -> Pat v -> Pat v #

min :: Pat v -> Pat v -> Pat v #

Show v => Show (Pat v) Source # 

Methods

showsPrec :: Int -> Pat v -> ShowS #

show :: Pat v -> String #

showList :: [Pat v] -> ShowS #

data PRef Source #

Literals and variables

Instances

Eq PRef Source # 

Methods

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

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

Ord PRef Source # 

Methods

compare :: PRef -> PRef -> Ordering #

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

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

(>) :: PRef -> PRef -> Bool #

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

max :: PRef -> PRef -> PRef #

min :: PRef -> PRef -> PRef #

Show PRef Source # 

Methods

showsPrec :: Int -> PRef -> ShowS #

show :: PRef -> String #

showList :: [PRef] -> ShowS #