module Combinatorics.Battleship.Count.ShortenShip where
import qualified Combinatorics.Battleship.Count.CountMap as CountMap
import qualified Combinatorics.Battleship.Count.Counter as Counter
import qualified Combinatorics.Battleship.Count.Frontier as Frontier
import qualified Combinatorics.Battleship.Fleet as Fleet
import qualified Combinatorics.Battleship.Size as Size
import Combinatorics.Battleship.Size (Nat, Size(Size), n6, n8, n10, )
import qualified Control.Monad.Trans.State.Strict as MS
import Control.Monad (when, guard, zipWithM_, forM_, )
import Control.Applicative (Alternative, (<|>), )
import Foreign.Storable (Storable, )
import Data.Word (Word64, )
import qualified Data.Map as Map
import qualified Data.List.Match as Match
import qualified Data.List.HT as ListHT
import qualified Data.Foldable as Fold
import Data.Map (Map, )
import Data.Monoid (mappend, )
import Data.Tuple.HT (mapFst, mapSnd, )
import Data.Function.HT (nest, )
import Data.List (intercalate, )
import Text.Printf (printf, )
import qualified Test.QuickCheck.Monadic as QCM
import qualified Test.QuickCheck as QC
type Count = Counter.Composed Word64 Word64
type CountMap w = CountMap.T w Count
type CountMapPath w = CountMap.Path w Count
baseCase :: Size w -> CountMap w
baseCase _size =
CountMap.singleton (Frontier.empty, Fleet.empty) Counter.one
asumTakeFrontier ::
(Nat w, Alternative f) =>
Frontier.T w -> Frontier.Position -> Size w -> [f a] -> f a
asumTakeFrontier frontier pos (Size size) =
Fold.asum . Match.take (takeWhile (Frontier.isFree frontier) [pos .. size-1])
widthRange :: (Nat w) => Size w -> [Int]
widthRange (Size size) = take size [0 ..]
atEnd :: Size w -> Int -> Bool
atEnd (Size size) pos = pos>=size
maxShipSize :: Fleet.ShipSize
maxShipSize = min Fleet.maxSize Frontier.maxShipSize
guardCumulativeSubset :: Fleet.T -> MS.StateT (Frontier.T w, Fleet.T) [] ()
guardCumulativeSubset cumMaxFleet = do
(frontier, fleet) <- MS.get
guard $
Fleet.subset
(Fleet.cumulate $ addFrontierFleet frontier fleet)
cumMaxFleet
newShip ::
Fleet.T -> Fleet.T ->
Fleet.ShipSize -> MS.StateT (Frontier.T w, Fleet.T) [] ()
newShip cumMaxFleet maxFleet shipSize = do
MS.modify $ mapSnd $ Fleet.inc shipSize
guard . flip Fleet.subset maxFleet =<< MS.gets snd
guardCumulativeSubset cumMaxFleet
insertVertical ::
(Nat w) =>
Fleet.T -> Int ->
Frontier.Position -> MS.StateT (Frontier.T w, Fleet.T) [] ()
insertVertical cumMaxFleet n pos = do
MS.modify $ mapFst $ Frontier.insertNew pos (Frontier.Vertical n)
guardCumulativeSubset cumMaxFleet
nextFrontier :: (Nat w) => Size w -> CountMap w -> CountMap w
nextFrontier width =
CountMap.mergeMany .
map
(\((frontier,fleet), cnt) ->
CountMap.fromList $
map (flip (,) cnt) $ mergeSymmetricFrontiers $
map (mapFst (Frontier.dilate width)) $
transitionFrontier width frontier fleet) .
CountMap.toAscList
transitionFrontier ::
(Nat w) => Size w -> Frontier.T w -> Fleet.T -> [(Frontier.T w, Fleet.T)]
transitionFrontier width oldFrontier =
let go pos =
when (not $ atEnd width pos) $ do
let insertVert n =
MS.modify $ mapFst $
Frontier.insertNew pos (Frontier.Vertical n)
let updateFleet = MS.modify . mapSnd
(frontier,fleet) <- MS.get
case Frontier.lookup oldFrontier pos of
Frontier.Blocked -> go (pos+1)
Frontier.Vertical n ->
go (pos+2)
<|>
(do guard (n < maxShipSize)
insertVert (n+1)
updateFleet (Fleet.inc (n+1) . Fleet.dec n)
go (pos+2))
Frontier.Free ->
go (pos+1)
<|>
(do insertVert 1
updateFleet (Fleet.inc 1)
go (pos+2))
<|>
(asumTakeFrontier oldFrontier pos width $
zipWith3
(\newPos shipSize newFrontierUpdate -> do
MS.put (newFrontierUpdate, fleet)
updateFleet (Fleet.inc shipSize)
go newPos)
[pos+2 ..]
[1 .. Fleet.maxSize]
(tail $
scanl
(flip (Frontier.blockBounded width))
frontier [pos ..]))
in MS.execStateT (go 0) . (,) Frontier.empty
count :: (Nat w) => (Size w, Int) -> Fleet.T -> Count
count (width,height) reqFleet =
Counter.sum $
map snd $
filter (\((_front,fleet), _) -> fleet == reqFleet) $
CountMap.toAscList $
nest height (nextFrontier width) $ baseCase width
nextFrontierBounded :: (Nat w) => Size w -> Fleet.T -> CountMap w -> CountMap w
nextFrontierBounded width maxFleet =
CountMap.mergeMany .
map
(\((frontier,fleet), cnt) ->
CountMap.fromList $
map (flip (,) cnt) $ mergeSymmetricFrontiers $
map (mapFst (Frontier.dilate width)) $
transitionFrontierBounded width maxFleet frontier fleet) .
CountMap.toAscList
nextFrontierBoundedExternal ::
(Nat w) => Size w -> Fleet.T -> CountMapPath w -> CountMap w -> IO ()
nextFrontierBoundedExternal width maxFleet path =
CountMap.writeSorted path .
map
(concatMap
(\((frontier,fleet), cnt) ->
map (flip (,) cnt) $ mergeSymmetricFrontiers $
map (mapFst (Frontier.dilate width)) $
transitionFrontierBounded width maxFleet frontier fleet)) .
ListHT.sliceVertical bucketSize .
CountMap.toAscList
transitionFrontierBounded ::
(Nat w) =>
Size w -> Fleet.T -> Frontier.T w -> Fleet.T ->
[(Frontier.T w, Fleet.T)]
transitionFrontierBounded width maxFleet oldFrontier =
let cumMaxFleet = Fleet.cumulate maxFleet
go pos =
when (not $ atEnd width pos) $ do
(frontier,fleet) <- MS.get
case Frontier.lookup oldFrontier pos of
Frontier.Blocked -> go (pos+1)
Frontier.Vertical n ->
(newShip cumMaxFleet maxFleet n
<|>
(guard (n < maxShipSize) >>
insertVertical cumMaxFleet (n+1) pos)
>>
go (pos+2))
Frontier.Free ->
go (pos+1)
<|>
(insertVertical cumMaxFleet 1 pos >> go (pos+2))
<|>
(asumTakeFrontier oldFrontier pos width $
zipWith3
(\newPos shipSize frontierUpdate -> do
MS.put (frontierUpdate,fleet)
newShip cumMaxFleet maxFleet shipSize
go newPos)
[pos+2 ..]
[1 .. Fleet.maxSize]
(tail $
scanl
(flip (Frontier.blockBounded width))
frontier [pos ..]))
in MS.execStateT (go 0) . (,) Frontier.empty
countBounded :: (Nat w) => (Size w, Int) -> Fleet.T -> Count
countBounded (width,height) reqFleet =
countBoundedFromMap reqFleet $
nest height (nextFrontierBounded width reqFleet) $ baseCase width
nextFrontierTouching :: (Nat w) => Size w -> Fleet.T -> CountMap w -> CountMap w
nextFrontierTouching width maxFleet =
CountMap.mergeMany .
map
(\((frontier,fleet), cnt) ->
CountMap.fromList $
map (flip (,) cnt) $ mergeSymmetricFrontiers $
transitionFrontierTouching width maxFleet frontier fleet) .
CountMap.toAscList
nextFrontierTouchingExternal ::
(Nat w) => Size w -> Fleet.T -> CountMapPath w -> CountMap w -> IO ()
nextFrontierTouchingExternal width maxFleet path =
CountMap.writeSorted path .
map
(concatMap
(\((frontier,fleet), cnt) ->
map (flip (,) cnt) $ mergeSymmetricFrontiers $
transitionFrontierTouching width maxFleet frontier fleet)) .
ListHT.sliceVertical bucketSize .
CountMap.toAscList
transitionFrontierTouching ::
(Nat w) =>
Size w -> Fleet.T -> Frontier.T w -> Fleet.T -> [(Frontier.T w, Fleet.T)]
transitionFrontierTouching width maxFleet oldFrontier =
let cumMaxFleet = Fleet.cumulate maxFleet
finishVerticals pos =
case Frontier.lookup oldFrontier pos of
Frontier.Blocked ->
error "in touching mode there must be no blocked fields"
Frontier.Vertical n ->
(guard (n < maxShipSize) >>
insertVertical cumMaxFleet (n+1) pos)
<|>
newShip cumMaxFleet maxFleet n
Frontier.Free -> return ()
startNewShips pos =
when (not $ atEnd width pos) $ do
frontier <- MS.gets fst
case Frontier.lookup frontier pos of
Frontier.Blocked ->
error "finishVerticals must not block fields"
Frontier.Vertical _ ->
startNewShips (pos+1)
Frontier.Free ->
startNewShips (pos+1)
<|>
(insertVertical cumMaxFleet 1 pos >> startNewShips (pos+1))
<|>
(asumTakeFrontier frontier pos width $
map
(\shipSize ->
newShip cumMaxFleet maxFleet shipSize >>
startNewShips (pos+shipSize)) $
[1 .. Fleet.maxSize])
in \fleet -> flip MS.execStateT (Frontier.empty, fleet) $ do
mapM_ finishVerticals (widthRange width)
startNewShips 0
countTouching :: (Nat w) => (Size w, Int) -> Fleet.T -> Count
countTouching (width,height) reqFleet =
countBoundedFromMap reqFleet $
nest height (nextFrontierTouching width reqFleet) $ baseCase width
canonicalFrontier :: (Nat w) => Frontier.T w -> Frontier.T w
canonicalFrontier fr = min fr (Frontier.reverse fr)
mergeSymmetricFrontiers ::
(Nat w) => [(Frontier.T w, fleet)] -> [(Frontier.T w, fleet)]
mergeSymmetricFrontiers = map (mapFst canonicalFrontier)
fleetAtFrontier :: Frontier.T w -> Fleet.T
fleetAtFrontier =
Frontier.foldMap
(\use ->
case use of
Frontier.Vertical n -> Fleet.singleton n 1
_ -> Fleet.empty)
addFrontierFleet :: Frontier.T w -> Fleet.T -> Fleet.T
addFrontierFleet frontier = mappend $ fleetAtFrontier frontier
{-# SPECIALISE countBoundedFromMap :: Fleet.T -> CountMap w -> Count #-}
countBoundedFromMap ::
(Counter.C a, Storable a) => Fleet.T -> CountMap.T w a -> a
countBoundedFromMap reqFleet =
Counter.sum .
map snd .
filter (\((front,fleet), _) ->
addFrontierFleet front fleet == reqFleet) .
CountMap.toAscList
countBoundedFleetsFromMap :: CountMap w -> Map Fleet.T Integer
countBoundedFleetsFromMap =
Map.fromListWith (+) .
map (\((front,fleet), cnt) ->
(addFrontierFleet front fleet,
Counter.toInteger cnt)) .
CountMap.toAscList
countBoundedFleetsFromMap_ :: CountMap w -> Map Fleet.T Integer
countBoundedFleetsFromMap_ =
Map.mapKeysWith (+) (uncurry addFrontierFleet) .
fmap Counter.toInteger .
CountMap.toMap
countSingleKind :: IO ()
countSingleKind =
mapM_
(print . countBounded (n10,10) . Fleet.fromList . (:[]))
[(5,1), (4,2), (3,3), (2,4)]
count8x8 :: IO ()
count8x8 =
let reqFleet = Fleet.english
width = n8
height = 8
in reportCounts
(baseCase width) (nextFrontierTouchingExternal width)
height reqFleet
countTouchingExternalReturn ::
Nat w => (Size w, Int) -> Fleet.T -> IO Count
countTouchingExternalReturn (width, height) =
countExternalGen (baseCase width) (nextFrontierTouchingExternal width) height
count10x10 :: IO ()
count10x10 =
print $ countBounded (n10,10) Fleet.english
countStandard :: IO ()
countStandard =
let
reqFleet = Fleet.english
width = n10
height = 12
in mapM_ (print . countBoundedFromMap reqFleet) $
take (height+1) $
iterate (nextFrontierBounded width reqFleet) $
baseCase width
bucketSize :: Int
bucketSize = 2^(14::Int)
tmpPath :: Int -> CountMap.Path w a
tmpPath = CountMap.Path . printf "/tmp/battleship%02d"
writeTmpCountMap :: Int -> CountMap w -> IO ()
writeTmpCountMap = CountMap.writeFile . tmpPath
writeTmps :: IO ()
writeTmps =
let width = n10
in zipWithM_ writeTmpCountMap [0 ..] $
iterate (nextFrontierBounded width Fleet.german) $
baseCase width
countExternalGen ::
(Counter.C a, Storable a) =>
CountMap w ->
(Fleet.T -> CountMap.Path w a -> CountMap.T w a -> IO ()) ->
Int -> Fleet.T -> IO a
countExternalGen base next height fleet = do
writeTmpCountMap 0 base
let pathPairs = ListHT.mapAdjacent (,) $ map tmpPath [0 .. height]
forM_ pathPairs $ \(src,dst) ->
next fleet dst =<< CountMap.readFile src
fmap (countBoundedFromMap fleet) $ CountMap.readFile $ tmpPath height
countExternalReturn ::
Nat w => (Size w, Int) -> Fleet.T -> IO Count
countExternalReturn (width, height) =
countExternalGen (baseCase width) (nextFrontierBoundedExternal width) height
reportCounts ::
(Counter.C a, Storable a, Show a) =>
CountMap w ->
(Fleet.T -> CountMap.Path w a -> CountMap.T w a -> IO ()) ->
Int -> Fleet.T -> IO ()
reportCounts base next height fleet = do
writeTmpCountMap 0 base
let pathPairs = ListHT.mapAdjacent (,) $ map tmpPath [0 .. height]
forM_ pathPairs $ \(src,dst) -> do
next fleet dst =<< CountMap.readFile src
print . countBoundedFromMap fleet =<< CountMap.readFile dst
countExternal :: IO ()
countExternal =
let width = n10
height = 10
in reportCounts
(baseCase width) (nextFrontierBoundedExternal width)
height Fleet.german
countFleets :: IO ()
countFleets =
Fold.mapM_ putStrLn .
Map.mapWithKey
(\fleet cnt ->
"|-\n| " ++
intercalate " || "
(map ((\n -> if n==0 then " " else show n) . Fleet.lookup fleet) [2..5]
++ [show cnt])) .
Map.filterWithKey (\fleet _cnt -> Fleet.subset fleet Fleet.german) .
countBoundedFleetsFromMap =<<
CountMap.readFile (tmpPath 10)
printMapSizes :: IO ()
printMapSizes =
mapM_ (print . CountMap.size) $
iterate (nextFrontierBounded n10 Fleet.german) $
baseCase n10
genShip :: QC.Gen Fleet.ShipSize
genShip = QC.choose (1, maxShipSize)
genFleet :: QC.Gen Fleet.T
genFleet = fmap Fleet.fromSizes $ flip QC.vectorOf genShip =<< QC.choose (0,4)
propCountSymmetry :: QC.Property
propCountSymmetry =
QC.forAllShrink genFleet QC.shrink $ \fleet ->
let d =
case mod (sum $ map (uncurry (*)) $ Fleet.toList fleet) 4 of
0 -> 1
2 -> 2
_ ->
if any odd $ map (uncurry (*)) $ Fleet.toList fleet
then 8
else 4
in mod (Counter.toInteger $ countBounded (n6,6) fleet) d == 0
propCountTransposed :: QC.Property
propCountTransposed =
QC.forAllShrink (QC.choose (0,4)) QC.shrink $ \width ->
QC.forAllShrink (QC.choose (0,8)) QC.shrink $ \height ->
QC.forAllShrink genFleet QC.shrink $ \fleet ->
Size.reifyInt width $ \w ->
Size.reifyInt height $ \h ->
countBounded (w,height) fleet == countBounded (h,width) fleet
propCountBounded :: QC.Property
propCountBounded =
QC.forAllShrink (QC.choose (0,4)) QC.shrink $ \width ->
QC.forAllShrink (QC.choose (0,10)) QC.shrink $ \height ->
QC.forAllShrink genFleet QC.shrink $ \fleet ->
Size.reifyInt width $ \w ->
count (w,height) fleet == countBounded (w,height) fleet
propCountTouchingTransposed :: QC.Property
propCountTouchingTransposed =
QC.forAllShrink (QC.choose (0,4)) QC.shrink $ \width ->
QC.forAllShrink (QC.choose (0,6)) QC.shrink $ \height ->
Size.reifyInt width $ \w ->
Size.reifyInt height $ \h ->
QC.forAllShrink genFleet QC.shrink $ \fleet ->
countTouching (w,height) fleet == countTouching (h,width) fleet
propCountMoreTouching :: QC.Property
propCountMoreTouching =
QC.forAllShrink (QC.choose (0,6)) QC.shrink $ \width ->
QC.forAllShrink (QC.choose (0,10)) QC.shrink $ \height ->
QC.forAllShrink genFleet QC.shrink $ \fleet ->
Size.reifyInt width $ \w ->
countBounded (w,height) fleet <= countTouching (w,height) fleet
propCountExternal :: QC.Property
propCountExternal =
QC.forAllShrink (QC.choose (0,4)) QC.shrink $ \width ->
QC.forAllShrink (QC.choose (0,10)) QC.shrink $ \height ->
QC.forAllShrink genFleet QC.shrink $ \fleet ->
Size.reifyInt width $ \w -> QCM.monadicIO $ do
c <- QCM.run $ countExternalReturn (w,height) fleet
QCM.assert $ count (w,height) fleet == c
propCountTouchingExternal :: QC.Property
propCountTouchingExternal =
QC.forAllShrink (QC.choose (0,4)) QC.shrink $ \width ->
QC.forAllShrink (QC.choose (0,10)) QC.shrink $ \height ->
QC.forAllShrink genFleet QC.shrink $ \fleet ->
Size.reifyInt width $ \w -> QCM.monadicIO $ do
c <- QCM.run $ countTouchingExternalReturn (w,height) fleet
QCM.assert $ countTouching (w,height) fleet == c