octane-0.20.1: Parse Rocket League replays.

Safe HaskellNone
LanguageHaskell2010

Octane.Type.List

Synopsis

Documentation

newtype List a Source #

A list of values.

Constructors

List 

Fields

Instances

HasField "content" (ArrayProperty a0) (List (Dictionary a0)) # 

Methods

getField :: Proxy# Symbol "content" -> ArrayProperty a0 -> List (Dictionary a0) #

HasField "unpack" (List a0) [a0] Source # 

Methods

getField :: Proxy# Symbol "unpack" -> List a0 -> [a0] #

ModifyField "content" (ArrayProperty a0) (ArrayProperty a0) (List (Dictionary a0)) (List (Dictionary a0)) # 

Methods

modifyField :: Proxy# Symbol "content" -> (List (Dictionary a0) -> List (Dictionary a0)) -> ArrayProperty a0 -> ArrayProperty a0 #

setField :: Proxy# Symbol "content" -> ArrayProperty a0 -> List (Dictionary a0) -> ArrayProperty a0 #

fieldLens :: Functor f => Proxy# Symbol "content" -> (List (Dictionary a0) -> f (List (Dictionary a0))) -> ArrayProperty a0 -> f (ArrayProperty a0) #

ModifyField "unpack" (List a0) (List a0) [a0] [a0] Source # 

Methods

modifyField :: Proxy# Symbol "unpack" -> ([a0] -> [a0]) -> List a0 -> List a0 #

setField :: Proxy# Symbol "unpack" -> List a0 -> [a0] -> List a0 #

fieldLens :: Functor f => Proxy# Symbol "unpack" -> ([a0] -> f [a0]) -> List a0 -> f (List a0) #

ModifyRec "content" (List (Dictionary a0)) cs0 => HasField "content" (Rec cs0 (ArrayProperty a0)) (List (Dictionary a0)) # 

Methods

getField :: Proxy# Symbol "content" -> Rec cs0 (ArrayProperty a0) -> List (Dictionary a0) #

ModifyRec "unpack" [a0] cs0 => HasField "unpack" (Rec cs0 (List a0)) [a0] Source # 

Methods

getField :: Proxy# Symbol "unpack" -> Rec cs0 (List a0) -> [a0] #

ModifyRec "content" (List (Dictionary a0)) cs0 => ModifyField "content" (Rec cs0 (ArrayProperty a0)) (Rec cs0 (ArrayProperty a0)) (List (Dictionary a0)) (List (Dictionary a0)) # 

Methods

modifyField :: Proxy# Symbol "content" -> (List (Dictionary a0) -> List (Dictionary a0)) -> Rec cs0 (ArrayProperty a0) -> Rec cs0 (ArrayProperty a0) #

setField :: Proxy# Symbol "content" -> Rec cs0 (ArrayProperty a0) -> List (Dictionary a0) -> Rec cs0 (ArrayProperty a0) #

fieldLens :: Functor f => Proxy# Symbol "content" -> (List (Dictionary a0) -> f (List (Dictionary a0))) -> Rec cs0 (ArrayProperty a0) -> f (Rec cs0 (ArrayProperty a0)) #

ModifyRec "unpack" [a0] cs0 => ModifyField "unpack" (Rec cs0 (List a0)) (Rec cs0 (List a0)) [a0] [a0] Source # 

Methods

modifyField :: Proxy# Symbol "unpack" -> ([a0] -> [a0]) -> Rec cs0 (List a0) -> Rec cs0 (List a0) #

setField :: Proxy# Symbol "unpack" -> Rec cs0 (List a0) -> [a0] -> Rec cs0 (List a0) #

fieldLens :: Functor f => Proxy# Symbol "unpack" -> ([a0] -> f [a0]) -> Rec cs0 (List a0) -> f (Rec cs0 (List a0)) #

Eq a => Eq (List a) Source # 

Methods

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

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

Ord a => Ord (List a) Source # 

Methods

compare :: List a -> List a -> Ordering #

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

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

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

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

max :: List a -> List a -> List a #

min :: List a -> List a -> List a #

Show a => Show (List a) Source # 

Methods

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

show :: List a -> String #

showList :: [List a] -> ShowS #

ToJSON a => ToJSON (List a) Source #

Encoded as a JSON array directly.

type FieldType "unpack" (List a0) Source # 
type FieldType "unpack" (List a0) = [a0]
type UpdateType "content" (ArrayProperty a0) (List (Dictionary a0)) # 
type UpdateType "content" (ArrayProperty a0) (List (Dictionary a0)) = ArrayProperty a0
type UpdateType "unpack" (List a0) [a0] Source # 
type UpdateType "unpack" (List a0) [a0] = List a0