| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Card
Contents
Synopsis
- data Team
- ppTeam :: Team -> String
- allTeams :: [Team]
- data Phase
- type family ItemType (p :: Phase) where ...
- type family ManaType (p :: Phase) where ...
- type family OffsetType (p :: Phase) where ...
- type family SkillType (p :: Phase) where ...
- type family TeamsType (p :: Phase) where ...
- type family MaybeTextType (p :: Phase) where ...
- type family TextType (p :: Phase) where ...
- type family TileType (p :: Phase) where ...
- type family TransientType (p :: Phase) where ...
- type Forall (c :: Type -> Constraint) (p :: Phase) = (c (ItemType p), c (ManaType p), c (MaybeTextType p), c (OffsetType p), c (SkillType p), c (TeamsType p), c (TextType p), c (TileType p), c (TransientType p))
-
data CreatureKind
- = Abomination
- | Archer
- | Assassin
- | Bear
- | Beholder
- | Bird
- | Captain
- | Church
- | Daemon
- | Defender
- | Falcon
- | Falconer
- | General
- | Ghost
- | Guardian
- | King
- | Knight
- | Necromancer
- | Minotaur
- | Mummy
- | Ogre
- | Priest
- | Ranger
- | Skeleton
- | Shade
- | Spearman
- | Specter
- | Squire
- | Swordsman
- | Trebuchet
- | Tree
- | Troll
- | Vampire
- | Veteran
- | Warrior
- | Worm
- allCreatureKinds :: [CreatureKind]
-
data CreatureID = CreatureID {
- creatureKind :: CreatureKind
- team :: Team
- isSkeleton :: CreatureID -> Bool
-
data Creature (p :: Phase) = Creature {
- creatureId :: CreatureID
- hp :: Nat
- attack :: Damage
- items :: [ItemType p]
- moral :: Int
- skills :: [SkillType p]
- transient :: TransientType p
- class Itemizable a where
-
data Neutral
- = Health
- | HuntingHorn
- | InfernalHaste
- | Life
- | Pandemonium
- | Plague
- | StrengthPot
- allNeutrals :: [Neutral]
-
data NeutralObject (p :: Phase) = NeutralObject {
- neutral :: Neutral
- title :: TextType p
- titleSzOffset :: OffsetType p
-
data Item
- = AxeOfRage
- | BannerFeather
- | BowOfGaia
- | BowOfStrength
- | CloakOfGaia
- | Crown
- | CrushingMace
- | FlailOfTheDamned
- | SkBanner
- | SpikyMace
- | SwordOfBlood
- | SwordOfMight
- data Requirement
- requirement :: Item -> Requirement
- allItems :: [Item]
-
data ItemObject (p :: Phase) = ItemObject {
- item :: Item
- title :: TextType p
- titleSzOffset :: OffsetType p
- mkCoreItemObject :: Item -> ItemObject Core
-
data CardCommon (p :: Phase) = CardCommon {
- mana :: ManaType p
- text :: MaybeTextType p
- textSzOffset :: OffsetType p
- tile :: TileType p
- mkCoreCardCommon :: CardCommon Core
-
data Card (p :: Phase)
- = CreatureCard (CardCommon p) (Creature p)
- | NeutralCard (CardCommon p) (NeutralObject p)
- | ItemCard (CardCommon p) (ItemObject p)
- toCommon :: Card p -> CardCommon p
- class Unlift t where
- toCreature :: Card p -> Maybe (Creature p)
- data ID
- toIdentifier :: Itemizable (Creature p) => Card p -> ID
- identToId :: ID -> Maybe CreatureID
- groupCards :: Itemizable (Creature p) => [Card p] -> Map ID [Card p]
- rawTeamDeck :: [Card UI] -> Team -> [Maybe (Card Core)]
- teamDeck :: [Card UI] -> Team -> [Card Core]
- data CardTargetKind
- data TargetType
- targetType :: ID -> TargetType
-
class Has a b where
- has :: a -> b -> Bool
- doesNotHave :: a -> b -> Bool
-
class To a b where
- to :: a -> b
- class Key a where
Documentation
Instances
| Bounded Team # | |
| Enum Team # | |
| Eq Team # | |
| Ord Team # | |
| Show Team # | |
| Generic Team # | |
| FromJSON Team # | |
| type Rep Team # | |
Defined in Card
type Rep Team = D1 (MetaData "Team" "Card" "main" False) ((C1 (MetaCons "Beastmen" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Evil" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Human" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Sylvan" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Undead" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ZKnights" PrefixI False) (U1 :: Type -> Type)))) | |
Constructors
| Core | Phase for data in core algorithms ( |
| UI | Phase for data in UI algorithms: contains more data related to drawing cards. Data in this phase is _formal_, i.e. hitpoints are the maximum (pristine) hitpoints, attack is formal attack (before maluses or bonuses), etc. |
type family OffsetType (p :: Phase) where ... #
Equations
| OffsetType UI = Int | |
| OffsetType Core = () |
type family MaybeTextType (p :: Phase) where ... #
Equations
| MaybeTextType UI = Maybe String | |
| MaybeTextType Core = () |
type family TransientType (p :: Phase) where ... #
Equations
| TransientType UI = () | |
| TransientType Core = Bool |
type Forall (c :: Type -> Constraint) (p :: Phase) = (c (ItemType p), c (ManaType p), c (MaybeTextType p), c (OffsetType p), c (SkillType p), c (TeamsType p), c (TextType p), c (TileType p), c (TransientType p)) #
data CreatureKind #
All kinds of creature
Constructors
Instances
data CreatureID #
The identifier of a creature. Not all identifiers are actually mapped
by Model.
Constructors
| CreatureID | |
Fields
| |
Instances
isSkeleton :: CreatureID -> Bool #
Constructors
| Creature | |
Fields
| |
Instances
class Itemizable a where #
Constructors
| Health | |
| HuntingHorn | |
| InfernalHaste | |
| Life | |
| Pandemonium | |
| Plague | |
| StrengthPot |
Instances
| Bounded Neutral # | |
| Enum Neutral # | |
| Eq Neutral # | |
| Ord Neutral # | |
| Show Neutral # | |
| Generic Neutral # | |
| FromJSON Neutral # | |
| Key Neutral # | |
| type Rep Neutral # | |
Defined in Card
type Rep Neutral = D1 (MetaData "Neutral" "Card" "main" False) ((C1 (MetaCons "Health" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HuntingHorn" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "InfernalHaste" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Life" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Pandemonium" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Plague" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StrengthPot" PrefixI False) (U1 :: Type -> Type)))) | |
allNeutrals :: [Neutral] #
data NeutralObject (p :: Phase) #
Constructors
| NeutralObject | |
Fields
| |
Instances
Constructors
| AxeOfRage | |
| BannerFeather | |
| BowOfGaia | |
| BowOfStrength | |
| CloakOfGaia | |
| Crown | |
| CrushingMace | |
| FlailOfTheDamned | |
| SkBanner | |
| SpikyMace | |
| SwordOfBlood | |
| SwordOfMight |
Instances
data Requirement #
Requirements for being able to have some item
requirement :: Item -> Requirement #
Requirements for being able to carry an item. Could be encoded in json, but I'm afraid complex requirements would be tartelette to implement.
data ItemObject (p :: Phase) #
Constructors
| ItemObject | |
Fields
| |
Instances
mkCoreItemObject :: Item -> ItemObject Core #
data CardCommon (p :: Phase) #
Data that is used by all three kind of cards
Constructors
| CardCommon | |
Fields
| |
Instances
Constructors
| CreatureCard (CardCommon p) (Creature p) | |
| NeutralCard (CardCommon p) (NeutralObject p) | |
| ItemCard (CardCommon p) (ItemObject p) |
Instances
toCommon :: Card p -> CardCommon p #
Instances
| Unlift Card # | |
| Unlift ItemObject # | |
Defined in Card Methods unlift :: ItemObject UI -> ItemObject Core # | |
| Unlift NeutralObject # | |
Defined in Card Methods unlift :: NeutralObject UI -> NeutralObject Core # | |
| Unlift Creature # | |
toCreature :: Card p -> Maybe (Creature p) #
The minimal identifier of a card. See Model to obtain
| a full-fledged card from that.
Instances
| Eq ID # | |
| Ord ID # | |
| Show ID # | |
| Generic ID # | |
| Key ID # | |
| type Rep ID # | |
Defined in Card
type Rep ID = D1 (MetaData "ID" "Card" "main" False) (C1 (MetaCons "IDC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CreatureID) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Item])) :+: (C1 (MetaCons "IDI" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Item)) :+: C1 (MetaCons "IDN" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Neutral)))) | |
toIdentifier :: Itemizable (Creature p) => Card p -> ID #
identToId :: ID -> Maybe CreatureID #
groupCards :: Itemizable (Creature p) => [Card p] -> Map ID [Card p] #
data CardTargetKind #
Instances
| Eq CardTargetKind # | |
Defined in Card Methods (==) :: CardTargetKind -> CardTargetKind -> Bool # (/=) :: CardTargetKind -> CardTargetKind -> Bool # | |
| Show CardTargetKind # | |
Defined in Card Methods showsPrec :: Int -> CardTargetKind -> ShowS # show :: CardTargetKind -> String # showList :: [CardTargetKind] -> ShowS # | |
data TargetType #
Constructors
| CardTargetType CardTargetKind | Target is a single card |
| PlayerTargetType | Target is an entire part of the bard |
Instances
| Eq TargetType # | |
Defined in Card | |
| Show TargetType # | |
Defined in Card Methods showsPrec :: Int -> TargetType -> ShowS # show :: TargetType -> String # showList :: [TargetType] -> ShowS # | |
targetType :: ID -> TargetType #
The kind of TargetType that a ID aims
Classes and instances
Class for runtime values having some quality. This is akin to a strongly typed entity system.
Minimal complete definition
Class from which some value can be obtained