Skip to content

Instantly share code, notes, and snippets.

@Akii
Created May 31, 2017 21:37
Show Gist options
  • Save Akii/de87f5bdc24bf2af147015d15986ef78 to your computer and use it in GitHub Desktop.
Save Akii/de87f5bdc24bf2af147015d15986ef78 to your computer and use it in GitHub Desktop.
Me trying to parse some stuff and turn it into HTML
Tapu Fini @ Life Orb
Ability: Misty Surge
EVs: 128 HP / 252 SpA / 128 SpD
Modest Nature
IVs: 0 Atk
- Moonblast
- Dazzling Gleam
- Surf
- Aqua Ring
Mimikyu @ Ghostium Z
Ability: Disguise
EVs: 200 HP / 124 Atk / 4 SpD / 180 Spe
Jolly Nature
- Bulk Up
- Shadow Claw
- Play Rough
- Shadow Sneak
<pre><span class="type-water">Tapu Fini </span>@ Life Orb
<span class="heading">Ability:</span> Misty Surge
<span class="heading">EVs:</span> 128 HP / 252 SpA / 128 SpD
Modest Nature
<span class="heading">IVs:</span> 0 Atk
<span class="type-fairy">-</span> Moonblast
<span class="type-fairy">-</span> Dazzling Gleam
<span class="type-water">-</span> Surf
<span class="type-water">-</span> Aqua Ring </pre>
<pre><span class="type-ghost">Mimikyu</span> @<span class="type-ghost"> Ghostium Z </span>
<span class="heading">Ability:</span> Disguise
<span class="heading">EVs:</span> 200 HP / 124 Atk / 4 SpD / 180 Spe
Jolly Nature
<span class="type-fighting">-</span> Bulk Up
<span class="type-ghost">-</span> Shadow Claw
<span class="type-fairy">-</span> Play Rough
<span class="type-ghost">-</span> Shadow Sneak </pre>
module Test where
import ClassyPrelude hiding (many, (<|>), readFile, optional)
import Prelude (read, readFile)
import Text.Parsec
import Text.Parsec.String
data Pokemon = Pokemon
{ pokeName :: String
, pokeThingAfterAt :: String
, pokeAbility :: Ability
, pokeEVs :: [EV]
, pokeNature :: Nature
, pokeIVs :: [EV] -- don't have enough data to deduce what this is
, pokeMoves :: [Move] -- yes, no idea about pokemon
} deriving (Show)
data Nature
= Modest
| Jolly
| UnknownNature
deriving (Show)
data PokemonType
= Fairy
| Water
| Fighting
| Ghost
| UnknownType
deriving (Show)
newtype Ability = Ability
{ getAbility :: String
} deriving (Show)
data EV
= HP Int
| Atk Int
| SpD Int
| Spe Int
| SpA Int
deriving (Show)
data Move = Move PokemonType String deriving (Show)
type Pokemons = [Pokemon]
pokemonBlockParser :: Parser Pokemon
pokemonBlockParser = do
(name,thingy) <- pokeNameLineParser
ability <- abilityLineParser
evs <- evsLineParser <* newline
nature <- natureLineParser
ivs <- ivsLineParser <|> return []
moves <- moveParser `sepBy` newline
return $ Pokemon name thingy ability evs nature ivs moves
pokeNameLineParser :: Parser (String,String)
pokeNameLineParser = do
name <- manyTill anyChar (char '@' *> spaces)
thingAfterAt <- manyTill anyChar newline
return (stripR name, stripR thingAfterAt)
abilityLineParser :: Parser Ability
abilityLineParser = do
_ <- string "Ability: "
Ability <$> manyTill anyChar newline
evsLineParser :: Parser [EV]
evsLineParser = do
_ <- string "EVs:" *> spaces
evParser `sepBy` (spaces <* char '/' *> spaces)
ivsLineParser :: Parser [EV]
ivsLineParser = do
_ <- string "IVs:" *> spaces
evParser `sepBy` (spaces <* char '/' *> spaces)
evParser :: Parser EV
evParser = do
amount <- read <$> many digit
_ <- char ' '
evType <- many alphaNum
case evType of
"HP" -> return (HP amount)
"Atk" -> return (Atk amount)
"SpD" -> return (SpD amount)
"SpA" -> return (SpA amount)
"Spe" -> return (Spe amount)
_ -> fail "unknown EV type"
natureLineParser :: Parser Nature
natureLineParser = do
nature <- manyTill anyChar (string " Nature")
return $ case nature of
"Modest" -> Modest
"Jolly" -> Jolly
_ -> UnknownNature
moveParser :: Parser Move
moveParser = do
_ <- char '-'
_ <- char ' '
move <- manyTill anyChar eof
return (Move (pokeTypeByMoveName move) move)
pokeTypeByMoveName :: String -> PokemonType
pokeTypeByMoveName s = UnknownType
stripR :: String -> String
stripR = reverse . stripL . reverse
stripL :: String -> String
stripL = dropWhile (== ' ')
@Akii
Copy link
Author

Akii commented May 31, 2017

@felixphew Saw your msg on IRC today and thought I give it a try. This is far from complete but here are the steps I'd (and will) take to transform the text file into HTML:

  1. Create an appropriate data type
  2. Parse the file to create that data type
  3. Turn the data type into HTML

Will work on it more tomorrow.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment