Yampa Particle Field - haskell

I want to have a particle field in Yampa. The single particle should just move in a straight line, but depending on an angle given. That angle and movement speed changes depending on the player's speed and angle. I don't know how better to explain, I'm developing something similar to this game.
Anyway, my code for now looks like this:
star :: (Float, Float) -> SF (Float, Float) (Float, Float)
star p0 = proc (vel, a) -> do
rec
v <- integral -< vel *^ (cos a, sin a)
p <- clampS ^<< (p0 ^+^) ^<< integral -< v ^+^ p
returnA -< p
clampS s#(x, y) | x > 1 = (x-2, y)
| x < (-1) = (x+2, y)
| y > 1 = (x, y-2)
| y < (-1) = (x, y+2)
| otherwise = s
vel is the current speed, a is the current angle. But the particles move in, well, strange ways. (Full code here
Unfortunately, I am sure I am thinking in a wrong way, but I have not yet been able to figure out how to do that, especially how using integral correctly.
Maybe someone can give me some hints.

With the little hint from #martingw, I was able to cook up this, which is quite what I was looking for:
star :: (Float, Float) -> SF (Float, Float) (Float, Float)
star p0 = proc (a, vel) -> do
let (vx,vy) = vel *^ (cos a, sin a)
p <- clampS ^<< (p0 ^+^) ^<< integral -< (-vx,vy)
returnA -< p
clampS (x, y) = (x `fMod` 800, y `fMod` 600)

Related

Foldl with lambda expresion

Hi I'm trying to sum a list of tuples into a tuple with the foldl function,
I tryed it with using as parameter a lambda expresion but it's giving out a wrong value
here the code:
data Point = Point {x,y :: Float}
sumPoint :: [Point] -> (Float,Float)
sumPoint xs = foldl (\(a,b) x-> (0+a,0+b)) (0.0,0.0) xs
It should come out sumPoint [Point 2 4, Point 1 2, Point (-1) (-2)] = (2.0,4.0)
But im getting (0.0,0.0)
How is this making any sense?
To be a little structural you better define operations among Point type values and then convert the Point type to Tuple wherever needed. Otherwise you may directly use Tuple and discard the Point type.
data Point = Point {x,y :: Float} deriving Show
toTuple :: Point -> (Float, Float)
toTuple p = (x p, y p)
addPts :: Point -> Point -> Point
addPts p q = Point (x p + x q) (y p + y q)
sumPts :: [Point] -> Point
sumPts = foldl addPts (Point 0 0)
So what you need is toTuple . sumPts function.
*Main> :t toTuple . sumPts
toTuple . sumPts :: [Point] -> (Float, Float)
I changed it to
sumPoint xs = foldl (\(a,b) (Point x y)-> (x+a,y+b)) (0.0,0.0) xs
The problem was I was ignoring the x and at 0+a is nothing happening.

Haskell Data types with context

I want to write base implementation for Vertex.
data Point a = Point a a
class XY c where
x :: c a -> a
y :: c a -> a
class XY c => Vertex c where
translate :: c a -> c a -> c a
scale :: a -> c a -> c a
rotate :: a -> c a -> c a
instance XY Point where
x (Point first second) = first
y (Point first second) = second
instance Vertex Point where
translate xy1 xy2 = Point (x xy1 + x xy2) (y xy1 + y xy2)
scale a xy = Point ((*a) $ x xy) ((*a) $ y xy)
rotate a xy = Point (x * cosA - y * sinA) (x * sinA + y * cosA) where
cosA = cos a
sinA = sin a
I have to create instance of typeclass Vertex with implementation of Floating typeclass in Point type parameter.
If i implement it like instance (Floating a) => Vertex Point a where i get:
Expected kind ‘* -> Constraint’,
but ‘Vertex Point’ has kind ‘Constraint’
What is the correct way to write it in Haskell?
Aww. This well-known problem is a pet peeve of mine. The correct™ solution is to make the XY and Point classes not for parametric types. The scalar argument becomes an associated type synonym, and everything works easily:
{-# LANGUAGE TypeFamilies #-}
class XY p where
type Component p :: *
x :: p -> Component p
y :: p -> Component p
class XY p => Vertex p where
translate :: p -> p -> p
scale :: Component p -> p -> p
rotate :: Component p -> p -> p
N.B. In fact you could even consider simplifying this to always use the same component type, since you'll likely never need anything else:class XY p where
x :: p -> Double
y :: p -> Double
class XY p => Vertex p where
translate :: p -> p -> p
scale :: Double -> p -> p
rotate :: Double -> p -> p
With the non-parametric form, you can now easily add a number-type constraint exactly where it's needed, namely in the instance Vertex Point instance:
instance XY (Point a) where
type Component (Point a) = a
x (Point xc _) = xc
y (Point _ yc) = yc
instance Floating a => Vertex (Point a) where
translate xy1 xy2 = Point (x xy1 + x xy2) (y xy1 + y xy2)
scale a xy = Point ((*a) $ x xy) ((*a) $ y xy)
rotate a xy = Point (x * cosA - y * sinA) (x * sinA + y * cosA)
where cosA = cos a
sinA = sin a
For some reason†, most people however prefer to make classes for geometric entities parametric over the scalar type, which is not only completely unnecessary but also un-geometric, because proper geometry is emphatically not depended of an actual basis decomposition.
†Actually I'm fairly certain what the reason is: Edward Kmett's decision to use parameterised types in the linear library. He should have known better, especially since Conal Elliott's vector-space library, which does it the right way, has been around for longer already.
The following version is corrected so that it compiles:
data Point a = Point a a
class XY c where
x :: c a -> a
y :: c a -> a
class XY c => Vertex c where
translate :: (Num a) => c a -> c a -> c a
scale :: (Num a) => a -> c a -> c a
rotate :: (Floating a) => a -> c a -> c a
instance XY Point where
x (Point first second) = first
y (Point first second) = second
instance Vertex Point where
translate xy1 xy2 = Point (x xy1 + x xy2) (y xy1 + y xy2)
scale a xy = Point ((*a) $ x xy) ((*a) $ y xy)
rotate a xy = Point ((x xy) * cosA - (y xy) * sinA) ((x xy) * sinA + (y xy) * cosA) where
cosA = cos a
sinA = sin a
There were only 2 changes needed, in fact:
I have added type constraints on a for the methods of the XY class. Otherwise, you can't use functions such as + which you have in the implementation of the instance for Point. (GHC actually makes this exact suggestion in one of the error messages it throws when trying to compile your version.) Note that these have to go on the class, not the instance, because the instance declaration makes no mention of the type a (even though the implementation does). If you don't put the constraints in the class then the methods are expected to work for all possible types a.
x and y are in fact functions, so you can't multiply them with numbers like sinA. I suspect you just got confused here and could have figured out what to do - you needed to apply them to the xy (the "point" itself) to get the "x" and "y" "co-ordinates".
So actually you were pretty close, and just needed to pay attention to what the compiler was telling you. GHC's error messages can seem a bit obscure when you're new to Haskell, but with a bit of practice you soon see that they're (often, although not always) quite helpful.

Haskell class instance

It's my first exercise to understand the classes in Haskell. My problem is how to define the functions that I have declared in the class and how to test them by terminal ghci.
I explain step by step what I did:
type Point2d = (Int, Int) -- point
type Vector2d = (Int, Int) -- vector
data Shape =
Line Point2d Point2d
| Triangle Point2d Point2d Point2d
deriving (Eq, Show)
class ClassShape s where
name :: s -> String
perim :: s -> Int -- given a CShape calculates the perimeter
move :: s -> Vector2d -> s
Now, I declare s as ClassShape instance, by implementing the corresponding functions.
nameShape :: Shape s -> String
nameShape Line = "Line"
nameShape Triangle = "Triangle"
perimShape :: Shape s -> Int
perimShape Line a b = 999 -- ...
perimShape Triangle a b c = 999 -- ...
Here's my problem: how should I declare the functions? I just need to see an "example" to understand the concept.
The error that Haskell returns is:
`Shape' is applied to too many type arguments
In the type signature for `nameShape':
nameShape :: Shape s -> String
`Shape' is applied to too many type arguments
In the type signature for `perimShape':
perimShape :: Shape s -> Int
Then, how do I test the program on Haskell?
Thanks to all.
Note that nameShape function will not work, because there is no Shape s type defined. Remember that s is a type variable. Only if you have defined Shape s type constructor you can use them. You have defined Shape type in your definition but not Shape s. For defining instance of typeclass, you have to do something like this:
instance ClassShape Shape where
name (Line _ _) = "Line"
name (Triangle _ _ _) = "Triangle"
perim (Line x y) = undefined -- Calculate perimiter using x and y
perim (Triangle x y z) = undefined
move (Line x y) = undefined
move (Triangle x y z) = undefined
You have to fill the undefined with working parts.
You're making a common confusion of early Haskell programmers: using two different things which work in related ways (sum types and classes) to do the same thing in two different ways. Thus there are two problems: the "little" problem (what does this error mean?) and the "big" problem (why is your code shaped like this?).
The Little Problem
You wrote Shape s when you meant to just write Shape. The way you have defined Shape, it has kind * (that is, it is a concrete type) rather than kind * -> *, which is the kind of adjectives -- things like "a list of" or "a pair of" which are abstract until you give them a concrete type to modify ("a list of strings" is concrete, "a list of" is abstract). When you write Shape s you are applying Shape as an adjective to a type variable s but it's not an adjective; it's a noun.
That is why you get the error:
`Shape' is applied to too many type arguments
Side note: you may be used to languages where the error message usually is not very well-related to the actual problem. In Haskell usually the compiler tells you exactly what is wrong, as it did in this case.
The Big Problem
Type classes are collections of unrelated types which can do the same things. The type class syntax passes an implicit context as a "constraint", this context can be implicit because it belongs to the type.
You may need to read that last paragraph a few times in a quiet corner. Basically I mean to say that you can do the same thing as a type class with a data constructor for the context:
data EqOrd s = EqOrdLib {getEq :: s -> s -> Bool, getCmp :: s -> s -> Ordering}
-- this is just provided to us as a primitive by Haskell
intEOL :: EqOrd Int
intEOL = EqOrdLib (==) compare
-- but we can then define things like this:
listEOL :: EqOrd x -> EqOrd [x]
listEOL (EqOrdLib base_eq base_cmp) = EqOrdLib list_eq list_cmp where
list_cmp [] [] = EQ
list_cmp (_:_) [] = GT
list_cmp [] (_:_) = LT
list_cmp (x:xs) (y:ys) = case base_cmp x y of
LT -> LT
GT -> GT
EQ -> list_cmp xs ys
list_eq xs ys = list_cmp xs ys == EQ
Now to use that sort of context, you would have to write explicitly:
quicksort :: EqOrd x -> [x] -> [x]
quicksort _ [] = []
quicksort lib (p:els) = quicksort lib lesser ++ [p] ++ quicksort lib greater
where cmp = getCmp lib
p_less_than x = cmp x p == LT
p_gte x = not . p_less_than
greater = filter p_less_than els
lesser = filter p_gte els
See, we explicitly pass in this library of functions lib and explicitly pull out the comparison function cmp = getCmp lib.
Type classes allow us to implicitly pass the library of functions, by stating up-front that the type itself only has one such library. We pass the library as a "constraint", so instead of EqOrd x -> [x] -> [x] you write Ord x => [x] -> [x] with the "fat arrow" of constraints. But secretly it means "when you ask me to use the < function on two values of type x, I know implicitly what library to get that function from and will get that function for you."
Now: you have one type, Shape, so you don't need typeclasses. (Go back to the first paragraph above: Type classes are collections of unrelated types which can do the same things.
If you want to do type classes then instead of the sum-type for Shape, let's define n-dimensional vectors of different types:
class Vector v where
(*.) :: (Num r) => r -> v r -> v r
(.+.) :: (Num r) => v r -> v r -> v r
norm :: (Num r, Floating r) => v r -> r
-- another advantage of type classes is *default declarations* like:
(.-.) :: (Num r) => v r -> v r -> v r
v1 .-. v2 = v1 .+. (-1 *. v2)
data V2D r = V2D r r deriving (Eq, Show)
instance Vector V2D where
s *. V2D x y = V2D (s * x) (s * y)
V2D x1 y1 .+. V2D x2 y2 = V2D (x1 + x2) (y1 + y2)
norm (V2D x y) = sqrt (x^2 + y^2)
data V3D r = V3D r r r deriving (Eq, Show)
instance Vector V3D where
s *. V3D x y z = V3D (s * x) (s * y) (s * z)
V3D x1 y1 z1 .+. V3D x2 y2 z2 = V3D (x1 + x2) (y1 + y2) (z1 + z2)
norm (V3D x y z) = sqrt (x^2 + y^2 + z^2)
Then we can write things like:
newtype GeneralPolygon v r = Poly [v r]
perimeter :: (Num r, Floating r, Vector v) -> GeneralPolygon v r -> r
perimeter (Poly []) = 0
perimeter (Poly (x : xs)) = foldr (+) 0 (map norm (zipWith (.-.) (x : xs) (xs ++ [x])))
translate :: (Vector v, Num r) => GeneralPolygon v r -> v r -> GeneralPolygon v r
translate (Poly xs) v = Poly (map (v .+.) xs)
Making Typeclasses Work For You
Now if you really want to, you can also unwrap your sum-type data declaration into a bunch of data declarations:
data Line = Line Point2d Point2d deriving (Eq, Show)
data Square = Square Point2d Point2d deriving (Eq, Show)
data Triangle = Triangle Point2d Point2d Point2d deriving (Eq, Show)
Now you can do something simple like:
class Shape s where
perim :: s -> Int
move :: s -> Vector2d -> s
Although I should say, you'll run into a problem when you want to do square roots for perimeters (sqrt is in the Floating typeclass, which Int does not have functions for, you'll want to change Int to Double or something).

Haskell applicative functor - compilation failure

I'm trying to chain together functions via the applicative functor pattern, but I'm having a problem compiling my code:
import Control.Applicative
buildMyList :: Float -> Float -> [Float]
buildMyList ul tick = [p | p <- [0,tick..ul]]
myFunctionChain :: [Float]
myFunctionChain = reverse <$> buildMyList 100 1
When I attempt to compile this I get the following compilation error:
Couldn't match type 'Float' with '[a0]'
Expected type: [[a0]]
Actual type: [Float]
In the return type of call of 'buildMyList'
It seems to me that I haven't managed to match the expected return context with the actual context. Not having enough experience in this area, I cant get any further!
The Applicative could be better explained using bulldMyList.
Assume you want to build an array of square matrix:
[(0,0), (0,1), (0,2), (1, 0) ...]. Using list comprehensions:
buildMyMatrix :: Int -> Int -> [(Int, Int)]
buildMyMatrix maxX maxY = [(x, y) | x <- [0..maxX], y <- [0..maxY]]
Using applicative combinators it can be rewritten as:
buildMyMatrix maxX maxY = pure (\x y -> (x, y)) <*> [0..maxX] <*> [0..maxY]
And according to applicative laws we can rewrite pure f <*> x = f <$> x, for all f and x:
buildMyMatrix maxX maxY = (\x y -> (x, y)) <$> [0..maxX] <*> [0..maxY]
I had to use slightly more complicated buildMyMatrix, as your buildMyList is too trivial to benefit from Applicative:
buildMyList :: Float -> Float -> [Float]
buildMyList ul tick = [p | p <- [0,tick..ul]]
buildMyList ul tick = id <$> [0,tick..ul] -- [by functor identity law]:
buildMyList ul tick = [0,tick..ul]

Is there a way to remove duplicate where statements in Haskell?

I have the following code in Haskell:
move :: Camera -> (Double, Double, Double) -> Camera
move camera (xt, yt, zt) = camera { cPosition = (x + xt, y + yt, z + zt) }
where (x, y, z) = cPosition camera
moveForward :: Camera -> Camera
moveForward camera = move camera (-1 * sin ya, 0, -1 * cos ya)
where (_, ya, _) = cRotation camera
moveBackward :: Camera -> Camera
moveBackward camera = move camera (sin ya, 0, cos ya)
where (_, ya, _) = cRotation camera
You'll notice that the moveForward and moveBackward functions have identical where statements. Is there a way to remove this duplication? I have numerous functions with the same where clauses (read: more than two).
I would prefer not to pass it in as another argument - since it will never change. It will always be cRotation.
What about making these functions take the tuple as an argument, and then wrapping them with another function that automatically does the boring work of extracting the tuple?
rotated :: ((Double, Double, Double) -> Camera -> a) -> Camera -> a
rotated f camera = f (cPosition camera) camera
moveForward :: Camera -> Camera
moveForward = rotated moveForward'
where moveForward' (_, ya, _) camera = move camera (-1 * sin ya, 0, -1 * cos ya)
moveBackward :: Camera -> Camera
moveBackward = rotated moveBackward'
where moveBackward' (_, ya, _) camera = move camera (sin ya, 0, cos ya)
Edit: Reviewing my answer six months later, I note there is some more duplication that could be lifted out: the move camera call. So really your functions like moveForward can just take a 3-tuple and return a 3-tuple, like so:
moveRotated :: ((Double, Double, Double) -> (Double, Double, Double)) -> Camera -> Camera
moveRotated f camera = move camera . f $ cPosition camera
moveForward :: Camera -> Camera
moveForward = moveRotated forward
where forward (_, ya, _) = (- sin ya, 0, - cos ya)
moveBackward :: Camera -> Camera
moveBackward = moveRotated backward
where backward (_, ya, _) = (sin ya, 0, cos ya)
This gives less power to moveForward and moveBackward, of course, since you can't use them to do anything but move. But it nicely distills them down to their essences, and ensures you can't accidentally do something other than move.
There's the simple answer of just define your own function
snd3 :: (a, b, c) -> b
snd3 (a, b, c) = b
And then you could use a lambda
moveForward camera = \ya -> (-1 * sin ya, 0, -1 * cos ya) $ snd3 $ cRotation camera
moveBackward camera = \ya -> (sin ya, 0, cos ya) $ snd3 $ cRotation camera
Or if you want to add the lens library as a dependency, you can replace snd3 cRotation camera with cRotation camera ^. _2 or equivalently view _2 $ cRotation camera. As for removing that lambda, there isn't much you can do other than defining a new function
apply3 :: (a -> a') -> (b -> b') -> (c -> c') -> (a, b, c) -> (a', b', c')
apply3 f1 f2 f3 (a, b, c) = (f1 a, f2 b, f3 c)
moveForward = apply3 (negate . sin) (const 0) (negate . cos) . snd3 . cRotation
moveBackward = apply3 sin (const 0) cos . snd3 . cRotation
And use some eta-reduction.
Unfortunately, there are lots of elegant tricks for working with 2-tuples but not as many for 3-tuples.

Resources