A cli database for some FFX stuff
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell   #-}
{-# LANGUAGE TypeApplications  #-}

module Item
    ( -- * Classes
      Ailment (..)
    , Category (..)
    , DamageType (..)
    , EffectType (..)
    , Element (..)
    , HasItemDetails (..)
    , HasTarget (..)
    , Item (Item)
    , ItemDetails (..)
    , RestoreAmount (..)
    , StatusEffect (..)
    , Target (..)
      -- * Collections
    , items
      -- * Utility
    , health
    , mana
    ) where

import           Data.Char          (isSpace)
import           Data.Maybe         (fromJust)
import           Data.PrintableText
import qualified Data.Text          as T

import           Control.Lens
import           Control.Lens.TH

import           Spell

data Category
    = Use
    | Potion
    | Weapon
    | Armor
    | Grid
    | KeyItem
    | Other deriving (Show, Eq, Ord)

data Target = Single | Multi | Random deriving (Show, Eq, Ord)

makeClassy ''Target

data Rarity = Common | Uncommon | Rare | VeryRare deriving (Show, Eq)

data StatusEffect = Ailment Ailment | Spell Spell deriving (Show, Eq, Ord)

data EffectType
    = Damage DamageType
    | StatusEffect
    | Remove StatusEffect
    | Restore Restore
    deriving (Show, Eq, Ord)

data Restore
    = HPRestore RestoreAmount
    | MPRestore RestoreAmount
    deriving (Show, Eq, Ord)

data RestoreAmount = RestoreAmount Int | RestoreFull deriving (Show, Eq, Ord)

data Ailment
    = Berserk
    | Confusion
    | Darkness
    | Petrify
    | Poison
    | Silence
    | Sleep
    | Slow
    | Zombie
    deriving (Show, Eq, Ord)

data Buff = Regen deriving (Show, Eq, Ord)

data DamageType = Normal
                  | Elemental Element
                  | Force
    deriving (Show, Eq, Ord)

data Element = Fire | Water | Ice | Lightning deriving (Show, Eq, Ord)

data ItemDetails = ItemDetails
    { _name        :: PrintableText
    , _description :: T.Text
    }
    deriving (Show, Eq, Ord)

makeClassy ''ItemDetails

data Item = Item
    { details    :: ItemDetails
    , itemTarget :: Target
    , _effects   :: [EffectType]
    , _category  :: Category
    , _rarity    :: Rarity
    }
    deriving (Show, Eq)

makeLenses ''Item

instance HasItemDetails Item where
    itemDetails = lens details (\x y -> x { details = y })

instance HasTarget Item where
    target = lens itemTarget (\x y -> x { itemTarget = y })

health :: (a -> RestoreAmount) -> a -> EffectType
health f = Restore . HPRestore . f

mana :: (a -> RestoreAmount) -> a -> EffectType
mana f = Restore . MPRestore . f

items :: [Item]
items =
    [ item "Bomb Core" "A bomb core" Single [Damage Normal] Use Rare
    , item "Potion" "Restores 200 HP" Single [health RestoreAmount 200] Potion Common
    , item "Hi-Potion" "Restores 1,000 HP" Single [health RestoreAmount 1000] Potion Common
    , item "X-Potion" "Fully restores HP" Single [health id RestoreFull] Potion Uncommon
    , item "Ether" "Restores 100 MP" Single [mana RestoreAmount 100] Potion Common
    , item "Eye Drops" "Removes Blindness" Single [remove Darkness] Potion Common
    , item "Soft" "Removes Petrification" Single [remove Petrify] Potion Common
    , item "Antidote" "Removes Poison" Single [remove Poison] Potion Common
    , item "Echo Screen" "Removes Silence" Single [remove Silence] Potion Common
    , item "Grenade" "Damages all enemies" Multi [Damage Normal] Use Uncommon
    , item "Mega Potion" "Restore 2000 HP for all allies" Multi [health RestoreAmount 2000] Potion Uncommon
    , item "Power Sphere" "Unlocks a Power node" Single [] Grid Common
    , item "Speed Sphere" "Unlocks a Speed node" Single [] Grid Common
    ]
    where
        mkName = fromJust . fromText
        details x = ItemDetails (mkName x)
        item x y = Item (details x y)
        remove = Remove . Ailment