{-#LANGUAGE OverloadedStrings#-}
{-#LANGUAGE TemplateHaskell#-}
{-#LANGUAGE OverloadedLabels #-}
{-#LANGUAGE DataKinds, MultiParamTypeClasses #-}
{-#LANGUAGE ConstraintKinds #-}
{-#LANGUAGE FlexibleContexts #-}
module Network.SC2.Internal.Types where
import Data.Text
import Data.Aeson
import Lens.Labels hiding ((.))
import Data.Aeson.TH
import Control.Lens

type RawIDMappable a = (HasLens' a "id" Integer, HasLens' a "canonicalName" Text)

data Unit = Unit {unitStableID :: Int, unitName :: Text} deriving (Eq, Show)

instance HasLens' Unit "id" Integer where
    lensOf' _ = lens (fromIntegral . unitStableID) (\u i-> u{ unitStableID = (fromIntegral i)})

instance HasLens' Unit "canonicalName" Text where
    lensOf' _ = lens unitName (\u n -> u{unitName = n})

data Ability = Ability {abilityStableID :: Int, abilityName :: Text, abilityButtonName :: Text, abilityFriendlyName :: Maybe Text, index :: Int, remapID :: Maybe Int} deriving (Eq, Show)
instance HasLens' Ability "id" Integer where
    lensOf' _ = lens (fromIntegral . abilityStableID) (\a i -> a{abilityStableID = fromIntegral i})



data Upgrade = Upgrade {upgradeStableID :: Int, upgradeName :: Text} deriving (Eq, Show)
instance HasLens' Upgrade "id" Integer where
    lensOf' _ = lens (fromIntegral . upgradeStableID) (\u i-> u{ upgradeStableID = (fromIntegral i)})

instance HasLens' Upgrade "canonicalName" Text where
    lensOf' _ = lens (\u -> (upgradeName u) `append` "Tech") (\u n -> u{upgradeName = n})

data Buff = Buff {buffStableID :: Int, buffName :: Text} deriving (Eq, Show)
instance HasLens' Buff "id" Integer where
    lensOf' _ = lens (fromIntegral . buffStableID) (\b i-> b{ buffStableID = (fromIntegral i)})

instance HasLens' Buff "canonicalName" Text where
    lensOf' _ = lens buffName (\b n -> b{buffName = n})

data Effect = Effect {effectStableID :: Int, effectName :: Text, effectFriendlyName :: Maybe Text, radius :: Maybe Float} deriving (Eq, Show)

instance HasLens' Effect "id" Integer where
    lensOf' _ = lens (fromIntegral . effectStableID) (\e i-> e{ effectStableID = (fromIntegral i)})

instance HasLens' Effect "canonicalName" Text where
    lensOf' _ = lens (\(Effect _ n fn _) -> case fn of
        Nothing -> n
        Just f -> f )
     (\e n -> e{effectName = n})

data IDs = IDs { units :: [Unit], abilities :: [Ability], upgrades :: [Upgrade], buffs :: [Buff], effects :: [Effect]} deriving (Eq, Show)

instance FromJSON Unit where
    parseJSON = withObject "Unit" $ \u -> Unit <$> u .: "id" <*> u.: "name"
instance FromJSON Ability where
    parseJSON = withObject "Ability" $ \u -> Ability <$> u .: "id" <*> u.: "name" <*> u.: "buttonname" <*> u.:? "friendlyname" <*> u.: "index" <*> u.:? "remapid"
instance FromJSON Upgrade where
    parseJSON = withObject "Upgrade" $ \u -> Upgrade <$> u .: "id" <*> u.: "name"
instance FromJSON Buff where
    parseJSON = withObject "Buff" $ \u -> Buff <$> u .: "id" <*> u.: "name"
instance FromJSON Effect where
    parseJSON = withObject "Effect" $ \u -> Effect <$> u .: "id" <*> u.: "name" <*> u.:? "friendlyname" <*> u.:? "radius"

$(let
    translation :: String -> String
    translation "units" = "Units"
    translation "abilities" = "Abilities"
    translation "upgrades" = "Upgrades"
    translation "buffs" = "Buffs"
    translation "effects" = "Effects"
    translation k = k
  in
    deriveFromJSON defaultOptions {fieldLabelModifier = translation} ''IDs)