Safe Haskell | None |
---|---|
Language | Haskell98 |
In this approach I construct the board row by row from the bottom to the top. In every step I maintain the necessary information in order to know, what ships and positions and orientations are allowed in the next row. This information is stored in the Frontier.
possible optimization: "meet in the middle" compute counts for 5x10 boards and put them together, problem: for a given frontier there are many other half boards that may match
Synopsis
- type Count = Composed Word64 Word64
- type CountMap w = T w Count
- type CountMapPath w = Path w Count
- baseCase :: Size w -> CountMap w
- asumTakeFrontier :: (Nat w, Alternative f) => T w -> Position -> Size w -> [f a] -> f a
- widthRange :: Nat w => Size w -> [Int]
- atEnd :: Size w -> Int -> Bool
- maxShipSize :: ShipSize
- guardCumulativeSubset :: T -> StateT (T w, T) [] ()
- newShip :: T -> T -> ShipSize -> StateT (T w, T) [] ()
- insertVertical :: Nat w => T -> Int -> Position -> StateT (T w, T) [] ()
- nextFrontier :: Nat w => Size w -> CountMap w -> CountMap w
- transitionFrontier :: Nat w => Size w -> T w -> T -> [(T w, T)]
- count :: Nat w => (Size w, Int) -> T -> Count
- nextFrontierBounded :: Nat w => Size w -> T -> CountMap w -> CountMap w
- nextFrontierBoundedExternal :: Nat w => Size w -> T -> CountMapPath w -> CountMap w -> IO ()
- transitionFrontierBounded :: Nat w => Size w -> T -> T w -> T -> [(T w, T)]
- countBounded :: Nat w => (Size w, Int) -> T -> Count
- nextFrontierTouching :: Nat w => Size w -> T -> CountMap w -> CountMap w
- nextFrontierTouchingExternal :: Nat w => Size w -> T -> CountMapPath w -> CountMap w -> IO ()
- transitionFrontierTouching :: Nat w => Size w -> T -> T w -> T -> [(T w, T)]
- countTouching :: Nat w => (Size w, Int) -> T -> Count
- canonicalFrontier :: Nat w => T w -> T w
- mergeSymmetricFrontiers :: Nat w => [(T w, fleet)] -> [(T w, fleet)]
- fleetAtFrontier :: T w -> T
- addFrontierFleet :: T w -> T -> T
- countBoundedFromMap :: (C a, Storable a) => T -> T w a -> a
- countBoundedFleetsFromMap :: CountMap w -> Map T Integer
- countBoundedFleetsFromMap_ :: CountMap w -> Map T Integer
- countSingleKind :: IO ()
- count8x8 :: IO ()
- countTouchingExternalReturn :: Nat w => (Size w, Int) -> T -> IO Count
- count10x10 :: IO ()
- countStandard :: IO ()
- bucketSize :: Int
- tmpPath :: Int -> Path w a
- writeTmpCountMap :: Int -> CountMap w -> IO ()
- writeTmps :: IO ()
- countExternalGen :: (C a, Storable a) => CountMap w -> (T -> Path w a -> T w a -> IO ()) -> Int -> T -> IO a
- countExternalReturn :: Nat w => (Size w, Int) -> T -> IO Count
- reportCounts :: (C a, Storable a, Show a) => CountMap w -> (T -> Path w a -> T w a -> IO ()) -> Int -> T -> IO ()
- countExternal :: IO ()
- countFleets :: IO ()
- printMapSizes :: IO ()
- genShip :: Gen ShipSize
- genFleet :: Gen T
- propCountSymmetry :: Property
- propCountTransposed :: Property
- propCountBounded :: Property
- propCountTouchingTransposed :: Property
- propCountMoreTouching :: Property
- propCountExternal :: Property
- propCountTouchingExternal :: Property
Documentation
type CountMapPath w = Path w Count Source #
count all possible fleets on a board with given width
asumTakeFrontier :: (Nat w, Alternative f) => T w -> Position -> Size w -> [f a] -> f a Source #
nextFrontier :: Nat w => Size w -> CountMap w -> CountMap w Source #
In this approach, the fleet contains all ships also the ones at the frontier.
count fleets with an upper bound
nextFrontierBounded :: Nat w => Size w -> T -> CountMap w -> CountMap w Source #
Here we save memory and speed up the computation in the following way: We stop searching deeper if
- the fleet becomes larger than the requested fleet ("larger" means, that for at least one ship size the number of ships is larger than in the requested fleet)
- the cumulated fleet becomes larger than the cumulated requested fleet This is necessary, since we do not know the final length of the vertical ships at the frontier.
In this approach, the fleet does not contain the vertical ships at the frontier.
nextFrontierBoundedExternal :: Nat w => Size w -> T -> CountMapPath w -> CountMap w -> IO () Source #
nextFrontierTouching :: Nat w => Size w -> T -> CountMap w -> CountMap w Source #
This solves a different problem. In this variant the ships are allowed to touch each other.
nextFrontierTouchingExternal :: Nat w => Size w -> T -> CountMapPath w -> CountMap w -> IO () Source #
fleetAtFrontier :: T w -> T Source #
retrieve counts from count maps
countSingleKind :: IO () Source #
countStandard :: IO () Source #
bucketSize :: Int Source #
countExternalGen :: (C a, Storable a) => CountMap w -> (T -> Path w a -> T w a -> IO ()) -> Int -> T -> IO a Source #
reportCounts :: (C a, Storable a, Show a) => CountMap w -> (T -> Path w a -> T w a -> IO ()) -> Int -> T -> IO () Source #
countExternal :: IO () Source #
countFleets :: IO () Source #
printMapSizes :: IO () Source #