kurita-0: Find the alpha emoji

Safe HaskellNone
LanguageHaskell2010

Kurita.Protocol

Contents

Synopsis

Documentation

data PlayedGame c s m Source #

Who played in a game, the score they got, sorted in score order.

Constructors

PlayedGame 

Fields

Instances
Functor (PlayedGame c s) Source # 
Instance details

Defined in Kurita.Protocol

Methods

fmap :: (a -> b) -> PlayedGame c s a -> PlayedGame c s b #

(<$) :: a -> PlayedGame c s b -> PlayedGame c s a #

(Eq m, Eq s, Eq c) => Eq (PlayedGame c s m) Source # 
Instance details

Defined in Kurita.Protocol

Methods

(==) :: PlayedGame c s m -> PlayedGame c s m -> Bool #

(/=) :: PlayedGame c s m -> PlayedGame c s m -> Bool #

(Ord m, Ord s, Ord c) => Ord (PlayedGame c s m) Source # 
Instance details

Defined in Kurita.Protocol

Methods

compare :: PlayedGame c s m -> PlayedGame c s m -> Ordering #

(<) :: PlayedGame c s m -> PlayedGame c s m -> Bool #

(<=) :: PlayedGame c s m -> PlayedGame c s m -> Bool #

(>) :: PlayedGame c s m -> PlayedGame c s m -> Bool #

(>=) :: PlayedGame c s m -> PlayedGame c s m -> Bool #

max :: PlayedGame c s m -> PlayedGame c s m -> PlayedGame c s m #

min :: PlayedGame c s m -> PlayedGame c s m -> PlayedGame c s m #

(Show m, Show s, Show c) => Show (PlayedGame c s m) Source # 
Instance details

Defined in Kurita.Protocol

Methods

showsPrec :: Int -> PlayedGame c s m -> ShowS #

show :: PlayedGame c s m -> String #

showList :: [PlayedGame c s m] -> ShowS #

(ToJSON c, ToJSON s, ToJSON m) => ToJSON (PlayedGame c s m) Source # 
Instance details

Defined in Kurita.Protocol

(FromJSON c, FromJSON s, FromJSON m, Ord c, Ord s) => FromJSON (PlayedGame c s m) Source # 
Instance details

Defined in Kurita.Protocol

gameSorted :: forall c s m c s. Lens (PlayedGame c s m) (PlayedGame c s m) (SortedList (s, c)) (SortedList (s, c)) Source #

gameExtra :: forall c s m m. Lens (PlayedGame c s m) (PlayedGame c s m) m m Source #

data Bracket c s m Source #

Constructors

Bracket 

Fields

  • _bPlayed :: ![[PlayedGame c s m]]

    list of rounds, recent first, containing played games, then which won. We append new games to the end of the first list. If we're playing a round, the first list in this must be for it.

  • _bUpcoming :: ![[c]]

    a list of the list of competitors that are scheduled for a game in this round. who have upcoming matches in this round.

  • _bCurrent :: !(Maybe (PlayedGame c s m))

    The current game, if Nothing the tournament is over.

Instances
Functor (Bracket c s) Source # 
Instance details

Defined in Kurita.Protocol

Methods

fmap :: (a -> b) -> Bracket c s a -> Bracket c s b #

(<$) :: a -> Bracket c s b -> Bracket c s a #

(Eq m, Eq s, Eq c) => Eq (Bracket c s m) Source # 
Instance details

Defined in Kurita.Protocol

Methods

(==) :: Bracket c s m -> Bracket c s m -> Bool #

(/=) :: Bracket c s m -> Bracket c s m -> Bool #

(Ord m, Ord s, Ord c) => Ord (Bracket c s m) Source # 
Instance details

Defined in Kurita.Protocol

Methods

compare :: Bracket c s m -> Bracket c s m -> Ordering #

(<) :: Bracket c s m -> Bracket c s m -> Bool #

(<=) :: Bracket c s m -> Bracket c s m -> Bool #

(>) :: Bracket c s m -> Bracket c s m -> Bool #

(>=) :: Bracket c s m -> Bracket c s m -> Bool #

max :: Bracket c s m -> Bracket c s m -> Bracket c s m #

min :: Bracket c s m -> Bracket c s m -> Bracket c s m #

(Show m, Show s, Show c) => Show (Bracket c s m) Source # 
Instance details

Defined in Kurita.Protocol

Methods

showsPrec :: Int -> Bracket c s m -> ShowS #

show :: Bracket c s m -> String #

showList :: [Bracket c s m] -> ShowS #

(ToJSON c, ToJSON s, ToJSON m) => ToJSON (Bracket c s m) Source # 
Instance details

Defined in Kurita.Protocol

Methods

toJSON :: Bracket c s m -> Value #

toEncoding :: Bracket c s m -> Encoding #

toJSONList :: [Bracket c s m] -> Value #

toEncodingList :: [Bracket c s m] -> Encoding #

(FromJSON c, FromJSON s, FromJSON m, Ord c, Ord s) => FromJSON (Bracket c s m) Source # 
Instance details

Defined in Kurita.Protocol

Methods

parseJSON :: Value -> Parser (Bracket c s m) #

parseJSONList :: Value -> Parser [Bracket c s m] #

HasBracket (Bracket c s m) c s m Source # 
Instance details

Defined in Kurita.Protocol

Methods

bracket :: Lens' (Bracket c s m) (Bracket c s m) Source #

bCurrent :: Lens' (Bracket c s m) (Maybe (PlayedGame c s m)) Source #

bPlayed :: Lens' (Bracket c s m) [[PlayedGame c s m]] Source #

bUpcoming :: Lens' (Bracket c s m) [[c]] Source #

class HasBracket c c s m | c -> c s m where Source #

Minimal complete definition

bracket

Methods

bracket :: Lens' c (Bracket c s m) Source #

bCurrent :: Lens' c (Maybe (PlayedGame c s m)) Source #

bPlayed :: Lens' c [[PlayedGame c s m]] Source #

bUpcoming :: Lens' c [[c]] Source #

Instances
HasBracket (Bracket c s m) c s m Source # 
Instance details

Defined in Kurita.Protocol

Methods

bracket :: Lens' (Bracket c s m) (Bracket c s m) Source #

bCurrent :: Lens' (Bracket c s m) (Maybe (PlayedGame c s m)) Source #

bPlayed :: Lens' (Bracket c s m) [[PlayedGame c s m]] Source #

bUpcoming :: Lens' (Bracket c s m) [[c]] Source #

changeVoteType :: (Ord c, Ord s2) => (s1 -> s2) -> Bracket c s1 a -> Bracket c s2 a Source #

seedBracket :: (Ord c, Ord s, Monoid s) => ([c] -> m) -> (Int -> [c] -> m) -> [c] -> Bracket c s m Source #

finishGame :: (Ord c, Ord s, Monoid s) => ([c] -> m) -> (Int -> [c] -> m) -> Bracket c s m -> Bracket c s m Source #

Finishes the current game and start the next, generating a new round if need be, or finishing the game if this was the last round.

upToGame :: (Ord c, Ord s, Monoid s) => ([c] -> m) -> [c] -> PlayedGame c s m Source #

addScores :: (Ord c, Ord s, Semigroup s) => [(c, s)] -> Bracket c s a -> Bracket c s a Source #

addScore :: (Ord c, Reifies p Integer) => c -> Word32 -> Bracket c (HyperLogLog p) a -> Bracket c (HyperLogLog p) a Source #

data TDown c Source #

Constructors

BattleStart 
ScoreUpdate [(c, Int64)] 
Instances
Show c => Show (TDown c) Source # 
Instance details

Defined in Kurita.Protocol

Methods

showsPrec :: Int -> TDown c -> ShowS #

show :: TDown c -> String #

showList :: [TDown c] -> ShowS #

ToJSON c => ToJSON (TDown c) Source # 
Instance details

Defined in Kurita.Protocol

(Ord c, FromJSON c) => FromJSON (TDown c) Source # 
Instance details

Defined in Kurita.Protocol

data TUp c Source #

Constructors

Vote c 
Instances
Eq c => Eq (TUp c) Source # 
Instance details

Defined in Kurita.Protocol

Methods

(==) :: TUp c -> TUp c -> Bool #

(/=) :: TUp c -> TUp c -> Bool #

Ord c => Ord (TUp c) Source # 
Instance details

Defined in Kurita.Protocol

Methods

compare :: TUp c -> TUp c -> Ordering #

(<) :: TUp c -> TUp c -> Bool #

(<=) :: TUp c -> TUp c -> Bool #

(>) :: TUp c -> TUp c -> Bool #

(>=) :: TUp c -> TUp c -> Bool #

max :: TUp c -> TUp c -> TUp c #

min :: TUp c -> TUp c -> TUp c #

Show c => Show (TUp c) Source # 
Instance details

Defined in Kurita.Protocol

Methods

showsPrec :: Int -> TUp c -> ShowS #

show :: TUp c -> String #

showList :: [TUp c] -> ShowS #

ToJSON c => ToJSON (TUp c) Source # 
Instance details

Defined in Kurita.Protocol

Methods

toJSON :: TUp c -> Value #

toEncoding :: TUp c -> Encoding #

toJSONList :: [TUp c] -> Value #

toEncodingList :: [TUp c] -> Encoding #

FromJSON c => FromJSON (TUp c) Source # 
Instance details

Defined in Kurita.Protocol

Methods

parseJSON :: Value -> Parser (TUp c) #

parseJSONList :: Value -> Parser [TUp c] #

data RUp hllsz c Source #

Constructors

Votes [(c, HyperLogLog hllsz)] 
Instances
Show c => Show (RUp hllsz c) Source # 
Instance details

Defined in Kurita.Protocol

Methods

showsPrec :: Int -> RUp hllsz c -> ShowS #

show :: RUp hllsz c -> String #

showList :: [RUp hllsz c] -> ShowS #

ToJSON c => ToJSON (RUp hllsz c) Source # 
Instance details

Defined in Kurita.Protocol

Methods

toJSON :: RUp hllsz c -> Value #

toEncoding :: RUp hllsz c -> Encoding #

toJSONList :: [RUp hllsz c] -> Value #

toEncodingList :: [RUp hllsz c] -> Encoding #

(Reifies hllsz Integer, FromJSON c) => FromJSON (RUp hllsz c) Source # 
Instance details

Defined in Kurita.Protocol

Methods

parseJSON :: Value -> Parser (RUp hllsz c) #

parseJSONList :: Value -> Parser [RUp hllsz c] #

Orphan instances