module Data.ShadowBox.Internal where
import Prelude (($),Int,Bool (..),(&&),(||),maybe,(==),otherwise,(),(+),(<),(>),(>=),(<=)
,(<$>),const,String,Maybe
,show,Either (..))
import Data.Array.BitArray (BitArray,(!))
import qualified Data.Array.BitArray as BitArray
import Data.Monoid
addModelToWorld :: Int -> Int -> ShadowModel -> World -> Either String World
addModelToWorld x y sm w = addPatchToWorld <$> makePatchable x y sm w
newtype ShadowModel = ShadowModel {_unshadowModel :: BitArray (Int,Int)}
showShadowBoxModel :: ShadowModel -> String
showShadowBoxModel (ShadowModel m) = mconcat $ convertDirectly
where
((_,_),(maxX,maxY)) = BitArray.bounds m
convertDirectly = [convertToChar x y (m!(x,y)) | x <-[0..maxX] , y <- [0.. maxY]]
convertToChar _ y c = case c of
True -> " " <> "X" <> " " <> finish
False -> " " <> "_" <> " " <> finish
where
finish
|y == maxY = "\n"
|otherwise = ""
shadowRect :: Int -> Int -> ShadowModel
shadowRect width height = ShadowModel $ BitArray.fill ((0,0), (width 1, height 1) ) True
showWorld :: World -> String
showWorld (World m) = mconcat $ convertDirectly
where
((_,_),(maxX,maxY)) = BitArray.bounds m
convertDirectly = [convertToChar x y (m!(x,y)) | x <-[0..maxX] , y <- [0.. maxY]]
convertToChar _ y c = case c of
True -> " " <> "X" <> " " <> finish
False -> " " <> "_" <> " " <> finish
where
finish
|y == maxY = "\n"
|otherwise = ""
newtype World = World { _unWorldShadow :: BitArray (Int,Int)}
(!?) :: World -> (Int, Int) -> Maybe Bool
val !? ix = ba BitArray.!? ix
where
(World ba) = val
emptyWorld :: Int -> Int -> World
emptyWorld width height = World $ BitArray.fill ((0,0), (width 1 ,height 1 ) ) False
data Patchable = Patchable {
_ix :: !Int
, _iy :: !Int
, _shadow :: ShadowModel
, _world :: World}
makePatchable :: Int -> Int -> ShadowModel -> World -> Either String Patchable
makePatchable xOrig yOrig s@(ShadowModel sm) w@(World world) = makePatchableFinal
where
upperXBoundOfTranslation = shadowX + xOrig
upperYBoundOfTranslation = shadowY + yOrig
((_,_) , (shadowX,shadowY)) = BitArray.bounds sm
((_,_) , (maxWorldX,maxWorldY)) = BitArray.bounds world
width = maxWorldX + 1
height = maxWorldY + 1
overlap = const ( BitArray.or $ transformedWorld ) <$> boundsCheck
eoverlap
| (Right True) == overlap = Left "Overlap found or out of bounds"
| otherwise = overlap
makePatchableFinal = (const $ Patchable xOrig yOrig s w) <$> eoverlap
transformedWorld = BitArray.ixmap ((0,0),(shadowX,shadowY)) transform twobitArray
forceOverlapError = trueIdx
transform i@(x',y') = maybe forceOverlapError readWorldValue ( world BitArray.!? (xOrig + x' , yOrig + y') )
where
readWorldValue val = if val && (sm!i)
then trueIdx
else falseIdx
boundsCheck
| (upperXBoundOfTranslation > width) || (upperYBoundOfTranslation > height) = Left $ "bounds exceeded upperX:" <> (show upperXBoundOfTranslation) <> " width:" <> (show width) <>
"bounds exceeded upperY:" <> (show upperYBoundOfTranslation) <> " height:" <> (show height)
| (width <= 0) || (height <= 0) = Left "Max World must be greater than zero in both dimensions"
| (xOrig < 0) || (yOrig < 0) = Left "Shadow coordinates must be greater than zero"
| (xOrig > width) || (yOrig > height) = Left $ "x-origin must be less than " <> (show width) <> " y-origin less than " <> (show height)
| otherwise = Right ()
addPatchToWorld :: Patchable
-> World
addPatchToWorld (Patchable x y (ShadowModel sm) (World world)) = assembleWorld
where
((_,_) , (shadowX,shadowY)) = BitArray.bounds sm
((_,_),(width,height)) = BitArray.bounds world
upperXBoundOfTranslation = (shadowX + x)
upperYBoundOfTranslation = shadowY + y
transform i = maybe (readWorldValue i) readShadowValue (sm BitArray.!? (translate i) )
assembleWorld = (World $ BitArray.ixmap ((0,0), (width, height)) transform twobitArray)
translate (xFromWorld,yFromWorld)
|(xFromWorld <= upperXBoundOfTranslation ) && (xFromWorld >= x) &&
(yFromWorld <= upperYBoundOfTranslation ) && (yFromWorld >= y) = (xFromWorld x, yFromWorld y)
| otherwise = (shadowX + 1, shadowY + 1)
readShadowValue val = if val
then trueIdx
else falseIdx
readWorldValue i = if world!i
then trueIdx
else falseIdx
trueIdx :: (Int,Int)
trueIdx = (0,0)
falseIdx:: (Int,Int)
falseIdx = (0,1)
twobitArray :: BitArray (Int, Int)
twobitArray = BitArray.array (trueIdx,falseIdx) [(trueIdx, True), (falseIdx,False)]