Skip to content

Instantly share code, notes, and snippets.

@Javran
Last active May 15, 2017 01:01
Show Gist options
  • Select an option

  • Save Javran/28bc46f4e0717db92b5a054b8afdf26b to your computer and use it in GitHub Desktop.

Select an option

Save Javran/28bc46f4e0717db92b5a054b8afdf26b to your computer and use it in GitHub Desktop.
ASW equipments
{-# LANGUAGE
NoMonomorphismRestriction
, PartialTypeSignatures
, MultiWayIf
#-}
{-# OPTIONS_GHC -fno-warn-partial-type-signatures #-}
module ASWTest where
import Data.List
import Text.Printf
import Data.Ord
data ASWType
= DC
| DCP
| Sonar
deriving (Eq, Show, Ord)
data ASWEquip = ASWE
{ desc :: String
, aswStat :: Int
, ty :: ASWType
} deriving (Eq, Show, Ord)
aswEquips :: [ASWEquip]
aswEquips =
[ ASWE "三式爆雷投射機" 8 DCP
, ASWE "二式爆雷" 7 DC
, ASWE "九五式爆雷" 4 DC
, ASWE "三式水中探信儀" 10 Sonar
, ASWE "四式水中聴音機" 12 Sonar
]
type EquipList = [ASWEquip]
fI :: _
fI = fromIntegral
firePower :: Int -> EquipList -> Double
firePower shipASW es =
(2*sqrt (fI shipASW) + 1.5*aswSum + 13) * aswMod
where
aswSum = sum $ (fI . aswStat) <$> es
aswMod = aswModifier es
aswModifier :: EquipList -> Double
aswModifier es = if
| hasDCP && hasDC && hasSonar -> 1.3
| hasDCP && hasSonar -> 1.15
| otherwise -> 1
where
tys = ty <$> es
has t = t `elem` tys
hasDCP = has DCP
hasDC = has DC
hasSonar = has Sonar
pickOne :: [a] -> _
pickOne [] = []
pickOne xs@(y:ys)
= (y,xs) -- with rep
: (y,ys) -- w/o rep
: pickOne ys -- skip
genEquips :: Int -> [EquipList]
genEquips = compact . genEquips' aswEquips
where
genEquips' _ 0 = pure []
genEquips' eqs n = do
(e,eqs') <- pickOne eqs
remained <- genEquips' eqs' (n-1)
pure (e:remained)
compact = nub . (sort <$>)
printTable :: Int -> IO ()
printTable shipASW = do
let rows = sortBy (flip $ comparing snd) $ (\es -> (es,firePower shipASW es)) <$> genEquips 3
ppr (es,fp) = printf "%s: %f\n" (intercalate " + " $ desc <$> es) fp
mapM_ ppr rows
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment