{-#LANGUAGE RankNTypes, DataKinds, ConstraintKinds, FlexibleContexts, GADTs, StandaloneDeriving, GeneralisedNewtypeDeriving, TypeSynonymInstances, FlexibleInstances#-} module Network.SC2.LowLevel.Types ( module Network.SC2.LowLevel.Types , A.Difficulty(..) , A.Status(..) -- , R.Alliance(..) , R.CloakState(..) , ) where import Data.Void import qualified Proto.S2clientprotocol.Sc2api as A import qualified Proto.S2clientprotocol.Raw as R import qualified Data.ByteString as BS import Lens.Labels (HasLens') import Data.Text import Data.Word import Data.Functor.Identity import Network.SC2.Constants.Entities import Data.Coerce type Point = (Float, Float) type PointI = (Int,Int) -- FIXME better image format data ImageData = ImageData Int (Int, Int) BS.ByteString deriving (Show, Eq) data Race' a = Terran | Zerg | Protoss | Random a deriving (Show, Eq) type Race = Race' () type RaceResolved = Race' (Maybe (Race' Void)) data Interface c = Raw | Score | FeatureLayer c | Render c deriving (Show, Eq) newtype PlayerID = PlayerID Int deriving (Show, Eq) data Player r = Observer | Participant r | Computer r A.Difficulty deriving (Show, Eq) data Map = BattlenetMap Text | LocalMap Text (Maybe BS.ByteString) deriving (Show, Eq) data ChatChannel = Broadcast | Team deriving (Eq, Show) type RawTag = Word64 newtype UnitID = UnitID {unRawTag :: RawTag} deriving (Eq, Show) type Alliance = R.Alliance data Unit = Unit { tag :: UnitID, unitType :: UnitType, alliance :: Alliance, owner :: PlayerID } deriving (Eq, Show) type IdentifiesUnit a = Lens.Labels.HasLens' a "unitTag" RawTag data Target where TargetPoint :: Point -> Target -- TargetScreen :: PointI -> Target -- TargetMinimap :: PointI -> Target TargetUnit :: UnitID -> Target deriving instance Eq Target deriving instance Show Target class Targetable a where asTarget :: a -> Target instance Targetable Point where asTarget = TargetPoint instance Targetable Unit where asTarget = TargetUnit . tag instance Targetable Target where asTarget = id data GameInfo = GameInfo deriving (Show, Eq) data GameInfoResponse = GameInfoResponse { mapName :: Text , modNames :: [Text] , localMapPath :: FilePath , playerInfo :: [(PlayerID, Player RaceResolved)] , startRaw :: Maybe StartRaw , interfaces :: [Interface ()] } deriving (Eq, Show) data StartRaw = StartRaw { mapSize :: (Int, Int) , pathingGrid :: ImageData , terrainHeight :: ImageData , placementGrid :: ImageData , playableArea :: ((Int, Int), (Int, Int)) , startLocations :: [Point] } deriving (Eq, Show) data PlayerCommon = PlayerCommon { playerID :: Int, minerals :: Int, vespene :: Int --TODO } data PlayerResources = PlayerResources type UnitContainer = [Unit] data Units where ControlGroup :: GroupID -> Units Ungrouped :: UnitContainer -> Units unitsToTags :: Units -> [RawTag] unitsToTags (Ungrouped u) = fmap (coerce . tag) u individualUnit :: Unit -> Units individualUnit u = Ungrouped ([u]) data MapInfo = MapInfo data Order = Order { abilityID :: AbilityType, target :: Target, queue :: Bool } class Orderable a where toIDs :: a -> [UnitID] instance Orderable Units where toIDs (Ungrouped u) = fmap tag u instance Orderable Unit where toIDs u = [tag u] instance Orderable UnitContainer where toIDs = fmap tag toTags :: Orderable a => a -> [RawTag] toTags = fmap (coerce) . toIDs newtype GroupID = GroupID Word deriving (Eq, Show, Enum, Bounded)