Skip to content
This repository has been archived by the owner on Dec 31, 2023. It is now read-only.

archive567/sap

Folders and files

NameName
Last commit message
Last commit date

Latest commit

 

History

9 Commits
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 

Repository files navigation

ToDo SAP R&D

  • [X] applying effects
    • [X] StartOfBattle effects
    • [X] Battle effect list
  • [ ] Level 1 / Tier 1 simulation
    • [ ] beaver buy
    • [ ] horse summoned modiftstats on buy
    • [ ] duck, otter, pig sale

sap

https://img.shields.io/hackage/v/sap.svg https://github.com/tonyday567/sap/workflows/haskell-ci/badge.svg

super auto pet

https://superauto.pet/

https://github.com/bencoveney/super-auto-pets-db

pragmas and imports

:r
:set prompt "> "
:set -Wno-type-defaults
:set -Wno-name-shadowing
:set -XOverloadedStrings
:set -XOverloadedLabels
:set -Wno-incomplete-uni-patterns
import Prelude hiding (lookup)
import Sap
import Data.Aeson
import qualified Data.ByteString.Lazy as B
import qualified Data.List as List
import qualified Data.Map.Strict as Map
import GHC.Generics
import qualified Data.Aeson.KeyMap as A
import Data.Aeson.Types hiding (Key)
import qualified Data.Text as Text
import qualified Data.Vector as V
import System.Random
import Control.Monad.State.Lazy
import Optics.Extra
putStrLn "ok"

SapState

s <- sapState StandardPack
s' = flip evalState s
prettyShow s startBoard

SapState checks

length $ foods s
length $ pets s
length $ statuses s
length $ turns s

adhoc error checking

head [e|(Error e) <- (fromJSON :: Value -> Result Pet) . snd <$> toList ps]
head $ snd <$> toList ss

initial JSON data exploration

json file as Value

(Just (Object v)) <- decode <$> B.readFile "other/sap.json" :: IO (Maybe Value)
(Just (Object fs)) = lookup "foods" v
(Just (Object ps)) = lookup "pets" v
(Just (Object ss)) = lookup "statuses" v
(Just (Object ts)) = lookup "turns" v
length <$> [fs,ps,ss,ts]

high level anaysis

keys v
take 200 $ show v

main keys

So there are 4 main data sections.

food

A quick peek at each section:

(Just (Object fs)) = lookup "foods" v
keys fs
(Just (Object fa)) = Data.Aeson.KeyMap.lookup "food-apple" fs
keys fa
Data.Aeson.KeyMap.lookup "ability" fa

pet

(Just (Object ps)) = lookup "pets" v
keys ps
(Just (Object pa)) = Data.Aeson.KeyMap.lookup "pet-ant" ps
keys pa
Data.Aeson.KeyMap.lookup "id" pa

status

(Just (Object ss)) = lookup "statuses" v
keys ss
Data.Aeson.KeyMap.lookup "status-bone-attack" ss
(Just (Object sba)) = Data.Aeson.KeyMap.lookup "status-bone-attack" ss
keys sba
keys . snd <$> [(k,m) | (k, Object m) <- toList ss]

turns

(Just (Object ts)) = lookup "turns" v
keys ts
Data.Aeson.KeyMap.lookup "turn-11" ts
keys . snd <$> [(k,m) | (k, Object m) <- toList ts]

key analysis

The food keys:

List.nub $ mconcat $ snd <$> [(k, keys m) | (k, Object m) <- toList fs]

The pet keys:

List.nub $ mconcat $ snd <$> [(k, keys m) | (k, Object m) <- toList ps]

The status keys:

List.nub $ mconcat $ snd <$> [(k, keys m) | (k, Object m) <- toList ss]

The turn keys:

List.nub $ mconcat $ snd <$> [(k, keys m) | (k, Object m) <- toList ts]

deeper dives

id

Are these exactly the same across the different sections?

foodspetsstatusesturns
[(k, Data.Aeson.KeyMap.lookup "id" m) | (k, Object m) <- toList fs]

It looks like id is redundant:

(\x -> Prelude.filter (not . (uncurry (==))) [(show k,show i)| (k,Just (String i)) <- [(k, Data.Aeson.KeyMap.lookup "id" m) | (k, Object m) <- toList x]]) <$> [fs, ps, ss, ts]

Not the advantages of working with generic (or weakly-typed data). If we had already undertaken a laborious specification of the type of each section data, we couldn’t combine them like this.

image

image is the emoji

putStrLn $ Text.unpack $ mconcat $ fmap snd $ [(k,u) |(k,(Just (String u))) <- [(k,Data.Aeson.KeyMap.lookup "unicodeCodePoint" m') |(k,Just (Object m')) <- [(k, Data.Aeson.KeyMap.lookup "image" m) | (k, Object m) <- toList fs]]]
putStrLn "\128028"
putStrLn $ Text.unpack $ mconcat $ fmap snd $ [(k,u) |(k,(Just (String u))) <- [(k,Data.Aeson.KeyMap.lookup "unicodeCodePoint" m') |(k,Just (Object m')) <- [(k, Data.Aeson.KeyMap.lookup "image" m) | (k, Object m) <- toList ps]]]
putStrLn $ Text.unpack $ mconcat $ fmap snd $ [(k,u) |(k,(Just (String u))) <- [(k,Data.Aeson.KeyMap.lookup "unicodeCodePoint" m') |(k,Just (Object m')) <- [(k, Data.Aeson.KeyMap.lookup "image" m) | (k, Object m) <- toList ss]]]

status unicodes are the same as the equivalent foods.

name

name looks like a label, and looks consistent across sections.

[(k, Data.Aeson.KeyMap.lookup "name" m) | (k, Object m) <- toList fs]
[(k, Data.Aeson.KeyMap.lookup "name" m) | (k, Object m) <- toList ps]
[(k, Data.Aeson.KeyMap.lookup "name" m) | (k, Object m) <- toList ss]
[(k, Data.Aeson.KeyMap.lookup "name" m) | (k, Object m) <- toList ts]

ability (and sub-objects)

food ability
take 1 $ fmap (snd) [(k, m') | (k,Just (Object m')) <- [(k,Data.Aeson.KeyMap.lookup "ability" m)| (k, Object m) <- toList fs]]

description is Text

effect has three different variations of key combinations:

List.nub $ keys . snd <$>  [(k,m'') | (k,Just (Object m'')) <- [(k, Data.Aeson.KeyMap.lookup "effect" m') | (k,Just (Object m')) <- [(k,Data.Aeson.KeyMap.lookup "ability" m)| (k, Object m) <- toList fs]]]
[(k,Data.Aeson.KeyMap.lookup "kind" m'') | (k,Just (Object m'')) <- [(k, Data.Aeson.KeyMap.lookup "effect" m') | (k,Just (Object m')) <- [(k,Data.Aeson.KeyMap.lookup "ability" m)| (k, Object m) <- toList fs]]]

kind is always a string

[(k,Data.Aeson.KeyMap.lookup "target" m'') | (k,Just (Object m'')) <- [(k, Data.Aeson.KeyMap.lookup "effect" m') | (k,Just (Object m')) <- [(k,Data.Aeson.KeyMap.lookup "ability" m)| (k, Object m) <- toList fs]]]

target is a kind and sometimes an n, which is a number.

status, to and amount are; a simple strings, 1 key objects, and a number.

[(k,Data.Aeson.KeyMap.lookup "amount" m'') | (k,Just (Object m'')) <- [(k, Data.Aeson.KeyMap.lookup "effect" m') | (k,Just (Object m')) <- [(k,Data.Aeson.KeyMap.lookup "ability" m)| (k, Object m) <- toList fs]]]
pet ability
abilities = mconcat $ (\z -> fmap (snd) [(k, m') | (k,Just (Object m')) <- [(k,Data.Aeson.KeyMap.lookup z m)| (k, Object m) <- toList ps]]) <$> ["level1Ability", "level2Ability", "level3Ability"]
:t abilities
import qualified Data.List as List
List.nub $ keys <$> abilities
List.sort $ List.nub [s|(Just (String s)) <- lookup "trigger" <$> abilities]

effect has three different variations of key combinations:

petEffects = [m'' | Just (Object m'') <- Data.Aeson.KeyMap.lookup "effect" <$> abilities]
:t petEffects

pet effects have a lot of variation:

List.nub $ keys <$> petEffects
peKeys = List.nub $ mconcat $ keys <$> petEffects
peKeys

attackAmount sometimes a String (?)

[x | (Just x) <- Data.Aeson.KeyMap.lookup "attackAmount" <$> petEffects]

healthAmount always a number

[x | (Just x) <- Data.Aeson.KeyMap.lookup "healthAmount" <$> petEffects]

kind a String and always there.

length [x | (Just x) <- Data.Aeson.KeyMap.lookup "kind" <$> petEffects]

target is strings and bools

take 4 $ [x | (Just (Object x)) <- Data.Aeson.KeyMap.lookup "target" <$> petEffects]

amount is sometimes an object: attackDamagePercent is the only key and is a number also.

[x | (Just x) <- Data.Aeson.KeyMap.lookup "amount" <$> petEffects]
[x | (Just x) <- Data.Aeson.KeyMap.lookup "status" <$> petEffects]
[x | (Just x) <- Data.Aeson.KeyMap.lookup "to" <$> petEffects]
[x | (Just x) <- Data.Aeson.KeyMap.lookup "copyAttack" <$> petEffects]
(\s -> [x | (Just x) <- Data.Aeson.KeyMap.lookup s <$> petEffects]) <$> ["from"]

pet effect effects is an Array all of which are length 2, but no new keys are there.

effectss = [x | (Just (Array x)) <- Data.Aeson.KeyMap.lookup "effects" <$> petEffects]
:t effectss
length <$> V.toList <$> effectss
keys <$> [m | (Object m) <- mconcat $ V.toList <$> effectss]
status ability
take 1 $ [m' | (Just (Object m')) <- [Data.Aeson.KeyMap.lookup "ability" m| (_,Object m) <- toList ss]]
List.nub $ keys <$> [m' | (Just (Object m')) <- [Data.Aeson.KeyMap.lookup "ability" m | (_,Object m) <- toList ss]]
[x | (Just (Object x)) <- [Data.Aeson.KeyMap.lookup "effect" m' | (Just (Object m')) <- [Data.Aeson.KeyMap.lookup "ability" m | (_,Object m) <- toList ss]]]

effect

List.nub $ keys <$> [x | (Just (Object x)) <- [Data.Aeson.KeyMap.lookup "effect" m' | (Just (Object m')) <- [Data.Aeson.KeyMap.lookup "ability" m | (_,Object m) <- toList ss]]]
List.nub $ keys <$> [x | (Just (Object x)) <- [Data.Aeson.KeyMap.lookup "effect" m' | (Just (Object m')) <- [Data.Aeson.KeyMap.lookup "ability" m | (_,Object m) <- toList fs]]]
List.nub $ mconcat $ (\x -> List.nub $ keys <$> [x | (Just (Object x)) <- [Data.Aeson.KeyMap.lookup "effect" m' | (Just (Object m')) <- [Data.Aeson.KeyMap.lookup x m | (_,Object m) <- toList ps]]]) <$> ["level1Ability", "level2Ability", "level3Ability"]

all of the effects

effects = mconcat $ mconcat $ (\(mega,os) -> (\o -> [(k,x) | (k,Just (Object x)) <- [(k,lookup "effect" m') | (k, Just (Object m')) <- [(k, lookup o m) | (k,Object m) <- Data.Aeson.KeyMap.toList mega]]]) <$> os) <$> [(ss,["ability"]), (ps,["level1Ability", "level2Ability", "level3Ability"]), (fs, ["ability"])]
length effects
[() | Nothing <- lookup "kind" . snd <$> effects]
mk = Data.Foldable.foldl' (\b (k,s,ks) -> Map.unionWith (<>) b (Map.singleton (k,ks) s)) Map.empty [(k,s, ks) | (k, Just (String s), ks) <- (\x -> (fst x, lookup "kind" . snd $ x, keys . snd $ x)) <$> effects]
Map.size mk
Prelude.filter ((== 2).length) $ List.groupBy (\a b -> fst a == fst b) (Map.keys mk)

List of effect keys

mk' = Data.Foldable.foldl' (\b (k,s,ks) -> Map.unionWith (<>) b (Map.singleton (s,ks) [k])) Map.empty [(k,s, ks) | (k, Just (String s), ks) <- (\x -> (fst x, lookup "kind" . snd $ x, keys . snd $ x)) <$> effects]
Map.keys mk'
Prelude.filter ((== 2).length) $ List.groupBy (\a b -> fst a == fst b) (Map.keys mk')
List.sort $ List.nub [s|(Just (String s)) <- [(lookup "kind" o) | (Object o) <- [x|(Just x) <- lookup "target" . snd <$> effects]]]
Prelude.filter ((== Just (String "DealDamage")) . lookup "kind" . snd) effects

probabilities

food probs
fp = [(k, Data.Aeson.KeyMap.lookup "probabilities" m) | (k, Object m) <- toList fs]
:t fp
[k | (k,Nothing) <- fp ]
length . snd <$> [(k,V.toList v) | (k,Just (Array v)) <- fp ]
:t mconcat $ snd <$> [(k,V.toList v) | (k,Just (Array v)) <- fp ]
List.nub $ keys <$> [m | (Object m) <- mconcat $ snd <$> [(k,V.toList v) | (k,Just (Array v)) <- fp ]]
take 3 [m | (Object m) <- mconcat $ snd <$> [(k,V.toList v) | (k,Just (Array v)) <- fp ]]
pet probs
pp = [(k, Data.Aeson.KeyMap.lookup "probabilities" m) | (k, Object m) <- toList ps]
:t pp
[k | (k,Nothing) <- pp ]
length . snd <$> [(k,V.toList v) | (k,Just (Array v)) <- pp ]
:t mconcat $ snd <$> [(k,V.toList v) | (k,Just (Array v)) <- pp ]
List.nub $ keys <$> [m | (Object m) <- mconcat $ snd <$> [(k,V.toList v) | (k,Just (Array v)) <- pp ]]
take 3 [m | (Object m) <- mconcat $ snd <$> [(k,V.toList v) | (k,Just (Array v)) <- pp ]]

cost | notes | packs | tier |

(\x -> [(k, Data.Aeson.KeyMap.lookup x m) | (k, Object m) <- toList fs]) <$> ["cost"]
(\x -> [(k, Data.Aeson.KeyMap.lookup x m) | (k, Object m) <- toList fs]) <$> ["notes"]
(\x -> [(k, Data.Aeson.KeyMap.lookup x m) | (k, Object m) <- toList fs]) <$> ["packs"]
(\x -> [(k, Data.Aeson.KeyMap.lookup x m) | (k, Object m) <- toList fs]) <$> ["tier"]

FromJSON development

I would guess that there are enough quirks that toJsons are impractical: the json data being used as the reference point is better thought of as immutable.

turns

(Just (Object ts)) = Data.Aeson.KeyMap.lookup "turns" v1
keys ts
Data.Aeson.KeyMap.lookup "turn-11" ts
length ts
length [(k,m) | (k, Object m) <- toList ts]
:t [(k,m) | (k, Object m) <- toList ts]
turns = [t| (Right t) <- (fmap (parseEither parseJSON . snd) $ toList ts) :: [Either String Turn]]
length turns

image

putStrLn $ Text.unpack $ mconcat $ fmap snd $ [(k,u) |(k,(Just (String u))) <- [(k,Data.Aeson.KeyMap.lookup "unicodeCodePoint" m') |(k,Just (Object m')) <- [(k, Data.Aeson.KeyMap.lookup "image" m) | (k, Object m) <- toList fs]]]
putStrLn $ Text.unpack $ mconcat $ fmap snd $ [(k,u) |(k,(Just (String u))) <- [(k,Data.Aeson.KeyMap.lookup "unicodeCodePoint" m') |(k,Just (Object m')) <- [(k, Data.Aeson.KeyMap.lookup "image" m) | (k, Object m) <- toList fs]]]
fromJSON . snd <$> toList fs :: [Result Emoji]

effect

effects = mconcat $ mconcat $ (\(mega,os) -> (\o -> [(k,x) | (k,Just (Object x)) <- [(k,lookup "effect" m') | (k, Just (Object m')) <- [(k, lookup o m) | (k,Object m) <- Data.Aeson.KeyMap.toList mega]]]) <$> os) <$> [(ss,["ability"]), (ps,["level1Ability", "level2Ability", "level3Ability"]), (fs, ["ability"])]
length effects
import Data.Bifunctor
import Data.Maybe
bad = fst <$> Prelude.filter (isNothing . snd) (second (parseMaybe parseJSON . Object) <$> effects :: [(Key, Maybe Effect)])
bad
import Data.Bifunctor
import Data.Maybe
bad' = Prelude.filter (isNothing . (parseMaybe parseJSON :: Value -> Maybe Effect) . Object . snd) effects
bad'
bado = (\k -> (Map.!) (Map.fromList effects) k) <$> bad
fromJSON . Object <$> bado :: [Result Effect]
bado

ability

allAbilities = mconcat $ mconcat $ (\(mega,os) -> (\o -> [(k,m') | (k, Just (Object m')) <- [(k, lookup o m) | (k,Object m) <- Data.Aeson.KeyMap.toList mega]]) <$> os) <$> [(ss,["ability"]), (ps,["level1Ability", "level2Ability", "level3Ability"]), (fs, ["ability"])]
length allAbilities
import Data.Bifunctor
import Data.Maybe
bad = Prelude.filter (isNothing . (parseMaybe parseJSON :: Value -> Maybe Ability) . Object . snd) allAbilities
length bad
take 10 bad
import Data.Bifunctor
import Data.Maybe
bad = Prelude.filter (isNothing . (parseMaybe parseJSON :: Value -> Maybe Ability) . Object . snd) allAbilities
length bad
take 10 bad

probabilities

pp = [(k, Data.Aeson.KeyMap.lookup "probabilities" m) | (k, Object m) <- toList ps]
length pp
[k| (k,Nothing) <- pp]
[x|(Error x) <- (fromJSON :: Value -> Result Probability) . Object <$> (mconcat $ (\x' -> [o|(Object o) <- x']) . V.toList <$> [x|(_,Just (Array x)) <- pp])]

food probs

fp = [(k, Data.Aeson.KeyMap.lookup "probabilities" m) | (k, Object m) <- toList fs]
length fp
[x|(Error x) <- (fromJSON :: Value -> Result Probability) . Object <$> (mconcat $ (\x' -> [o|(Object o) <- x']) . V.toList <$> [x|(_,Just (Array x)) <- fp])]

pet

bad = Prelude.filter (isNothing . (parseMaybe parseJSON :: Value -> Maybe Pet) . snd) (toList ps)
take 2 bad
bad = [x|(Error x) <- ((fromJSON :: Value -> Result Pet) . snd) <$> (toList ps)]
bad

food

bad = Prelude.filter (isNothing . (parseMaybe parseJSON :: Value -> Maybe Food) . snd) (toList fs)
take 2 bad
bad = [x|(Error x) <- ((fromJSON :: Value -> Result Food) . snd) <$> (toList fs)]
bad

code snippets

probabilities

pets that don’t have probabilities

[k| (k, Nothing) <- second petProbabilities <$> pets s]

Tier 1 pets from the StandardPack

kp = Prelude.filter ((\x -> (List.elem StandardPack . packs $ x) && (isJust . petProbabilities $ x) && (TierN 1 == tier x)) . snd) $ Map.toList (pets s)
length kp
putStrLn $ mconcat $ char . petEmoji . snd <$> kp
sum $ snd <$> (second (fromJust . standardPack . perSlot . head . fromJust . fmap (Prelude.filter ((=="turn-1") . turn)) . petProbabilities) <$> kp)

zoom

:set -XOverloadedLabels
:t (\xs -> zoom #gen (rva xs)) :: [(Key, Double)] -> State SapState Key
:t \t -> zoom #gen ((fmap cumProbs . foodSlotProbs $ t))
:t \t -> (fmap cumProbs . foodSlotProbs) t

a tier-1 initial roll

s' = flip evalState s
s' $ startBoard
view (#foodAbility % #effect) $ (Map.!) (foods s) "food-apple"

recruitPetAlways decomposition

tl = [["pet-ant","pet-beaver","pet-cricket","pet-duck","pet-fish","pet-horse","pet-mosquito","pet-otter","pet-pig"]]
flip evalState s (recruitPet tl `mPlug` (recruitPet tl `mPlug` (recruitPet tl =<< startBoard)))
flip evalState s $ midRoll `mPlug` (recruitPet tl `mPlug` (recruitPet tl `mPlug` (recruitPet tl =<< startBoard)))
:set -XOverloadedLabels
tl = [["pet-ant","pet-beaver","pet-cricket","pet-duck","pet-fish","pet-horse","pet-mosquito","pet-otter","pet-pig"]]
b2 = flip evalState s (replicateM 2 $ recruitPetAlways tl =<< startBoard)
fmap (view #deck) <$> b2

Initial Battle

Just Tier 1, Level 1 Ability

tl = [["pet-ant","pet-beaver","pet-cricket","pet-duck","pet-fish","pet-horse","pet-mosquito","pet-otter","pet-pig"]]
bAlways = fromMaybe (error "wtf") <$> (recruitPetAlways tl =<< startBoard)
s <- sapState StandardPack
b = flip evalState s $ mkBattle <$> bAlways <*> bAlways
prettyShow s (pure b)

Tier 1, Level 1 Abilities

as = [(k,a)|(k,Just a ) <- Map.toList $ fmap (\x -> view #level1Ability x) $ Map.filter (\x -> (List.elem StandardPack . packs $ x) && (isJust . petProbabilities $ x) && (TierN 1 == tier x)) (pets s)]
length as
as

StartOfBattle effects

s <- sapState StandardPack
s' = flip evalState s
b = s' $ mkBattle <$> bAlways <*> bAlways
prettyShow s (pure b)
s' (bEffects StartOfBattle b)
s' (bEffects StartOfBattle b)

loop debug test

tl = [["pet-ant","pet-beaver","pet-cricket","pet-duck","pet-fish","pet-horse","pet-mosquito","pet-otter","pet-pig"]] :: [[Sap.Key PetKey]]
bAlways = fromMaybe (error "wtf") <$> (recruitPetAlways tl =<< startBoard)
s <- sapState StandardPack
b = flip evalState s $ mkBattle <$> bAlways <*> bAlways
s' = flip evalState s
p = prettyShow s
p (pure b)
res = loop =<< startP b
resDebug = loopDebug 6 =<< startP b
uncurry (\r b -> traverse_ Text.putStrLn ([r] <> [b])) $ bimap (Text.pack . show) (s' . pretty) (s' res)
uncurry (\r bs -> traverse_ Text.putStrLn ([r] <> take 10 bs)) $ bimap (Text.pack . show) (fmap (s' . pretty)) (s' resDebug)

level 1 buy and sell effects

view #level1Ability $ pets s Map.! "pet-beaver"
view #level1Ability $ pets s Map.! "pet-otter"
view #level1Ability $ pets s Map.! "pet-horse"
view #level1Ability $ pets s Map.! "pet-duck"
view #level1Ability $ pets s Map.! "pet-beaver"

random battle using bAlways

tl = [["pet-ant","pet-beaver","pet-cricket","pet-duck","pet-fish","pet-horse","pet-mosquito","pet-otter","pet-pig"]] :: [[Sap.Key PetKey]]
bAlways = fromMaybe (error "wtf") <$> (recruitPetAlways tl =<< startBoard)
s <- sapState StandardPack
b = flip evalState s $ mkBattle <$> bAlways <*> bAlways
s' = flip evalState s
prettyShow s (pure b)

startP testing

sr <- sapState StandardPack
prettyShow sr $ startP b

step by step

p = prettyShow s
p $ startP b
p $ fightP =<< startP b
p $ fightP =<< fightP =<< startP b
p $ fightP =<< fightP =<< fightP =<< startP b

manual Battle tests

:set -XOverloadedLists
t1 = Battle {decks = (BattleDeck {bdeckV = [BattlePet {bpet = Key {aKey = "pet-fish"}, battack = 2, bhealth = 3, bstatus = Nothing},BattlePet {bpet = Key {aKey = "pet-ant"}, battack = 2, bhealth = 1, bstatus = Nothing}]},BattleDeck {bdeckV = [BattlePet {bpet = Key {aKey = "pet-cricket"}, battack = 1, bhealth = 1, bstatus = Nothing},BattlePet {bpet = Key {aKey = "pet-pig"}, battack = 3, bhealth = 1, bstatus = Nothing}]})}
s <- sapState StandardPack
s' = flip evalState s
prettyShow s (pure t1)
prettyShow s $ fightP t1
s' $ fightP =<< fightP =<< fightP t1

adhoc effect testing

prettyShow s $ pure b
prettyShow s $ startP b
b
s' $ bfEffects StartOfBattle (\_ _ -> True) b
prettyShow s $ applyEffect (DealDamage (Amount 1) (Target {targetType = RandomEnemy, targetN = Just 1, includingFutures = Nothing})) (Pos {posSide = SideRight, posIndex = 1}) b
side = SideRight
n = view (bdSize (other side)) b
r = s' $ zoom #gen (rvi n)
over (bdPet (Pos (other side) 0) % #bhealth) (\h -> h - 1) b
b_1 = Battle {decks = (BattleDeck {bdeckV = [BattlePet {bpet = Key {aKey = "pet-fish"}, battack = 2, bhealth = 3, bstatus = Nothing},BattlePet {bpet = Key {aKey = "pet-fish"}, battack = 2, bhealth = 3, bstatus = Nothing},BattlePet {bpet = Key {aKey = "pet-mosquito"}, battack = 2, bhealth = 2, bstatus = Nothing}]},BattleDeck {bdeckV = [BattlePet {bpet = Key {aKey = "pet-fish"}, battack = 2, bhealth = 3, bstatus = Nothing},BattlePet {bpet = Key {aKey = "pet-fish"}, battack = 2, bhealth = 3, bstatus = Nothing},BattlePet {bpet = Key {aKey = "pet-mosquito"}, battack = 2, bhealth = 2, bstatus = Nothing}]})}
p (pure b_1)
p (startP b_1)

horse fight effect

view #level1Ability $ pets s Map.! "pet-horse"

Hard-coded Level 1s

  • [ ] beaver buy
    • solo
    • 2 options to hit
  • [ ] buy with horse (+ 1) in deck
  • [ ] duck, otter, pig sale
s <- sapState StandardPack
s' = flip evalState s
b = blankBoard (Key "turn-1")
horse = mkDeckPet (PetShopBoosts 0 0) (Key "pet-horse")
otter = mkDeckPet (PetShopBoosts 0 0) (Key "pet-otter")
beaver = mkDeckPet (PetShopBoosts 0 0) (Key "pet-beaver")
fish = mkDeckPet (PetShopBoosts 0 0) (Key "pet-fish")

toShop ps = foldr ($) (s' b) $ zipWith (\i p -> set (sPet i) (Just (UnFrozen, (s' p)))) [0..] ps
  pb b = prettyShow s (pure b)
  p b = prettyShow s b
  pb (toShop [otter])

Done otter solo

p $ buy 0 0 (toShop [otter])

otter singleton

b = toShop [otter, fish]
pb b
b' = buy 1 0 b
b'' = s' $ recruit 0 0 <$> b'
pb b''

junk

bh = Board {hearts = Hearts {nhearts = 7}, deck = Deck {deckV = V.fromList [Just (DeckPet {deckPet = Key {aKey = "pet-fish"}, attack = 2, health = 3, attackUeob = 0, healthUeob = 0, dpStatus = Nothing}),Just (DeckPet {deckPet = Key {aKey = "pet-fish"}, attack = 2, health = 3, attackUeob = 0, healthUeob = 0, dpStatus = Nothing}),Nothing,Nothing,Nothing]}, shop = Shop {petShop = PetShop {petShopV = V.fromList [Just (UnFrozen,DeckPet {deckPet = Key {aKey = "pet-horse"}, attack = 2, health = 1, attackUeob = 0, healthUeob = 0, dpStatus = Nothing}),Nothing,Nothing]}, foodShop = FoodShop {foodShopV = V.fromList [Nothing]}, petShopSize = 3, foodShopSize = 1, petShopBoosts = PetShopBoosts 0 0}, boardTurn = Key {aKey = "turn-1"}}
slive <- sapState StandardPack
-- flip evalState slive $ buy 0 2 bh
prettyShow slive $ fmap (either undefined id) $ buy 0 1 bh
:t applyBoardEffectsBy Summoned ((==EachFriend) . view #targetType) (\k _ -> k/=1) $ either undefined id (recruit 0 1 bh)

About

No description, website, or topics provided.

Resources

License

Stars

Watchers

Forks

Releases

No releases published

Packages

No packages published