Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Infinite recursion in list comprehension (Dushyant Juneja)
   2. Re:  Infinite recursion in list comprehension (akash g)
   3. Re:  Infinite recursion in list comprehension (Dushyant Juneja)
   4. Re:  Double vs. Num (Ben Rogalski)


----------------------------------------------------------------------

Message: 1
Date: Thu, 05 May 2016 12:43:02 +0000
From: Dushyant Juneja <juneja.dushy...@gmail.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] Infinite recursion in list comprehension
Message-ID:
        <cajkb0uolfxhmbbzvzhku7ee-lzb91+ps0kfb3wwh2vjmrc+...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi,

I seem to be landing into infinite recursion when using higher order
functions with list comprehension. Take this for an example. The following
works well, and gives answers for numbers like 2000000 as well:

primesBelowN :: Integer -> [Integer]
primesBelowN n = 2:3:filter f [6*k+i | k <- [1..(n-1)`div`6], i <- [-1, 1]]
                     where f x = foldr g True xs
                                 where g t ac = (x `rem` t /= 0) && ac
                                       xs = [5, 7..(truncate (sqrt
(fromInteger x)))]


However, the following never returns anything for the same number, probably
due to some kind of loop malfunction:

primesBelowN :: Integer -> [Integer]
primesBelowN n = 2:3:filter f [6*k+i | k <- [1..(n-1)`div`6], i <- [-1, 1]]
                     where f x = foldr g True xs
                                 where g t ac = (x `rem` t /= 0) && ac
                                       xs = [ m | m <- [5, 7, ..], m
<= (truncate
(sqrt (fromInteger x)))]

Any ideas what might be going wrong?

Thanks in advance!

DJ
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160505/3999ede8/attachment-0001.html>

------------------------------

Message: 2
Date: Thu, 5 May 2016 18:31:15 +0530
From: akash g <akabe...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Infinite recursion in list
        comprehension
Message-ID:
        <caliga_fchzpwlvfcohfdau7nt8xfj_myhidyipzip_knwsw...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi Dushyant,

The problem most likely is
[m | m <- [5,7..], m <= (truncate (sqrt (fromInteger x)))]

 This is because, the filter condition (the last part) does a very simple
thing:  It filters out any element that does not fulfil the criteria.  You
are operating on a list that is monotonically increasing.  However, the
filter isn't aware of this property.  Hence, this list comprehension never
ends because it doesn't know that once the condition fails, it will always
fail.

Thus, the solution would be to generate a finite set (or take a part of the
infinite set using takeWhile or something like that), instead of using an
infinite one.

Regards,
G Akash.

On Thu, May 5, 2016 at 6:13 PM, Dushyant Juneja <juneja.dushy...@gmail.com>
wrote:

> Hi,
>
> I seem to be landing into infinite recursion when using higher order
> functions with list comprehension. Take this for an example. The following
> works well, and gives answers for numbers like 2000000 as well:
>
> primesBelowN :: Integer -> [Integer]
> primesBelowN n = 2:3:filter f [6*k+i | k <- [1..(n-1)`div`6], i <- [-1, 1]]
>                      where f x = foldr g True xs
>                                  where g t ac = (x `rem` t /= 0) && ac
>                                        xs = [5, 7..(truncate (sqrt
> (fromInteger x)))]
>
>
> However, the following never returns anything for the same number,
> probably due to some kind of loop malfunction:
>
> primesBelowN :: Integer -> [Integer]
> primesBelowN n = 2:3:filter f [6*k+i | k <- [1..(n-1)`div`6], i <- [-1, 1]]
>                      where f x = foldr g True xs
>                                  where g t ac = (x `rem` t /= 0) && ac
>                                        xs = [ m | m <- [5, 7, ..], m <= 
> (truncate
> (sqrt (fromInteger x)))]
>
> Any ideas what might be going wrong?
>
> Thanks in advance!
>
> DJ
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160505/01a7fb1a/attachment-0001.html>

------------------------------

Message: 3
Date: Thu, 05 May 2016 13:44:26 +0000
From: Dushyant Juneja <juneja.dushy...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Infinite recursion in list
        comprehension
Message-ID:
        <CAJkb0UM7bY7=ohohyj2hw+gu+ce1xylojjkg4sp4o1xpqk9...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi Akash,

Thanks for the response. A very simple and lucid explanation. Looks
interesting.

So, here's the big picture now, for which I need this. I intend to
implement a lookalike Sieve of Eratosthenes algorithm in haskell. For this,
I intend to use the earlier function recursively, as follows:

primesBelowN :: Integer -> [Integer]
primesBelowN n = 2:3:filter f [6*k+i | k <- [1..(n-1)`div`6], i <- [-1, 1]]
                     where f x = foldr g True xs
                                 where g t ac = (x `rem` t /= 0) && ac
                                       xs = [ m | m <- primesBelowN n,
m <= (truncate
(sqrt (fromInteger x)))]

Of course, I could do something like this:

primesBelowN :: Integer -> [Integer]
primesBelowN n = 2:3:filter f [6*k+i | k <- [1..(n-1)`div`6], i <- [-1, 1]]
                     where f x = foldr g True xs
                                 where g t ac = (x `rem` t /= 0) && ac
                                       xs = [ m | m <- primesBelowN (truncate
(sqrt (fromInteger x)))]

However, this calls primesBelowN function with a new argument everytime. I
suppose that is not optimal (correct me if I am wrong).

Point number 2: both fail. Grrh.

Any ideas how I could go recursive with this function?

Dushyant


On Thu, May 5, 2016 at 6:31 PM akash g <akabe...@gmail.com> wrote:

> Hi Dushyant,
>
> The problem most likely is
> [m | m <- [5,7..], m <= (truncate (sqrt (fromInteger x)))]
>
>  This is because, the filter condition (the last part) does a very simple
> thing:  It filters out any element that does not fulfil the criteria.  You
> are operating on a list that is monotonically increasing.  However, the
> filter isn't aware of this property.  Hence, this list comprehension never
> ends because it doesn't know that once the condition fails, it will always
> fail.
>
> Thus, the solution would be to generate a finite set (or take a part of
> the infinite set using takeWhile or something like that), instead of using
> an infinite one.
>
> Regards,
> G Akash.
>
> On Thu, May 5, 2016 at 6:13 PM, Dushyant Juneja <juneja.dushy...@gmail.com
> > wrote:
>
>> Hi,
>>
>> I seem to be landing into infinite recursion when using higher order
>> functions with list comprehension. Take this for an example. The following
>> works well, and gives answers for numbers like 2000000 as well:
>>
>> primesBelowN :: Integer -> [Integer]
>> primesBelowN n = 2:3:filter f [6*k+i | k <- [1..(n-1)`div`6], i <- [-1,
>> 1]]
>>                      where f x = foldr g True xs
>>                                  where g t ac = (x `rem` t /= 0) && ac
>>                                        xs = [5, 7..(truncate (sqrt
>> (fromInteger x)))]
>>
>>
>> However, the following never returns anything for the same number,
>> probably due to some kind of loop malfunction:
>>
>> primesBelowN :: Integer -> [Integer]
>> primesBelowN n = 2:3:filter f [6*k+i | k <- [1..(n-1)`div`6], i <- [-1,
>> 1]]
>>                      where f x = foldr g True xs
>>                                  where g t ac = (x `rem` t /= 0) && ac
>>                                        xs = [ m | m <- [5, 7, ..], m <= 
>> (truncate
>> (sqrt (fromInteger x)))]
>>
>> Any ideas what might be going wrong?
>>
>> Thanks in advance!
>>
>> DJ
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>>
>>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160505/84f2c2b8/attachment-0001.html>

------------------------------

Message: 4
Date: Thu, 5 May 2016 10:10:45 -0400
From: Ben Rogalski <bwrogal...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Double vs. Num
Message-ID:
        <cal-j+nkyicvf6omsa+hc6epyqna-0ea+wxi8tduqtkjyy+e...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Tim and Christopher, here is my code. There is a lot of it, but I've tried
to cut out the irrelevent parts.

If I change the type of Transform3D.append from

append :: (Floating a) => Transformer a -> Transform a -> Transformer a

to

append :: Transformer Double -> Transform Double -> Transformer Double

The framerate goes from ~1400 fps to ~2200 fps.



module Render where

...

renderTree :: GLInfo -> Tree (Attribute Double) -> IO ()
renderTree (GLInfo names attribs uniforms) t = fst $ cFold2 f (return
(),identity) t
  where f acc Hidden = Skip acc
        f (a,tr) (Transformation t) = Continue (a, append tr t)
        f (a,tr) (Clip b) =
          let (x1:.y1:._, x2:.y2:._) = extremes $ applyAABB tr b
              a' = do
                glUniform2f (uniforms M.! "maskMin") (realToFrac x1)
(realToFrac y1)
                glUniform2f (uniforms M.! "maskMax") (realToFrac x2)
(realToFrac y2)
          in  Continue (a >> a', tr)
        f (a,tr) (Texture _ (x1:.y1:.x2:.y2:._)) =
          let a' = do
                glUniform1i (uniforms M.! "texSampler") 0
                glUniform4f (uniforms M.! "uvCoords") (realToFrac x1)
(realToFrac y1) (realToFrac x2) (realToFrac y2)
                glUniformMatrix4fv' (uniforms M.! "mvp") 1 (fromBool False)
(map realToFrac $ transformerToList tr)
                glDrawElements gl_TRIANGLES (fromIntegral $ attribs M.!
"iboLenSquare") gl_UNSIGNED_INT nullPtr
          in  Continue (a >> a', tr)
        f acc _ = Continue acc

...



module Transform3D where

...

data Transform a =
    RotationZ a
  | Scale (Vec3 a)
  | Translation (Vec3 a) deriving (Eq, Read, Show)

newtype Transformer a = Transformer (Vec4 (Vec4 a))

append :: (Floating a) => Transformer a -> Transform a -> Transformer a
append (Transformer m) t = Transformer $ m #*# toMatrix t

identity :: (Num a) => Transformer a
identity = Transformer identityMatrix

toMatrix :: (Floating a) => Transform a -> Vec4 (Vec4 a)
toMatrix (RotationZ z) = rotationZMatrix z
toMatrix (Scale (x:.y:.z:._)) = scaleMatrix x y z
toMatrix (Translation (x:.y:.z:._)) = translationMatrix x y z

identityMatrix :: (Num a) => Vec4 (Vec4 a)
identityMatrix =
  (1:.0:.0:.0:.Nil):.
  (0:.1:.0:.0:.Nil):.
  (0:.0:.1:.0:.Nil):.
  (0:.0:.0:.1:.Nil):.Nil

rotationZMatrix :: (Floating a) => a -> Vec4 (Vec4 a)
rotationZMatrix a =
  let c = cos a
      s = sin a
  in  (c:.(-s):.0:.0:.Nil):.
      (s:.c:.0:.0:.Nil):.
      (0:.0:.1:.0:.Nil):.
      (0:.0:.0:.1:.Nil):.Nil

scaleMatrix :: (Num a) => a -> a -> a -> Vec4 (Vec4 a)
scaleMatrix x y z =
  (x:.0:.0:.0:.Nil):.
  (0:.y:.0:.0:.Nil):.
  (0:.0:.z:.0:.Nil):.
  (0:.0:.0:.1:.Nil):.Nil

translationMatrix :: (Num a) => a -> a -> a -> Vec4 (Vec4 a)
translationMatrix x y z =
  (1:.0:.0:.x:.Nil):.
  (0:.1:.0:.y:.Nil):.
  (0:.0:.1:.z:.Nil):.
  (0:.0:.0:.1:.Nil):.Nil

...



module Vector where

...

infixr 5 :.
--data Cons u t = (:.) t (u t) deriving (Eq, Read, Show)
data Cons u t = (:.) ! t ! (u t) deriving (Eq, Read, Show)

data Nil t = Nil deriving (Eq, Read, Show)

...

(|*#) :: (Num t, Vector w, Vector u) => w t -> w (u t) -> u t
(|*#) v m = (transpose m) #*| v

(#*#) :: (Num t, Vector u, Vector v, Vector w) => u (v t) -> v (w t) -> u
(w t)
(#*#) x y = transpose $ fmap (x #*|) (transpose y)

dot :: (Num t, Vector v) => v t -> v t -> t
dot xs ys = sum ((*) <$> xs <*> ys)

...
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160505/2f68534c/attachment.html>

------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 95, Issue 7
****************************************

Reply via email to