The output looks like this:
You should just see a flat, continuous red wall on one side, blue wall on another, green on another, yellow on another (see the definition of the map, testMapTiles, it's just a map with four walls). Yet there are these phantom wall faces of varying height, which are perpendicular to the real walls. Why?
Note that the white "gaps" aren't actually gaps: it's trying to draw a wall of height Infinity (distance 0). If you specifically account for it (this version of the code doesn't) and just cap it at screen height, then you just see a very high wall there.
The source code is below. It's plain Haskell, using Haste to compile to JavaScript and render to canvas. It is based on the C++ code from this tutorial, though note that I replaced mapX and mapY with tileX and tileY, and I don't have the ray prefix for pos and dir within the main loop. Any discrepancies from the C++ code are probably what's breaking everything, but I can't seem to find any after having pored over this code many times.
Any help?
import Data.Array.IArray
import Control.Arrow (first, second)
import Control.Monad (forM_)
import Haste
import Haste.Graphics.Canvas
data MapTile = Empty | RedWall | BlueWall | GreenWall | YellowWall deriving (Eq)
type TilemapArray = Array (Int, Int) MapTile
emptyTilemapArray :: (Int, Int) -> TilemapArray
emptyTilemapArray dim#(w, h) = listArray ((1, 1), dim) $ replicate (w * h) Empty
testMapTiles :: TilemapArray
testMapTiles =
let arr = emptyTilemapArray (16, 16)
myBounds#((xB, yB), (w, h)) = bounds arr
in listArray myBounds $ flip map (indices arr) (\(x, y) ->
if x == xB then RedWall
else if y == yB then BlueWall
else if x == w then GreenWall
else if y == h then YellowWall
else Empty)
type Vec2 a = (a, a)
type DblVec2 = Vec2 Double
type IntVec2 = Vec2 Int
add :: (Num a) => Vec2 a -> Vec2 a -> Vec2 a
add (x1, y1) (x2, y2) = (x1 + x2, y1 + y2)
mul :: (Num a) => Vec2 a -> a -> Vec2 a
mul (x, y) factor = (x * factor, y * factor)
rot :: (Floating a) => Vec2 a -> a -> Vec2 a
rot (x, y) angle =
(x * (cos angle) - y * (sin angle), x * (sin angle) + y * (cos angle))
dbl :: Int -> Double
dbl = fromIntegral
-- fractional part of a float
-- `truncate` matches behaviour of C++'s int()
frac :: Double -> Double
frac d = d - dbl (truncate d)
-- get whole and fractional parts of a float
split :: Double -> (Int, Double)
split d = (truncate d, frac d)
-- stops 'Warning: Defaulting the following constraint(s) to type ‘Integer’'
square :: Double -> Double
square = (^ (2 :: Int))
-- raycasting algorithm based on code here:
-- http://lodev.org/cgtutor/raycasting.html#Untextured_Raycaster_
data HitSide = NorthSouth | EastWest deriving (Show)
-- direction, tile, distance
type HitInfo = (HitSide, IntVec2, Double)
-- pos: start position
-- dir: initial direction
-- plane: camera "plane" (a line, really, perpendicular to the direction)
traceRays :: TilemapArray -> Int -> DblVec2 -> DblVec2 -> DblVec2 -> [HitInfo]
traceRays arr numRays pos dir plane =
flip map [0..numRays] $ \x ->
let cameraX = 2 * ((dbl x) / (dbl numRays)) - 1
in traceRay arr pos $ dir `add` (plane `mul` cameraX)
traceRay :: TilemapArray -> DblVec2 -> DblVec2 -> HitInfo
traceRay arr pos#(posX, posY) dir#(dirX, dirY) =
-- map tile we're in (whole part of position)
-- position within map tile (fractional part of position)
let ((tileX, fracX), (tileY, fracY)) = (split posX, split posY)
tile = (tileX, tileY)
-- length of ray from one x or y-side to next x or y-side
deltaDistX = sqrt $ 1 + (square dirY / square dirX)
deltaDistY = sqrt $ 1 + (square dirX / square dirY)
deltaDist = (deltaDistX, deltaDistY)
-- direction of step
stepX = if dirX < 0 then -1 else 1
stepY = if dirY < 0 then -1 else 1
step = (stepX, stepY)
-- length of ray from current position to next x or y-side
sideDistX = deltaDistX * if dirX < 0 then fracX else 1 - fracX
sideDistY = deltaDistY * if dirY < 0 then fracY else 1 - fracY
sideDist = (sideDistX, sideDistY)
(hitSide, wallTile) = traceRayInner arr step deltaDist tile sideDist
in (hitSide, wallTile, calculateDistance hitSide pos dir wallTile step)
traceRayInner :: TilemapArray -> IntVec2 -> DblVec2 -> IntVec2 -> DblVec2 -> (HitSide, IntVec2)
traceRayInner arr step#(stepX, stepY) deltaDist#(deltaDistX, deltaDistY) tile sideDist#(sideDistX, sideDistY)
-- a wall has been hit, report hit direction and coördinates
| arr ! tile /= Empty = (hitSide, tile)
-- advance until a wall is hit
| otherwise = case hitSide of
EastWest ->
let newSideDist = first (deltaDistX+) sideDist
newTile = first (stepX+) tile
in
traceRayInner arr step deltaDist newTile newSideDist
NorthSouth ->
let newSideDist = second (deltaDistY+) sideDist
newTile = second (stepY+) tile
in
traceRayInner arr step deltaDist newTile newSideDist
where
hitSide = if sideDistX < sideDistY then EastWest else NorthSouth
-- calculate distance projected on camera direction
-- (an oblique distance would give a fisheye effect)
calculateDistance :: HitSide -> DblVec2 -> DblVec2 -> IntVec2 -> IntVec2 -> Double
calculateDistance EastWest (startX, _) (dirX, _) (tileX, _) (stepX, _) =
((dbl tileX) - startX + (1 - dbl stepX) / 2) / dirX
calculateDistance NorthSouth (_, startY) (_, dirY) (_, tileY) (_, stepY) =
((dbl tileY) - startY + (1 - dbl stepY) / 2) / dirY
-- calculate the height of the vertical line on-screen based on the distance
calculateHeight :: Double -> Double -> Double
calculateHeight screenHeight 0 = screenHeight
calculateHeight screenHeight perpWallDist = screenHeight / perpWallDist
width :: Double
height :: Double
(width, height) = (640, 480)
main :: IO ()
main = do
cvElem <- newElem "canvas" `with` [
attr "width" =: show width,
attr "height" =: show height
]
addChild cvElem documentBody
Just canvas <- getCanvas cvElem
let pos = (8, 8)
dir = (-1, 0)
plane = (0, 0.66)
renderGame canvas pos dir plane
renderGame :: Canvas -> DblVec2 -> DblVec2 -> DblVec2 -> IO ()
renderGame canvas pos dir plane = do
let rays = traceRays testMapTiles (floor width) pos dir plane
render canvas $ forM_ (zip [0..width - 1] rays) (\(x, (side, tile, dist)) ->
let lineHeight = calculateHeight height dist
wallColor = case testMapTiles ! tile of
RedWall -> RGB 255 0 0
BlueWall -> RGB 0 255 0
GreenWall -> RGB 0 0 255
YellowWall -> RGB 255 255 0
_ -> RGB 255 255 255
shadedWallColor = case side of
EastWest ->
let (RGB r g b) = wallColor
in RGB (r `div` 2) (g `div` 2) (b `div` 2)
NorthSouth -> wallColor
in color shadedWallColor $ do
translate (x, height / 2) $ stroke $ do
line (0, -lineHeight / 2) (0, lineHeight / 2))
-- 25fps
let fps = 25
timeout = (1000 `div` fps) :: Int
rots_per_min = 1
rots_per_sec = dbl rots_per_min / 60
rots_per_frame = rots_per_sec / dbl fps
tau = 2 * pi
increment = tau * rots_per_frame
setTimeout timeout $ do
renderGame canvas pos (rot dir $ -increment) (rot plane $ -increment)
HTML page:
<!doctype html>
<meta charset=utf-8>
<title>Raycaster</title>
<noscript>If you're seeing this message, either your browser doesn't support JavaScript, or it is disabled for some reason. This game requires JavaScript to play, so you'll need to make sure you're using a browser which supports it, and enable it, to play.</noscript>
<script src=raycast.js></script>
The "phantom faces" are occurring because an incorrect HitSide is being reported: you're saying the face was hit on a horizontal move (EastWest), but was actually hit on a vertical move (NorthSouth), or vice-versa.
Why is it reporting an incorrect value, then? if sideDistX < sideDistY then EastWest else NorthSouth seems pretty foolproof, right? And it is.
The problem isn't how we calculated that value. It's when we calculated that value. The distance calculation function needs to know the direction we moved in to get to the wall. However, what we've actually given is the direction we would move in if we were to keep going (that is, if that tile wasn't a wall, or we were to ignore it for some reason).
Look at the Haskell code:
traceRayInner arr step#(stepX, stepY) deltaDist#(deltaDistX, deltaDistY) tile sideDist#(sideDistX, sideDistY)
-- a wall has been hit, report hit direction and coördinates
| arr ! tile /= Empty = (hitSide, tile)
-- advance until a wall is hit
| otherwise = case hitSide of
EastWest ->
let newSideDist = first (deltaDistX+) sideDist
newTile = first (stepX+) tile
in
traceRayInner arr step deltaDist newTile newSideDist
NorthSouth ->
let newSideDist = second (deltaDistY+) sideDist
newTile = second (stepY+) tile
in
traceRayInner arr step deltaDist newTile newSideDist
where
hitSide = if sideDistX < sideDistY then EastWest else NorthSouth
Notice that we do things in this order:
calculate hitSide
check if a wall has been hit, and if so, report hitSide
move
Compare this to the original C++ code:
//perform DDA
while (hit == 0)
{
//jump to next map square, OR in x-direction, OR in y-direction
if (sideDistX < sideDistY)
{
sideDistX += deltaDistX;
mapX += stepX;
side = 0;
}
else
{
sideDistY += deltaDistY;
mapY += stepY;
side = 1;
}
//Check if ray has hit a wall
if (worldMap[mapX][mapY] > 0) hit = 1;
}
It does things in a different order:
check if a wall has been hit, and if so, report side (equivalent to hitSide)
move and calculate side
The C++ code only calculates side when it moves, and then it reports that value if it hits a wall. So, it reports the way it moved in order to hit the wall.
The Haskell code calculates side whether or not it moves: so it's correct for each move, but when it hits a wall, it reports the way it would have moved were it to keep going.
So, the Haskell code can be fixed by re-ordering it so that it checks for a hit after moving, and if so, reports the hitSide value from that move. This isn't pretty code, but it works:
traceRayInner arr step#(stepX, stepY) deltaDist#(deltaDistX, deltaDistY) tile sideDist#(sideDistX, sideDistY) =
let hitSide = if sideDistX < sideDistY then EastWest else NorthSouth
in case hitSide of
EastWest ->
let newSideDist = first (deltaDistX+) sideDist
newTile = first (stepX+) tile
in case arr ! newTile of
-- advance until a wall is hit
Empty -> traceRayInner arr step deltaDist newTile newSideDist
-- a wall has been hit, report hit direction and coördinates
_ -> (hitSide, newTile)
NorthSouth ->
let newSideDist = second (deltaDistY+) sideDist
newTile = second (stepY+) tile
in case arr ! newTile of
-- advance until a wall is hit
Empty -> traceRayInner arr step deltaDist newTile newSideDist
-- a wall has been hit, report hit direction and coördinates
_ -> (hitSide, newTile)
Problem solved!
Side note: I figured out what was wrong after carrying out the algorithm on paper. While in that particular case it just so happened the last two HitSide values matched, it became obvious that that they might not in every case. So, a big thanks to Madsy on Freenode's #algorithms for suggesting trying it out on paper. :)
Related
I started this function as follows:
type Place = (String, Float, Float, [Int])
distanceList :: Float -> Float-> [Place] -> [Float]
distanceList _ _ [] = []
distanceList degN degE ((location, float1, float2, rainfall):place) =
sqrt((float1-degN)^2 + (float2-degE)^2) : distanceList degN degE place
minDistance :: Float -> Float-> Float -> Float -> [Float] -> Float
minDistance _ _ _ _ [] = 0
minDistance degN degE float1 float2 (x:xs)
| x < minDistance degN degE float1 float2 xs = x
| otherwise = minDistance degN degE float1 float2 xs
closestPlace :: Float -> Float -> [Place] -> String
closestPlace _ _ [] = " An error as occured "
closestPlace degN degE ((location, float1, float2, rainfall):place)
| rainfall !!0 == 0 && pythag == distance = location
| otherwise = closestPlace degN degE place
where
pythag = sqrt((float1-degN)^2 + (float2-degE)^2)
distance = minDistance degN degE float1 float2 (distanceList
degN degE place)
i have test data which is passed through the Place. and the two floats are coordinates north and east, i need to use Pythagoras theorem to return a single String of which location is closest.
The code above runs but when thee closestPlace function runs it never gets passed the first part which is the error message, i just need the function to compare the Pythagorus output of the two functions above to and print the string of the location which is closest to the coordinates inputted.
the code to run this is as follows:
demo :: Int -> IO ()
demo 7 = putStrLn (closestPlace 55.0 (-5.3) testData)
You're pretty much there. As far as calculating the distance goes, one observation can be made:
If the distance to point A is greater than the distance to point B, the square of distance to A will be greater than the square of the distance to B.
This means that instead of comparing distances (and computing a square root unnecessarily), we can compare squares of them, which are calculated like so:
dist2 x1 y1 x2 y2 = (x2-x1)^2 + (y2-y1)^2
However, you also want to extract some additional metadata. Two common approaches are appending the sorting key and stripping it after, or using the comparison function directly. Here, the second approach will work quite well:
closestPlace :: Float -> Float -> [Place] -> Place
closestPlace x y = minimumBy (comparing (dist2P x y))
I've added a helper here called dist2P that allows us to compare a pair of points to a place directly; this is convenient, because we can then use comparing to automatically apply that on a pair of points that is then used by minimumBy to find the closest point.
dist2P :: Float -> Float -> Place -> Float
dist2P x y (_, x', y', _) = dist x y x' y'
That helper then gets partially applied with the source point.
Thanks to minimumBy we're also able to eta-reduce closestPlace, which is always nice.
And finally, I've decided to change the signature of your function to return Place instead of String. Why? Well, if it turns out you need any other information from the place, you can easily access it with a getter like so:
placeName :: Place -> String
placeName (s, _, _, _) = s
And similarly, your original function would thus be implemented as a composition of the two:
closestPlaceName :: Float -> Float -> [Place] -> String
closestPlaceName x y = placeName . closestPlace x y
I'm trying to make what I think is called an Ulam spiral using Haskell.
It needs to go outwards in a clockwise rotation:
6 - 7 - 8 - 9
| |
5 0 - 1 10
| | |
4 - 3 - 2 11
|
..15- 14- 13- 12
For each step I'm trying to create coordinates, the function would be given a number and return spiral coordinates to the length of input number eg:
mkSpiral 9
> [(0,0),(1,0),(1,-1),(0,-1),(-1,-1),(-1,0),(-1,1),(0,1),(1,1)]
(-1, 1) - (0, 1) - (1, 1)
|
(-1, 0) (0, 0) - (1, 0)
| |
(-1,-1) - (0,-1) - (1,-1)
I've seen Looping in a spiral solution, but this goes counter-clockwise and it's inputs need to the size of the matrix.
I also found this code which does what I need but it seems to go counterclock-wise, stepping up rather than stepping right then clockwise :(
type Spiral = Int
type Coordinate = (Int, Int)
-- number of squares on each side of the spiral
sideSquares :: Spiral -> Int
sideSquares sp = (sp * 2) - 1
-- the coordinates for all squares in the given spiral
coordinatesForSpiral :: Spiral -> [Coordinate]
coordinatesForSpiral 1 = [(0, 0)]
coordinatesForSpiral sp = [(0, 0)] ++ right ++ top ++ left ++ bottom
where fixed = sp - 1
sides = sideSquares sp - 1
right = [(x, y) | x <- [fixed], y <- take sides [-1*(fixed-1)..]]
top = [(x, y) | x <- reverse (take sides [-1*fixed..]), y <- [fixed]]
left = [(x, y) | x <- [-1*fixed], y <- reverse(take sides [-1*fixed..])]
bottom = [(x, y) | x <- take sides [-1*fixed+1..], y <- [-1*fixed]]
-- an endless list of coordinates (the complete spiral)
mkSpiral :: Int -> [Coordinate]
mkSpiral x = take x endlessSpiral
endlessSpiral :: [Coordinate]
endlessSpiral = endlessSpiral' 1
endlessSpiral' start = coordinatesForSpiral start ++ endlessSpiral' (start + 1)
After much experimentation I can't seem to change the rotation or starting step direction, could someone point me in the right way or a solution that doesn't use list comprehension as I find them tricky to decode?
Let us first take a look at how the directions of a spiral are looking:
R D L L U U R R R D D D L L L L U U U U ....
We can split this in sequences like:
n times n+1 times
_^_ __^__
/ \ / \
R … R D … D L L … L U U … U
\_ _/ \__ __/
v v
n times n+1 times
We can repeat that, each time incrementing n by two, like:
data Dir = R | D | L | U
spiralSeq :: Int -> [Dir]
spiralSeq n = rn R ++ rn D ++ rn1 L ++ rn1 U
where rn = replicate n
rn1 = replicate (n + 1)
spiral :: [Dir]
spiral = concatMap spiralSeq [1, 3..]
Now we can use Dir here to calculate the next coordinate, like:
move :: (Int, Int) -> Dir -> (Int, Int)
move (x, y) = go
where go R = (x+1, y)
go D = (x, y-1)
go L = (x-1, y)
go U = (x, y+1)
We can use scanl :: (a -> b -> a) -> a -> [b] -> [a] to generate the points, like:
spiralPos :: [(Int, Int)]
spiralPos = scanl move (0,0) spiral
This will yield an infinite list of coordinates for the clockwise spiral. We can use take :: Int -> [a] -> [a] to take the first k items:
Prelude> take 9 spiralPos
[(0,0),(1,0),(1,-1),(0,-1),(-1,-1),(-1,0),(-1,1),(0,1),(1,1)]
The idea with the following solution is that instead of trying to generate the coordinates directly, we’ll look at the directions from one point to the next. If you do that, you’ll notice that starting from the first point, we go 1× right, 1× down, 2× left, 2× up, 3× right, 3× down, 4× left… These can then be seperated into the direction and the number of times repeated:
direction: > v < ^ > v < …
# reps: 1 1 2 2 3 3 4 …
And this actually gives us two really straightforward patterns! The directions just rotate > to v to < to ^ to >, while the # of reps goes up by 1 every 2 times. Once we’ve made two infinite lists with these patterns, they can be combined together to get an overall list of directions >v<<^^>>>vvv<<<<…, which can then be iterated over to get the coordinate values.
Now, I’ve always thought that just giving someone a bunch of code as the solution is not the best way to learn, so I would highly encourage you to try implementing the above idea yourself before looking at my solution below.
Welcome back (if you did try to implement it yourself). Now: onto my own solution. First I define a Stream data type for an infinite stream:
data Stream a = Stream a (Stream a) deriving (Show)
Strictly speaking, I don’t need streams for this; Haskell’s predefined lists are perfectly adequate for this task. But I happen to like streams, and they make some of the pattern matching a bit easier (because I don’t have to deal with the empty list).
Next, I define a type for directions, as well as a function specifying how they interact with points:
-- Note: I can’t use plain Left and Right
-- since they conflict with constructors
-- of the ‘Either’ data type
data Dir = LeftDir | RightDir | Up | Down deriving (Show)
type Point = (Int, Int)
move :: Dir -> Point -> Point
move LeftDir (x,y) = (x-1,y)
move RightDir (x,y) = (x+1, y)
move Up (x,y) = (x,y+1)
move Down (x,y) = (x,y-1)
Now I go on to the problem itself. I’ll define two streams — one for the directions, and one for the number of repetitions of each direction:
dirStream :: Stream Dir
dirStream = Stream RightDir $ Stream Down $ Stream LeftDir $ Stream Up dirVals
numRepsStream :: Stream Int
numRepsStream = go 1
where
go n = Stream n $ Stream n $ go (n+1)
At this point we’ll need a function for replicating each element of a stream a specific number of times:
replicateS :: Stream Int -> Stream a -> Stream a
replicateS (Stream n ns) (Stream a as) = conss (replicate n a) $ replicateS ns as
where
-- add more than one element to the beginning of a stream
conss :: [a] -> Stream a -> Stream a
conss [] s = s
conss (x:xs) s = Stream x $ appends xs s
This gives replicateS dirStream numRepsStream for the stream of directions. Now we just need a function to convert those directions to coordinates, and we’ve solved the problem:
integrate :: Stream Dir -> Stream Point
integrate = go (0,0)
where
go p (Stream d ds) = Stream p (go (move d p) ds)
spiral :: Stream Point
spiral = integrate $ replicateS numRepsStream dirStream
Unfortunately, it’s somewhat inconvenient to print an infinite stream, so the following function is useful for debugging and printing purposes:
takeS :: Int -> Stream a -> [a]
takeS 0 _ = []; takeS n (Stream x xs) = x : (takeS (n-1) xs)
I want to take two different images (taken from image files, like .png) and draw one over the other several times in different positions. The resulting image should be presented on screen or generate a new image file, whichever is easier. I´ll be taking that new image and drawing on it more with further operations
Is there any Haskell library that allows me to do this?
You can use JuicyPixels to do that sort of thing:
module Triangles where
import Codec.Picture
import LineGraphics
{-| Parameterize color smoothly as a function of angle -}
colorWheel :: Float -> Colour
colorWheel x = (r, g, b, a)
where
r = floor $ (cos x + 1) * (255 / 2)
g = floor $ (sin x + 1) * (255 / 2)
b = floor $ (cos (x+(pi/2)) + 1) * (255 / 2)
a = 255
{-| Draw a triangle centered about the point (x, y) -}
triangle :: Point -> Path
triangle (x, y) =
[ (x - k, y - k)
, (x + k, y - k)
, (x, y + k)
, (x - k, y - k)
]
where
size = 30
k = size / 2
{-|
Draw 'n' equally-spaced triangles at a radius of 'r' about a center
point, '(x, y)'.
-}
triangles :: Float -> Radius -> Vector -> Picture
triangles n r (x, y) =
[ (colorWheel theta, tri theta) | theta <- steps n ]
where
tri theta = triangle ((r * cos theta) + x, (r * sin theta) + y)
{-| Interpolate the range [0, 2pi] by 'n' steps -}
steps :: Float -> [Float]
steps n = map (\i -> i * (2*pi/n)) [0 .. n]
And we'll use this module of supporting code:
module LineGraphics (
Point, Vector, Line, Path, Picture, Colour, Radius,
black,
drawPicture,
) where
import Graphics.Rasterific hiding (Point, Vector, Line, Path, polygon)
import Graphics.Rasterific.Texture
import Codec.Picture
type Radius = Float
type Point = (Float, Float)
type Vector = (Float, Float)
type Line = (Point, Point)
type Path = [Point]
type Picture = [(Colour, Path)]
type Colour = (Int, Int, Int, Int) -- red, green, blue, opacity
black = (0, 0, 0, 255)
drawPicture :: Float -> Picture -> Image PixelRGBA8
drawPicture linewidth picture =
renderDrawing 800 800 (toColour black) $
mapM_ renderFn picture
where
renderFn (col, path) = withTexture (uniformTexture $ toColour col) (drawPath path)
drawPath points = stroke linewidth JoinRound (CapRound, CapStraight 0) $
polyline (map (\(x, y) -> V2 x y) points)
toColour (a,b,c,d) = PixelRGBA8
(fromIntegral a) (fromIntegral b) (fromIntegral c) (fromIntegral d)
And here's what we get:
I've written some code that's meant to integrate a function numerically using the trapezoidal rule. It works, but the answer it produces has a wrong sign. Why might that be?
The code is:
integration :: (Double -> Double) -> Double -> Double -> Double
integration f a b = h * (f a + f b + partial_sum)
where
h = (b - a) / 1000
most_parts = map f (points (1000-1) h)
partial_sum = sum most_parts
points :: Double -> Double -> [Double]
points x1 x2
| x1 <= 0 = []
| otherwise = (x1*x2) : points (x1-1) x2
Trapezoidal rule
The code is probably inelegant, but I'm only a student of Haskell and would like to deal with the current problem first and coding style matters after that.
Note: This answer is written in literate Haskell. Save it with .lhs as extension and load it in GHCi to test the solution.
Finding the culprit
First of all, let's take a look at integration. In its current form, it contains only summation of function values f x. Even though the factors aren't correct at the moment, the overall approach is fine: you evaluate f at the grid points. However, we can use the following function to verify that there's something wrong:
ghci> integration (\x -> if x >= 10 then 1 else (-1)) 10 15
-4.985
Wait a second. x isn't even negative in [10,15]. This suggests that you use the wrong grid points.
Grid points revisited
Even though you've linked the article, let's have a look at an exemplary use of the trapezoidal rule (public domain, original file by Oleg Alexandrov):
Although this doesn't use a uniform grid, let's suppose that the 6 grid points are equidistant with grid distance h = (b - a) / 5. What are the x coordinates of those points?
x_0 = a + 0 * h (== a)
x_1 = a + 1 * h
x_2 = a + 2 * h
x_3 = a + 3 * h
x_4 = a + 4 * h
x_5 = a + 5 * h (== b)
If we use set a = 10 and b = 15 (and therefore h = 1), we should end up with [10, 11, 12, 13, 14, 15]. Let's check your points. In this case, you would use points 5 1 and end up with [5,4,3,2,1].
And there's the error. points doesn't respect the boundary. We can easily fix this by using pointsWithOffset:
> points :: Double -> Double -> [Double]
> points x1 x2
> | x1 <= 0 = []
> | otherwise = (x1*x2) : points (x1-1) x2
>
> pointsWithOffset :: Double -> Double -> Double -> [Double]
> pointsWithOffset x1 x2 offset = map (+offset) (points x1 x2)
That way, we can still use your current points definition to generate grid points from x1 to 0 (almost). If we use integration with pointsWithOffset, we end up with
integration :: (Double -> Double) -> Double -> Double -> Double
integration f a b = h * (f a + f b + partial_sum)
where
h = (b - a) / 1000
most_parts = map f (pointsWithOffset (1000-1) h a)
partial_sum = sum most_parts
Tying up loose ends
However, this doesn't take into account that you use all inner points twice in the trapezoid rule. If we add the factors, we end up with
> integration :: (Double -> Double) -> Double -> Double -> Double
> integration f a b =
> h / 2 * (f a + f b + 2 * partial_sum)
> -- ^^^ ^^^
> where
> h = (b - a) / 1000
> most_parts = map f (pointsWithOffset (1000-1) h a)
> partial_sum = sum most_parts
Which yields the correct value for our test function above.
Exercise
Your current version only supports 1000 grid points. Add an Int argument so that one can change the number of grid points:
integration :: Int -> (Double -> Double) -> Double -> Double -> Double
integration n f a b = -- ...
Furthermore, try to write points in different ways, for example go from a to b, use takeWhile and iterate, or even a list comprehension.
Yes it indeed was the points plus you had some factors wrong (the inner points are multiplied by 2) - this is the fixed version of your code:
integration :: (Double -> Double) -> Double -> Double -> Double
integration f a b = h * (f a + f b + innerSum) / 2
where
h = (b - a) / 1000
innerPts = map ((2*) . f . (a+)) (points (1000-1) h)
innerSum = sum innerPts
points :: Double -> Double -> [Double]
points i x
| i <= 0 = []
| otherwise = (i*x) : points (i-1) x
which gives sensible approximations (to 1000 points):
λ> integration (const 2) 1 2
2.0
λ> integration id 1 2
1.5
λ> integration (\x -> x*x) 1 2
2.3333334999999975
λ> 7/3
2.3333333333333335
During last three days I have been trying to solve Project Euler 15 in Haskell.
Here is my current state:
import Data.Map as Map
data Coord = Coord Int Int deriving (Show, Ord, Eq)
corner :: Coord -> Bool
corner (Coord x y) = (x == 0) && (y == 0)
side :: Coord -> Bool
side (Coord x y) = (x == 0) || (y == 0)
move_right :: Coord -> Coord
move_right (Coord x y) = Coord (x - 1) y
move_down :: Coord -> Coord
move_down (Coord x y) = Coord x (y - 1)
calculation :: Coord -> Integer
calculation coord
| corner coord = 0
| side coord = 1
| otherwise = (calculation (move_right coord)) + (calculation (move_down coord))
problem_15 :: Int -> Integer
problem_15 size =
calculation (Coord size size)
It works fine but it is very slow if the 'n' is getting bigger.
As I know I can use the dynamic programming and the hashtable (Data.Map, for example) to cache calculated values.
I was trying to use memoization, but don't have a success. I was trying to use Data.Map, but each next error was more scary then previous. So I ask your help: how to cache values which was already calculated ?
I know about mathematical solution of this problem (Pascal triangle), but I am interested in the algorithmic solution.
Instead of a Map, this problem is better suited for an two-dimensional array cache, since we have a bounded range for input values.
import Control.Applicative
import Data.Array
data Coord = Coord Int Int deriving (Show, Ord, Eq, Ix)
calculation :: Coord -> Integer
calculation coord#(Coord maxX maxY) = cache ! coord where
cache = listArray bounds $ map calculate coords
calculate coord
| corner coord = 0
| side coord = 1
| otherwise = cache ! move_right coord + cache ! move_down coord
zero = Coord 0 0
bounds = (zero, coord)
coords = Coord <$> [0..maxX] <*> [0..maxY]
We add deriving Ix to Coord so we can use it directly as an array index and in calculation, we initialize a two-dimensional array cache with the lower bound of Coord 0 0 and upper bound of coord. Then instead of recursively calling calculation we just refer to the values in the cache.
Now we can calculate even large values relatively quickly.
*Main> problem_15 1000
2048151626989489714335162502980825044396424887981397033820382637671748186202083755828932994182610206201464766319998023692415481798004524792018047549769261578563012896634320647148511523952516512277685886115395462561479073786684641544445336176137700738556738145896300713065104559595144798887462063687185145518285511731662762536637730846829322553890497438594814317550307837964443708100851637248274627914170166198837648408435414308177859470377465651884755146807496946749238030331018187232980096685674585602525499101181135253534658887941966653674904511306110096311906270342502293155911108976733963991149120
Since you already know the correct (efficient) solution, I'm not spoiling anything for you:
You can use an array (very appropriate here, since the domain is a rectangle)
import Data.Array
pathCounts :: Int -> Int -> Array (Int,Int) Integer
pathCounts height width = solution
where
solution =
array ((0,0),(height-1,width-1)) [((i,j), count i j) | i <- [0 .. height-1]
, j <- [0 .. width-1]]
count 0 j = 1 -- at the top, we can only come from the left
count i 0 = 1 -- on the left edge, we can only come from above
count i j = solution ! (i-1,j) + solution ! (i,j-1)
Or you can use the State monad (the previously calculated values are the state, stored in a Map):
import qualified Data.Map as Map
import Control.Monad.State.Strict
type Path = State (Map Coord Integer)
calculation :: Coord -> Path Integer
calculation coord = do
mb_count <- gets (Map.lookup coord)
case mb_count of
Just count -> return count
Nothing
| corner coord -> modify (Map.insert coord 0) >> return 0 -- should be 1, IMO
| side coord -> modify (Map.insert coord 1) >> return 1
| otherwise -> do
above <- calculation (move_down coord)
left <- calculation (move_right coord)
let count = above + left
modify (Map.insert coord count)
return count
and run that with
evalState (calculation target) Map.empty
Or you can use one of the memoisation packages on hackage, off the top of my head I remember data-memocombinators, but there are more, possibly some even better. (And there are still more possible ways of course.)