module Swarm.Game.Achievement.Definitions (
CategorizedAchievement (..),
GlobalAchievement (..),
GameplayAchievement (..),
listAchievements,
ExpectedEffort (..),
Quotation (..),
FlavorText (..),
AchievementInfo (..),
ValidityConditions (..),
SystemTypeValidity (..),
GameplayModeValidity (..),
) where
import Data.Aeson
import Data.List.Extra (enumerate)
import Data.Text (Text)
import GHC.Generics (Generic)
import Swarm.Language.Syntax (Syntax)
import Swarm.Language.Text.Markdown (Document)
data ExpectedEffort
= Trivial
| Easy
| Moderate
| Gruelling
deriving (ExpectedEffort -> ExpectedEffort -> Bool
(ExpectedEffort -> ExpectedEffort -> Bool)
-> (ExpectedEffort -> ExpectedEffort -> Bool) -> Eq ExpectedEffort
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExpectedEffort -> ExpectedEffort -> Bool
== :: ExpectedEffort -> ExpectedEffort -> Bool
$c/= :: ExpectedEffort -> ExpectedEffort -> Bool
/= :: ExpectedEffort -> ExpectedEffort -> Bool
Eq, Eq ExpectedEffort
Eq ExpectedEffort =>
(ExpectedEffort -> ExpectedEffort -> Ordering)
-> (ExpectedEffort -> ExpectedEffort -> Bool)
-> (ExpectedEffort -> ExpectedEffort -> Bool)
-> (ExpectedEffort -> ExpectedEffort -> Bool)
-> (ExpectedEffort -> ExpectedEffort -> Bool)
-> (ExpectedEffort -> ExpectedEffort -> ExpectedEffort)
-> (ExpectedEffort -> ExpectedEffort -> ExpectedEffort)
-> Ord ExpectedEffort
ExpectedEffort -> ExpectedEffort -> Bool
ExpectedEffort -> ExpectedEffort -> Ordering
ExpectedEffort -> ExpectedEffort -> ExpectedEffort
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ExpectedEffort -> ExpectedEffort -> Ordering
compare :: ExpectedEffort -> ExpectedEffort -> Ordering
$c< :: ExpectedEffort -> ExpectedEffort -> Bool
< :: ExpectedEffort -> ExpectedEffort -> Bool
$c<= :: ExpectedEffort -> ExpectedEffort -> Bool
<= :: ExpectedEffort -> ExpectedEffort -> Bool
$c> :: ExpectedEffort -> ExpectedEffort -> Bool
> :: ExpectedEffort -> ExpectedEffort -> Bool
$c>= :: ExpectedEffort -> ExpectedEffort -> Bool
>= :: ExpectedEffort -> ExpectedEffort -> Bool
$cmax :: ExpectedEffort -> ExpectedEffort -> ExpectedEffort
max :: ExpectedEffort -> ExpectedEffort -> ExpectedEffort
$cmin :: ExpectedEffort -> ExpectedEffort -> ExpectedEffort
min :: ExpectedEffort -> ExpectedEffort -> ExpectedEffort
Ord, Int -> ExpectedEffort -> ShowS
[ExpectedEffort] -> ShowS
ExpectedEffort -> String
(Int -> ExpectedEffort -> ShowS)
-> (ExpectedEffort -> String)
-> ([ExpectedEffort] -> ShowS)
-> Show ExpectedEffort
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExpectedEffort -> ShowS
showsPrec :: Int -> ExpectedEffort -> ShowS
$cshow :: ExpectedEffort -> String
show :: ExpectedEffort -> String
$cshowList :: [ExpectedEffort] -> ShowS
showList :: [ExpectedEffort] -> ShowS
Show, ExpectedEffort
ExpectedEffort -> ExpectedEffort -> Bounded ExpectedEffort
forall a. a -> a -> Bounded a
$cminBound :: ExpectedEffort
minBound :: ExpectedEffort
$cmaxBound :: ExpectedEffort
maxBound :: ExpectedEffort
Bounded, Int -> ExpectedEffort
ExpectedEffort -> Int
ExpectedEffort -> [ExpectedEffort]
ExpectedEffort -> ExpectedEffort
ExpectedEffort -> ExpectedEffort -> [ExpectedEffort]
ExpectedEffort
-> ExpectedEffort -> ExpectedEffort -> [ExpectedEffort]
(ExpectedEffort -> ExpectedEffort)
-> (ExpectedEffort -> ExpectedEffort)
-> (Int -> ExpectedEffort)
-> (ExpectedEffort -> Int)
-> (ExpectedEffort -> [ExpectedEffort])
-> (ExpectedEffort -> ExpectedEffort -> [ExpectedEffort])
-> (ExpectedEffort -> ExpectedEffort -> [ExpectedEffort])
-> (ExpectedEffort
-> ExpectedEffort -> ExpectedEffort -> [ExpectedEffort])
-> Enum ExpectedEffort
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ExpectedEffort -> ExpectedEffort
succ :: ExpectedEffort -> ExpectedEffort
$cpred :: ExpectedEffort -> ExpectedEffort
pred :: ExpectedEffort -> ExpectedEffort
$ctoEnum :: Int -> ExpectedEffort
toEnum :: Int -> ExpectedEffort
$cfromEnum :: ExpectedEffort -> Int
fromEnum :: ExpectedEffort -> Int
$cenumFrom :: ExpectedEffort -> [ExpectedEffort]
enumFrom :: ExpectedEffort -> [ExpectedEffort]
$cenumFromThen :: ExpectedEffort -> ExpectedEffort -> [ExpectedEffort]
enumFromThen :: ExpectedEffort -> ExpectedEffort -> [ExpectedEffort]
$cenumFromTo :: ExpectedEffort -> ExpectedEffort -> [ExpectedEffort]
enumFromTo :: ExpectedEffort -> ExpectedEffort -> [ExpectedEffort]
$cenumFromThenTo :: ExpectedEffort
-> ExpectedEffort -> ExpectedEffort -> [ExpectedEffort]
enumFromThenTo :: ExpectedEffort
-> ExpectedEffort -> ExpectedEffort -> [ExpectedEffort]
Enum, (forall x. ExpectedEffort -> Rep ExpectedEffort x)
-> (forall x. Rep ExpectedEffort x -> ExpectedEffort)
-> Generic ExpectedEffort
forall x. Rep ExpectedEffort x -> ExpectedEffort
forall x. ExpectedEffort -> Rep ExpectedEffort x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExpectedEffort -> Rep ExpectedEffort x
from :: forall x. ExpectedEffort -> Rep ExpectedEffort x
$cto :: forall x. Rep ExpectedEffort x -> ExpectedEffort
to :: forall x. Rep ExpectedEffort x -> ExpectedEffort
Generic, Maybe ExpectedEffort
Value -> Parser [ExpectedEffort]
Value -> Parser ExpectedEffort
(Value -> Parser ExpectedEffort)
-> (Value -> Parser [ExpectedEffort])
-> Maybe ExpectedEffort
-> FromJSON ExpectedEffort
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ExpectedEffort
parseJSON :: Value -> Parser ExpectedEffort
$cparseJSONList :: Value -> Parser [ExpectedEffort]
parseJSONList :: Value -> Parser [ExpectedEffort]
$comittedField :: Maybe ExpectedEffort
omittedField :: Maybe ExpectedEffort
FromJSON, [ExpectedEffort] -> Value
[ExpectedEffort] -> Encoding
ExpectedEffort -> Bool
ExpectedEffort -> Value
ExpectedEffort -> Encoding
(ExpectedEffort -> Value)
-> (ExpectedEffort -> Encoding)
-> ([ExpectedEffort] -> Value)
-> ([ExpectedEffort] -> Encoding)
-> (ExpectedEffort -> Bool)
-> ToJSON ExpectedEffort
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ExpectedEffort -> Value
toJSON :: ExpectedEffort -> Value
$ctoEncoding :: ExpectedEffort -> Encoding
toEncoding :: ExpectedEffort -> Encoding
$ctoJSONList :: [ExpectedEffort] -> Value
toJSONList :: [ExpectedEffort] -> Value
$ctoEncodingList :: [ExpectedEffort] -> Encoding
toEncodingList :: [ExpectedEffort] -> Encoding
$comitField :: ExpectedEffort -> Bool
omitField :: ExpectedEffort -> Bool
ToJSON)
data Quotation = Quotation
{ Quotation -> Text
attribution :: Text
, Quotation -> Text
content :: Text
}
deriving (Quotation -> Quotation -> Bool
(Quotation -> Quotation -> Bool)
-> (Quotation -> Quotation -> Bool) -> Eq Quotation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Quotation -> Quotation -> Bool
== :: Quotation -> Quotation -> Bool
$c/= :: Quotation -> Quotation -> Bool
/= :: Quotation -> Quotation -> Bool
Eq, Int -> Quotation -> ShowS
[Quotation] -> ShowS
Quotation -> String
(Int -> Quotation -> ShowS)
-> (Quotation -> String)
-> ([Quotation] -> ShowS)
-> Show Quotation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Quotation -> ShowS
showsPrec :: Int -> Quotation -> ShowS
$cshow :: Quotation -> String
show :: Quotation -> String
$cshowList :: [Quotation] -> ShowS
showList :: [Quotation] -> ShowS
Show, (forall x. Quotation -> Rep Quotation x)
-> (forall x. Rep Quotation x -> Quotation) -> Generic Quotation
forall x. Rep Quotation x -> Quotation
forall x. Quotation -> Rep Quotation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Quotation -> Rep Quotation x
from :: forall x. Quotation -> Rep Quotation x
$cto :: forall x. Rep Quotation x -> Quotation
to :: forall x. Rep Quotation x -> Quotation
Generic, Maybe Quotation
Value -> Parser [Quotation]
Value -> Parser Quotation
(Value -> Parser Quotation)
-> (Value -> Parser [Quotation])
-> Maybe Quotation
-> FromJSON Quotation
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Quotation
parseJSON :: Value -> Parser Quotation
$cparseJSONList :: Value -> Parser [Quotation]
parseJSONList :: Value -> Parser [Quotation]
$comittedField :: Maybe Quotation
omittedField :: Maybe Quotation
FromJSON, [Quotation] -> Value
[Quotation] -> Encoding
Quotation -> Bool
Quotation -> Value
Quotation -> Encoding
(Quotation -> Value)
-> (Quotation -> Encoding)
-> ([Quotation] -> Value)
-> ([Quotation] -> Encoding)
-> (Quotation -> Bool)
-> ToJSON Quotation
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Quotation -> Value
toJSON :: Quotation -> Value
$ctoEncoding :: Quotation -> Encoding
toEncoding :: Quotation -> Encoding
$ctoJSONList :: [Quotation] -> Value
toJSONList :: [Quotation] -> Value
$ctoEncodingList :: [Quotation] -> Encoding
toEncodingList :: [Quotation] -> Encoding
$comitField :: Quotation -> Bool
omitField :: Quotation -> Bool
ToJSON)
data FlavorText
= Freeform (Document Syntax)
| FTQuotation Quotation
deriving (FlavorText -> FlavorText -> Bool
(FlavorText -> FlavorText -> Bool)
-> (FlavorText -> FlavorText -> Bool) -> Eq FlavorText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FlavorText -> FlavorText -> Bool
== :: FlavorText -> FlavorText -> Bool
$c/= :: FlavorText -> FlavorText -> Bool
/= :: FlavorText -> FlavorText -> Bool
Eq, Int -> FlavorText -> ShowS
[FlavorText] -> ShowS
FlavorText -> String
(Int -> FlavorText -> ShowS)
-> (FlavorText -> String)
-> ([FlavorText] -> ShowS)
-> Show FlavorText
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FlavorText -> ShowS
showsPrec :: Int -> FlavorText -> ShowS
$cshow :: FlavorText -> String
show :: FlavorText -> String
$cshowList :: [FlavorText] -> ShowS
showList :: [FlavorText] -> ShowS
Show, (forall x. FlavorText -> Rep FlavorText x)
-> (forall x. Rep FlavorText x -> FlavorText) -> Generic FlavorText
forall x. Rep FlavorText x -> FlavorText
forall x. FlavorText -> Rep FlavorText x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FlavorText -> Rep FlavorText x
from :: forall x. FlavorText -> Rep FlavorText x
$cto :: forall x. Rep FlavorText x -> FlavorText
to :: forall x. Rep FlavorText x -> FlavorText
Generic, Maybe FlavorText
Value -> Parser [FlavorText]
Value -> Parser FlavorText
(Value -> Parser FlavorText)
-> (Value -> Parser [FlavorText])
-> Maybe FlavorText
-> FromJSON FlavorText
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser FlavorText
parseJSON :: Value -> Parser FlavorText
$cparseJSONList :: Value -> Parser [FlavorText]
parseJSONList :: Value -> Parser [FlavorText]
$comittedField :: Maybe FlavorText
omittedField :: Maybe FlavorText
FromJSON, [FlavorText] -> Value
[FlavorText] -> Encoding
FlavorText -> Bool
FlavorText -> Value
FlavorText -> Encoding
(FlavorText -> Value)
-> (FlavorText -> Encoding)
-> ([FlavorText] -> Value)
-> ([FlavorText] -> Encoding)
-> (FlavorText -> Bool)
-> ToJSON FlavorText
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: FlavorText -> Value
toJSON :: FlavorText -> Value
$ctoEncoding :: FlavorText -> Encoding
toEncoding :: FlavorText -> Encoding
$ctoJSONList :: [FlavorText] -> Value
toJSONList :: [FlavorText] -> Value
$ctoEncodingList :: [FlavorText] -> Encoding
toEncodingList :: [FlavorText] -> Encoding
$comitField :: FlavorText -> Bool
omitField :: FlavorText -> Bool
ToJSON)
data SystemTypeValidity
= ValidForSystemRobot
| OnlyPlayerRobot
deriving (SystemTypeValidity -> SystemTypeValidity -> Bool
(SystemTypeValidity -> SystemTypeValidity -> Bool)
-> (SystemTypeValidity -> SystemTypeValidity -> Bool)
-> Eq SystemTypeValidity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SystemTypeValidity -> SystemTypeValidity -> Bool
== :: SystemTypeValidity -> SystemTypeValidity -> Bool
$c/= :: SystemTypeValidity -> SystemTypeValidity -> Bool
/= :: SystemTypeValidity -> SystemTypeValidity -> Bool
Eq, Int -> SystemTypeValidity -> ShowS
[SystemTypeValidity] -> ShowS
SystemTypeValidity -> String
(Int -> SystemTypeValidity -> ShowS)
-> (SystemTypeValidity -> String)
-> ([SystemTypeValidity] -> ShowS)
-> Show SystemTypeValidity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SystemTypeValidity -> ShowS
showsPrec :: Int -> SystemTypeValidity -> ShowS
$cshow :: SystemTypeValidity -> String
show :: SystemTypeValidity -> String
$cshowList :: [SystemTypeValidity] -> ShowS
showList :: [SystemTypeValidity] -> ShowS
Show, (forall x. SystemTypeValidity -> Rep SystemTypeValidity x)
-> (forall x. Rep SystemTypeValidity x -> SystemTypeValidity)
-> Generic SystemTypeValidity
forall x. Rep SystemTypeValidity x -> SystemTypeValidity
forall x. SystemTypeValidity -> Rep SystemTypeValidity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SystemTypeValidity -> Rep SystemTypeValidity x
from :: forall x. SystemTypeValidity -> Rep SystemTypeValidity x
$cto :: forall x. Rep SystemTypeValidity x -> SystemTypeValidity
to :: forall x. Rep SystemTypeValidity x -> SystemTypeValidity
Generic, Maybe SystemTypeValidity
Value -> Parser [SystemTypeValidity]
Value -> Parser SystemTypeValidity
(Value -> Parser SystemTypeValidity)
-> (Value -> Parser [SystemTypeValidity])
-> Maybe SystemTypeValidity
-> FromJSON SystemTypeValidity
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser SystemTypeValidity
parseJSON :: Value -> Parser SystemTypeValidity
$cparseJSONList :: Value -> Parser [SystemTypeValidity]
parseJSONList :: Value -> Parser [SystemTypeValidity]
$comittedField :: Maybe SystemTypeValidity
omittedField :: Maybe SystemTypeValidity
FromJSON, [SystemTypeValidity] -> Value
[SystemTypeValidity] -> Encoding
SystemTypeValidity -> Bool
SystemTypeValidity -> Value
SystemTypeValidity -> Encoding
(SystemTypeValidity -> Value)
-> (SystemTypeValidity -> Encoding)
-> ([SystemTypeValidity] -> Value)
-> ([SystemTypeValidity] -> Encoding)
-> (SystemTypeValidity -> Bool)
-> ToJSON SystemTypeValidity
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: SystemTypeValidity -> Value
toJSON :: SystemTypeValidity -> Value
$ctoEncoding :: SystemTypeValidity -> Encoding
toEncoding :: SystemTypeValidity -> Encoding
$ctoJSONList :: [SystemTypeValidity] -> Value
toJSONList :: [SystemTypeValidity] -> Value
$ctoEncodingList :: [SystemTypeValidity] -> Encoding
toEncodingList :: [SystemTypeValidity] -> Encoding
$comitField :: SystemTypeValidity -> Bool
omitField :: SystemTypeValidity -> Bool
ToJSON)
data GameplayModeValidity
= ValidInCreativeMode
| ExcludesCreativeMode
deriving (GameplayModeValidity -> GameplayModeValidity -> Bool
(GameplayModeValidity -> GameplayModeValidity -> Bool)
-> (GameplayModeValidity -> GameplayModeValidity -> Bool)
-> Eq GameplayModeValidity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GameplayModeValidity -> GameplayModeValidity -> Bool
== :: GameplayModeValidity -> GameplayModeValidity -> Bool
$c/= :: GameplayModeValidity -> GameplayModeValidity -> Bool
/= :: GameplayModeValidity -> GameplayModeValidity -> Bool
Eq, Int -> GameplayModeValidity -> ShowS
[GameplayModeValidity] -> ShowS
GameplayModeValidity -> String
(Int -> GameplayModeValidity -> ShowS)
-> (GameplayModeValidity -> String)
-> ([GameplayModeValidity] -> ShowS)
-> Show GameplayModeValidity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GameplayModeValidity -> ShowS
showsPrec :: Int -> GameplayModeValidity -> ShowS
$cshow :: GameplayModeValidity -> String
show :: GameplayModeValidity -> String
$cshowList :: [GameplayModeValidity] -> ShowS
showList :: [GameplayModeValidity] -> ShowS
Show, (forall x. GameplayModeValidity -> Rep GameplayModeValidity x)
-> (forall x. Rep GameplayModeValidity x -> GameplayModeValidity)
-> Generic GameplayModeValidity
forall x. Rep GameplayModeValidity x -> GameplayModeValidity
forall x. GameplayModeValidity -> Rep GameplayModeValidity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GameplayModeValidity -> Rep GameplayModeValidity x
from :: forall x. GameplayModeValidity -> Rep GameplayModeValidity x
$cto :: forall x. Rep GameplayModeValidity x -> GameplayModeValidity
to :: forall x. Rep GameplayModeValidity x -> GameplayModeValidity
Generic, Maybe GameplayModeValidity
Value -> Parser [GameplayModeValidity]
Value -> Parser GameplayModeValidity
(Value -> Parser GameplayModeValidity)
-> (Value -> Parser [GameplayModeValidity])
-> Maybe GameplayModeValidity
-> FromJSON GameplayModeValidity
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser GameplayModeValidity
parseJSON :: Value -> Parser GameplayModeValidity
$cparseJSONList :: Value -> Parser [GameplayModeValidity]
parseJSONList :: Value -> Parser [GameplayModeValidity]
$comittedField :: Maybe GameplayModeValidity
omittedField :: Maybe GameplayModeValidity
FromJSON, [GameplayModeValidity] -> Value
[GameplayModeValidity] -> Encoding
GameplayModeValidity -> Bool
GameplayModeValidity -> Value
GameplayModeValidity -> Encoding
(GameplayModeValidity -> Value)
-> (GameplayModeValidity -> Encoding)
-> ([GameplayModeValidity] -> Value)
-> ([GameplayModeValidity] -> Encoding)
-> (GameplayModeValidity -> Bool)
-> ToJSON GameplayModeValidity
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: GameplayModeValidity -> Value
toJSON :: GameplayModeValidity -> Value
$ctoEncoding :: GameplayModeValidity -> Encoding
toEncoding :: GameplayModeValidity -> Encoding
$ctoJSONList :: [GameplayModeValidity] -> Value
toJSONList :: [GameplayModeValidity] -> Value
$ctoEncodingList :: [GameplayModeValidity] -> Encoding
toEncodingList :: [GameplayModeValidity] -> Encoding
$comitField :: GameplayModeValidity -> Bool
omitField :: GameplayModeValidity -> Bool
ToJSON)
data ValidityConditions = ValidityConditions SystemTypeValidity GameplayModeValidity
deriving (ValidityConditions -> ValidityConditions -> Bool
(ValidityConditions -> ValidityConditions -> Bool)
-> (ValidityConditions -> ValidityConditions -> Bool)
-> Eq ValidityConditions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ValidityConditions -> ValidityConditions -> Bool
== :: ValidityConditions -> ValidityConditions -> Bool
$c/= :: ValidityConditions -> ValidityConditions -> Bool
/= :: ValidityConditions -> ValidityConditions -> Bool
Eq, Int -> ValidityConditions -> ShowS
[ValidityConditions] -> ShowS
ValidityConditions -> String
(Int -> ValidityConditions -> ShowS)
-> (ValidityConditions -> String)
-> ([ValidityConditions] -> ShowS)
-> Show ValidityConditions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ValidityConditions -> ShowS
showsPrec :: Int -> ValidityConditions -> ShowS
$cshow :: ValidityConditions -> String
show :: ValidityConditions -> String
$cshowList :: [ValidityConditions] -> ShowS
showList :: [ValidityConditions] -> ShowS
Show, (forall x. ValidityConditions -> Rep ValidityConditions x)
-> (forall x. Rep ValidityConditions x -> ValidityConditions)
-> Generic ValidityConditions
forall x. Rep ValidityConditions x -> ValidityConditions
forall x. ValidityConditions -> Rep ValidityConditions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ValidityConditions -> Rep ValidityConditions x
from :: forall x. ValidityConditions -> Rep ValidityConditions x
$cto :: forall x. Rep ValidityConditions x -> ValidityConditions
to :: forall x. Rep ValidityConditions x -> ValidityConditions
Generic, Maybe ValidityConditions
Value -> Parser [ValidityConditions]
Value -> Parser ValidityConditions
(Value -> Parser ValidityConditions)
-> (Value -> Parser [ValidityConditions])
-> Maybe ValidityConditions
-> FromJSON ValidityConditions
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ValidityConditions
parseJSON :: Value -> Parser ValidityConditions
$cparseJSONList :: Value -> Parser [ValidityConditions]
parseJSONList :: Value -> Parser [ValidityConditions]
$comittedField :: Maybe ValidityConditions
omittedField :: Maybe ValidityConditions
FromJSON, [ValidityConditions] -> Value
[ValidityConditions] -> Encoding
ValidityConditions -> Bool
ValidityConditions -> Value
ValidityConditions -> Encoding
(ValidityConditions -> Value)
-> (ValidityConditions -> Encoding)
-> ([ValidityConditions] -> Value)
-> ([ValidityConditions] -> Encoding)
-> (ValidityConditions -> Bool)
-> ToJSON ValidityConditions
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ValidityConditions -> Value
toJSON :: ValidityConditions -> Value
$ctoEncoding :: ValidityConditions -> Encoding
toEncoding :: ValidityConditions -> Encoding
$ctoJSONList :: [ValidityConditions] -> Value
toJSONList :: [ValidityConditions] -> Value
$ctoEncodingList :: [ValidityConditions] -> Encoding
toEncodingList :: [ValidityConditions] -> Encoding
$comitField :: ValidityConditions -> Bool
omitField :: ValidityConditions -> Bool
ToJSON)
data AchievementInfo = AchievementInfo
{ AchievementInfo -> Text
title :: Text
, AchievementInfo -> Maybe FlavorText
humorousElaboration :: Maybe FlavorText
, AchievementInfo -> Document Syntax
attainmentProcess :: Document Syntax
, AchievementInfo -> ExpectedEffort
effort :: ExpectedEffort
, AchievementInfo -> Bool
isObfuscated :: Bool
}
deriving (AchievementInfo -> AchievementInfo -> Bool
(AchievementInfo -> AchievementInfo -> Bool)
-> (AchievementInfo -> AchievementInfo -> Bool)
-> Eq AchievementInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AchievementInfo -> AchievementInfo -> Bool
== :: AchievementInfo -> AchievementInfo -> Bool
$c/= :: AchievementInfo -> AchievementInfo -> Bool
/= :: AchievementInfo -> AchievementInfo -> Bool
Eq, Int -> AchievementInfo -> ShowS
[AchievementInfo] -> ShowS
AchievementInfo -> String
(Int -> AchievementInfo -> ShowS)
-> (AchievementInfo -> String)
-> ([AchievementInfo] -> ShowS)
-> Show AchievementInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AchievementInfo -> ShowS
showsPrec :: Int -> AchievementInfo -> ShowS
$cshow :: AchievementInfo -> String
show :: AchievementInfo -> String
$cshowList :: [AchievementInfo] -> ShowS
showList :: [AchievementInfo] -> ShowS
Show, (forall x. AchievementInfo -> Rep AchievementInfo x)
-> (forall x. Rep AchievementInfo x -> AchievementInfo)
-> Generic AchievementInfo
forall x. Rep AchievementInfo x -> AchievementInfo
forall x. AchievementInfo -> Rep AchievementInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AchievementInfo -> Rep AchievementInfo x
from :: forall x. AchievementInfo -> Rep AchievementInfo x
$cto :: forall x. Rep AchievementInfo x -> AchievementInfo
to :: forall x. Rep AchievementInfo x -> AchievementInfo
Generic, Maybe AchievementInfo
Value -> Parser [AchievementInfo]
Value -> Parser AchievementInfo
(Value -> Parser AchievementInfo)
-> (Value -> Parser [AchievementInfo])
-> Maybe AchievementInfo
-> FromJSON AchievementInfo
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AchievementInfo
parseJSON :: Value -> Parser AchievementInfo
$cparseJSONList :: Value -> Parser [AchievementInfo]
parseJSONList :: Value -> Parser [AchievementInfo]
$comittedField :: Maybe AchievementInfo
omittedField :: Maybe AchievementInfo
FromJSON, [AchievementInfo] -> Value
[AchievementInfo] -> Encoding
AchievementInfo -> Bool
AchievementInfo -> Value
AchievementInfo -> Encoding
(AchievementInfo -> Value)
-> (AchievementInfo -> Encoding)
-> ([AchievementInfo] -> Value)
-> ([AchievementInfo] -> Encoding)
-> (AchievementInfo -> Bool)
-> ToJSON AchievementInfo
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AchievementInfo -> Value
toJSON :: AchievementInfo -> Value
$ctoEncoding :: AchievementInfo -> Encoding
toEncoding :: AchievementInfo -> Encoding
$ctoJSONList :: [AchievementInfo] -> Value
toJSONList :: [AchievementInfo] -> Value
$ctoEncodingList :: [AchievementInfo] -> Encoding
toEncodingList :: [AchievementInfo] -> Encoding
$comitField :: AchievementInfo -> Bool
omitField :: AchievementInfo -> Bool
ToJSON)
data CategorizedAchievement
= GlobalAchievement GlobalAchievement
| GameplayAchievement GameplayAchievement
deriving (CategorizedAchievement -> CategorizedAchievement -> Bool
(CategorizedAchievement -> CategorizedAchievement -> Bool)
-> (CategorizedAchievement -> CategorizedAchievement -> Bool)
-> Eq CategorizedAchievement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CategorizedAchievement -> CategorizedAchievement -> Bool
== :: CategorizedAchievement -> CategorizedAchievement -> Bool
$c/= :: CategorizedAchievement -> CategorizedAchievement -> Bool
/= :: CategorizedAchievement -> CategorizedAchievement -> Bool
Eq, Eq CategorizedAchievement
Eq CategorizedAchievement =>
(CategorizedAchievement -> CategorizedAchievement -> Ordering)
-> (CategorizedAchievement -> CategorizedAchievement -> Bool)
-> (CategorizedAchievement -> CategorizedAchievement -> Bool)
-> (CategorizedAchievement -> CategorizedAchievement -> Bool)
-> (CategorizedAchievement -> CategorizedAchievement -> Bool)
-> (CategorizedAchievement
-> CategorizedAchievement -> CategorizedAchievement)
-> (CategorizedAchievement
-> CategorizedAchievement -> CategorizedAchievement)
-> Ord CategorizedAchievement
CategorizedAchievement -> CategorizedAchievement -> Bool
CategorizedAchievement -> CategorizedAchievement -> Ordering
CategorizedAchievement
-> CategorizedAchievement -> CategorizedAchievement
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CategorizedAchievement -> CategorizedAchievement -> Ordering
compare :: CategorizedAchievement -> CategorizedAchievement -> Ordering
$c< :: CategorizedAchievement -> CategorizedAchievement -> Bool
< :: CategorizedAchievement -> CategorizedAchievement -> Bool
$c<= :: CategorizedAchievement -> CategorizedAchievement -> Bool
<= :: CategorizedAchievement -> CategorizedAchievement -> Bool
$c> :: CategorizedAchievement -> CategorizedAchievement -> Bool
> :: CategorizedAchievement -> CategorizedAchievement -> Bool
$c>= :: CategorizedAchievement -> CategorizedAchievement -> Bool
>= :: CategorizedAchievement -> CategorizedAchievement -> Bool
$cmax :: CategorizedAchievement
-> CategorizedAchievement -> CategorizedAchievement
max :: CategorizedAchievement
-> CategorizedAchievement -> CategorizedAchievement
$cmin :: CategorizedAchievement
-> CategorizedAchievement -> CategorizedAchievement
min :: CategorizedAchievement
-> CategorizedAchievement -> CategorizedAchievement
Ord, Int -> CategorizedAchievement -> ShowS
[CategorizedAchievement] -> ShowS
CategorizedAchievement -> String
(Int -> CategorizedAchievement -> ShowS)
-> (CategorizedAchievement -> String)
-> ([CategorizedAchievement] -> ShowS)
-> Show CategorizedAchievement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CategorizedAchievement -> ShowS
showsPrec :: Int -> CategorizedAchievement -> ShowS
$cshow :: CategorizedAchievement -> String
show :: CategorizedAchievement -> String
$cshowList :: [CategorizedAchievement] -> ShowS
showList :: [CategorizedAchievement] -> ShowS
Show, (forall x. CategorizedAchievement -> Rep CategorizedAchievement x)
-> (forall x.
Rep CategorizedAchievement x -> CategorizedAchievement)
-> Generic CategorizedAchievement
forall x. Rep CategorizedAchievement x -> CategorizedAchievement
forall x. CategorizedAchievement -> Rep CategorizedAchievement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CategorizedAchievement -> Rep CategorizedAchievement x
from :: forall x. CategorizedAchievement -> Rep CategorizedAchievement x
$cto :: forall x. Rep CategorizedAchievement x -> CategorizedAchievement
to :: forall x. Rep CategorizedAchievement x -> CategorizedAchievement
Generic)
categorizedAchievementJsonOptions :: Options
categorizedAchievementJsonOptions :: Options
categorizedAchievementJsonOptions =
Options
defaultOptions
{ sumEncoding = UntaggedValue
}
instance ToJSON CategorizedAchievement where
toJSON :: CategorizedAchievement -> Value
toJSON = Options -> CategorizedAchievement -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
categorizedAchievementJsonOptions
instance FromJSON CategorizedAchievement where
parseJSON :: Value -> Parser CategorizedAchievement
parseJSON = Options -> Value -> Parser CategorizedAchievement
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
categorizedAchievementJsonOptions
data GlobalAchievement
= CompletedSingleTutorial
| CompletedAllTutorials
| LookedAtAboutScreen
deriving (GlobalAchievement -> GlobalAchievement -> Bool
(GlobalAchievement -> GlobalAchievement -> Bool)
-> (GlobalAchievement -> GlobalAchievement -> Bool)
-> Eq GlobalAchievement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GlobalAchievement -> GlobalAchievement -> Bool
== :: GlobalAchievement -> GlobalAchievement -> Bool
$c/= :: GlobalAchievement -> GlobalAchievement -> Bool
/= :: GlobalAchievement -> GlobalAchievement -> Bool
Eq, Eq GlobalAchievement
Eq GlobalAchievement =>
(GlobalAchievement -> GlobalAchievement -> Ordering)
-> (GlobalAchievement -> GlobalAchievement -> Bool)
-> (GlobalAchievement -> GlobalAchievement -> Bool)
-> (GlobalAchievement -> GlobalAchievement -> Bool)
-> (GlobalAchievement -> GlobalAchievement -> Bool)
-> (GlobalAchievement -> GlobalAchievement -> GlobalAchievement)
-> (GlobalAchievement -> GlobalAchievement -> GlobalAchievement)
-> Ord GlobalAchievement
GlobalAchievement -> GlobalAchievement -> Bool
GlobalAchievement -> GlobalAchievement -> Ordering
GlobalAchievement -> GlobalAchievement -> GlobalAchievement
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GlobalAchievement -> GlobalAchievement -> Ordering
compare :: GlobalAchievement -> GlobalAchievement -> Ordering
$c< :: GlobalAchievement -> GlobalAchievement -> Bool
< :: GlobalAchievement -> GlobalAchievement -> Bool
$c<= :: GlobalAchievement -> GlobalAchievement -> Bool
<= :: GlobalAchievement -> GlobalAchievement -> Bool
$c> :: GlobalAchievement -> GlobalAchievement -> Bool
> :: GlobalAchievement -> GlobalAchievement -> Bool
$c>= :: GlobalAchievement -> GlobalAchievement -> Bool
>= :: GlobalAchievement -> GlobalAchievement -> Bool
$cmax :: GlobalAchievement -> GlobalAchievement -> GlobalAchievement
max :: GlobalAchievement -> GlobalAchievement -> GlobalAchievement
$cmin :: GlobalAchievement -> GlobalAchievement -> GlobalAchievement
min :: GlobalAchievement -> GlobalAchievement -> GlobalAchievement
Ord, Int -> GlobalAchievement -> ShowS
[GlobalAchievement] -> ShowS
GlobalAchievement -> String
(Int -> GlobalAchievement -> ShowS)
-> (GlobalAchievement -> String)
-> ([GlobalAchievement] -> ShowS)
-> Show GlobalAchievement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GlobalAchievement -> ShowS
showsPrec :: Int -> GlobalAchievement -> ShowS
$cshow :: GlobalAchievement -> String
show :: GlobalAchievement -> String
$cshowList :: [GlobalAchievement] -> ShowS
showList :: [GlobalAchievement] -> ShowS
Show, GlobalAchievement
GlobalAchievement -> GlobalAchievement -> Bounded GlobalAchievement
forall a. a -> a -> Bounded a
$cminBound :: GlobalAchievement
minBound :: GlobalAchievement
$cmaxBound :: GlobalAchievement
maxBound :: GlobalAchievement
Bounded, Int -> GlobalAchievement
GlobalAchievement -> Int
GlobalAchievement -> [GlobalAchievement]
GlobalAchievement -> GlobalAchievement
GlobalAchievement -> GlobalAchievement -> [GlobalAchievement]
GlobalAchievement
-> GlobalAchievement -> GlobalAchievement -> [GlobalAchievement]
(GlobalAchievement -> GlobalAchievement)
-> (GlobalAchievement -> GlobalAchievement)
-> (Int -> GlobalAchievement)
-> (GlobalAchievement -> Int)
-> (GlobalAchievement -> [GlobalAchievement])
-> (GlobalAchievement -> GlobalAchievement -> [GlobalAchievement])
-> (GlobalAchievement -> GlobalAchievement -> [GlobalAchievement])
-> (GlobalAchievement
-> GlobalAchievement -> GlobalAchievement -> [GlobalAchievement])
-> Enum GlobalAchievement
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: GlobalAchievement -> GlobalAchievement
succ :: GlobalAchievement -> GlobalAchievement
$cpred :: GlobalAchievement -> GlobalAchievement
pred :: GlobalAchievement -> GlobalAchievement
$ctoEnum :: Int -> GlobalAchievement
toEnum :: Int -> GlobalAchievement
$cfromEnum :: GlobalAchievement -> Int
fromEnum :: GlobalAchievement -> Int
$cenumFrom :: GlobalAchievement -> [GlobalAchievement]
enumFrom :: GlobalAchievement -> [GlobalAchievement]
$cenumFromThen :: GlobalAchievement -> GlobalAchievement -> [GlobalAchievement]
enumFromThen :: GlobalAchievement -> GlobalAchievement -> [GlobalAchievement]
$cenumFromTo :: GlobalAchievement -> GlobalAchievement -> [GlobalAchievement]
enumFromTo :: GlobalAchievement -> GlobalAchievement -> [GlobalAchievement]
$cenumFromThenTo :: GlobalAchievement
-> GlobalAchievement -> GlobalAchievement -> [GlobalAchievement]
enumFromThenTo :: GlobalAchievement
-> GlobalAchievement -> GlobalAchievement -> [GlobalAchievement]
Enum, (forall x. GlobalAchievement -> Rep GlobalAchievement x)
-> (forall x. Rep GlobalAchievement x -> GlobalAchievement)
-> Generic GlobalAchievement
forall x. Rep GlobalAchievement x -> GlobalAchievement
forall x. GlobalAchievement -> Rep GlobalAchievement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GlobalAchievement -> Rep GlobalAchievement x
from :: forall x. GlobalAchievement -> Rep GlobalAchievement x
$cto :: forall x. Rep GlobalAchievement x -> GlobalAchievement
to :: forall x. Rep GlobalAchievement x -> GlobalAchievement
Generic)
instance FromJSON GlobalAchievement
instance ToJSON GlobalAchievement
data GameplayAchievement
= CraftedBitcoin
| RobotIntoWater
| AttemptSelfDestructBase
| DestroyedBase
| LoseScenario
| GetDisoriented
| SwapSame
| GaveToSelf
| EquippedAllDevices
deriving (GameplayAchievement -> GameplayAchievement -> Bool
(GameplayAchievement -> GameplayAchievement -> Bool)
-> (GameplayAchievement -> GameplayAchievement -> Bool)
-> Eq GameplayAchievement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GameplayAchievement -> GameplayAchievement -> Bool
== :: GameplayAchievement -> GameplayAchievement -> Bool
$c/= :: GameplayAchievement -> GameplayAchievement -> Bool
/= :: GameplayAchievement -> GameplayAchievement -> Bool
Eq, Eq GameplayAchievement
Eq GameplayAchievement =>
(GameplayAchievement -> GameplayAchievement -> Ordering)
-> (GameplayAchievement -> GameplayAchievement -> Bool)
-> (GameplayAchievement -> GameplayAchievement -> Bool)
-> (GameplayAchievement -> GameplayAchievement -> Bool)
-> (GameplayAchievement -> GameplayAchievement -> Bool)
-> (GameplayAchievement
-> GameplayAchievement -> GameplayAchievement)
-> (GameplayAchievement
-> GameplayAchievement -> GameplayAchievement)
-> Ord GameplayAchievement
GameplayAchievement -> GameplayAchievement -> Bool
GameplayAchievement -> GameplayAchievement -> Ordering
GameplayAchievement -> GameplayAchievement -> GameplayAchievement
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GameplayAchievement -> GameplayAchievement -> Ordering
compare :: GameplayAchievement -> GameplayAchievement -> Ordering
$c< :: GameplayAchievement -> GameplayAchievement -> Bool
< :: GameplayAchievement -> GameplayAchievement -> Bool
$c<= :: GameplayAchievement -> GameplayAchievement -> Bool
<= :: GameplayAchievement -> GameplayAchievement -> Bool
$c> :: GameplayAchievement -> GameplayAchievement -> Bool
> :: GameplayAchievement -> GameplayAchievement -> Bool
$c>= :: GameplayAchievement -> GameplayAchievement -> Bool
>= :: GameplayAchievement -> GameplayAchievement -> Bool
$cmax :: GameplayAchievement -> GameplayAchievement -> GameplayAchievement
max :: GameplayAchievement -> GameplayAchievement -> GameplayAchievement
$cmin :: GameplayAchievement -> GameplayAchievement -> GameplayAchievement
min :: GameplayAchievement -> GameplayAchievement -> GameplayAchievement
Ord, Int -> GameplayAchievement -> ShowS
[GameplayAchievement] -> ShowS
GameplayAchievement -> String
(Int -> GameplayAchievement -> ShowS)
-> (GameplayAchievement -> String)
-> ([GameplayAchievement] -> ShowS)
-> Show GameplayAchievement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GameplayAchievement -> ShowS
showsPrec :: Int -> GameplayAchievement -> ShowS
$cshow :: GameplayAchievement -> String
show :: GameplayAchievement -> String
$cshowList :: [GameplayAchievement] -> ShowS
showList :: [GameplayAchievement] -> ShowS
Show, GameplayAchievement
GameplayAchievement
-> GameplayAchievement -> Bounded GameplayAchievement
forall a. a -> a -> Bounded a
$cminBound :: GameplayAchievement
minBound :: GameplayAchievement
$cmaxBound :: GameplayAchievement
maxBound :: GameplayAchievement
Bounded, Int -> GameplayAchievement
GameplayAchievement -> Int
GameplayAchievement -> [GameplayAchievement]
GameplayAchievement -> GameplayAchievement
GameplayAchievement -> GameplayAchievement -> [GameplayAchievement]
GameplayAchievement
-> GameplayAchievement
-> GameplayAchievement
-> [GameplayAchievement]
(GameplayAchievement -> GameplayAchievement)
-> (GameplayAchievement -> GameplayAchievement)
-> (Int -> GameplayAchievement)
-> (GameplayAchievement -> Int)
-> (GameplayAchievement -> [GameplayAchievement])
-> (GameplayAchievement
-> GameplayAchievement -> [GameplayAchievement])
-> (GameplayAchievement
-> GameplayAchievement -> [GameplayAchievement])
-> (GameplayAchievement
-> GameplayAchievement
-> GameplayAchievement
-> [GameplayAchievement])
-> Enum GameplayAchievement
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: GameplayAchievement -> GameplayAchievement
succ :: GameplayAchievement -> GameplayAchievement
$cpred :: GameplayAchievement -> GameplayAchievement
pred :: GameplayAchievement -> GameplayAchievement
$ctoEnum :: Int -> GameplayAchievement
toEnum :: Int -> GameplayAchievement
$cfromEnum :: GameplayAchievement -> Int
fromEnum :: GameplayAchievement -> Int
$cenumFrom :: GameplayAchievement -> [GameplayAchievement]
enumFrom :: GameplayAchievement -> [GameplayAchievement]
$cenumFromThen :: GameplayAchievement -> GameplayAchievement -> [GameplayAchievement]
enumFromThen :: GameplayAchievement -> GameplayAchievement -> [GameplayAchievement]
$cenumFromTo :: GameplayAchievement -> GameplayAchievement -> [GameplayAchievement]
enumFromTo :: GameplayAchievement -> GameplayAchievement -> [GameplayAchievement]
$cenumFromThenTo :: GameplayAchievement
-> GameplayAchievement
-> GameplayAchievement
-> [GameplayAchievement]
enumFromThenTo :: GameplayAchievement
-> GameplayAchievement
-> GameplayAchievement
-> [GameplayAchievement]
Enum, (forall x. GameplayAchievement -> Rep GameplayAchievement x)
-> (forall x. Rep GameplayAchievement x -> GameplayAchievement)
-> Generic GameplayAchievement
forall x. Rep GameplayAchievement x -> GameplayAchievement
forall x. GameplayAchievement -> Rep GameplayAchievement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GameplayAchievement -> Rep GameplayAchievement x
from :: forall x. GameplayAchievement -> Rep GameplayAchievement x
$cto :: forall x. Rep GameplayAchievement x -> GameplayAchievement
to :: forall x. Rep GameplayAchievement x -> GameplayAchievement
Generic)
instance FromJSON GameplayAchievement
instance ToJSON GameplayAchievement
listAchievements :: [CategorizedAchievement]
listAchievements :: [CategorizedAchievement]
listAchievements =
(GlobalAchievement -> CategorizedAchievement)
-> [GlobalAchievement] -> [CategorizedAchievement]
forall a b. (a -> b) -> [a] -> [b]
map GlobalAchievement -> CategorizedAchievement
GlobalAchievement [GlobalAchievement]
forall a. (Enum a, Bounded a) => [a]
enumerate
[CategorizedAchievement]
-> [CategorizedAchievement] -> [CategorizedAchievement]
forall a. Semigroup a => a -> a -> a
<> (GameplayAchievement -> CategorizedAchievement)
-> [GameplayAchievement] -> [CategorizedAchievement]
forall a b. (a -> b) -> [a] -> [b]
map GameplayAchievement -> CategorizedAchievement
GameplayAchievement [GameplayAchievement]
forall a. (Enum a, Bounded a) => [a]
enumerate