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.  Apology (Peter McIlroy)
   2. Re:  Infinite recursion in list comprehension (Dushyant Juneja)
   3. Re:  Type depending on value (Dmitriy Matrosov)


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

Message: 1
Date: Thu, 5 May 2016 12:57:24 -0700
From: Peter McIlroy <pmcil...@gmail.com>
To: "beginners@haskell.org" <beginners@haskell.org>
Subject: [Haskell-beginners] Apology
Message-ID: <572ba5b1.4f19620a.348a9.4...@mx.google.com>
Content-Type: text/plain; charset="windows-1252"

Apologies for the two bad messages. I won't attempt responding by phone to this 
list anymore. 
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160505/a8056c78/attachment-0001.html>

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

Message: 2
Date: Fri, 06 May 2016 07:48:24 +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:
        <cajkb0um7chqsgl7uubujzek841atglhxva2uz84wepqyva7...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Silent Leaf, Akash,

Thanks for your inputs. I think my issue got sorted out. As Akash pointed
out, the issue lies with the truncation condition never being met for some
cases. I got this finally working using 'takeWhile'. The recursion is as
elegant now:

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 = takeWhile (<= squareRoot x) $
primesBelowN n

Since squareRoot x will never be more than x, the recursion has no
opportunity to overflow to infinity.

Thanks for your inputs!

Having said all of this, I now realize that this is not really the Sieve of
Eratosthenes, but an optimized trial division method. Thanks to this, now I
know something more about list comprehension and its pitfalls. And some
things about optimization in haskell.

Thanks again for your time and effort.

Dushyant

On Thu, May 5, 2016 at 11:41 PM Silent Leaf <silent.le...@gmail.com> wrote:

> Implicitly, primesBelow shouldn't ever in fact call itself, not as it is
> articulated here **at the very least**, not without wasting a lot of
> calculus.
>
> As it is, and maybe no matter what (i'm not sure, don't have the knowledge
> to certify that), when primesBelow checks if a value "v" is prime or not,
> well no matter what it'll already have calculated and stored all primes
> below this value n (this, according to how primesBelow is articulated, aka
> filtering of Naturals bottom-top).
>
> Thus, if for each potential element "v" of the result (in my version,
> "list") of primesBelow, you call once again primesBelow, asking it to
> generate again all primes below sqrt(v), you'll do nothing more than doing
> again what you already did, because all those previous primes have already
> been generated, stored away, and especially very accessible, in the
> list-result in-construction of the **current** call to primesBelow, so if
> you don't use it but call again primesBelow to get a copy of what you
> already have, you'll multiply immensely the work without any gain.
> That's why I named the very result of primesBelow, to get a way to use
> "list" (the previously generated items of the future result-list) in
> "checker".
>
> 2016-05-05 15:44 GMT+02:00 Dushyant Juneja <juneja.dushy...@gmail.com>:
>
>> 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
>>>
>>
>> _______________________________________________
>> 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/20160506/07f9c34c/attachment-0001.html>

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

Message: 3
Date: Fri, 6 May 2016 13:42:18 +0300
From: Dmitriy Matrosov <sgf....@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Type depending on value
Message-ID:
        <CAFdVUFkmhECCQQoQO7Y9W7KWkykN=oxfarubropmxh_j8vr...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

> {-# LANGUAGE DataKinds, GADTs, StandaloneDeriving, Rank2Types, PolyKinds, 
> FlexibleInstances, MultiParamTypeClasses, FunctionalDependencies, 
> ScopedTypeVariables #-}
>
> import Unsafe.Coerce


 > Have you tried using a SNatClass that works more like
 > KnownNat, that is, having a method that returns a Nat?

I don't sure what you mean, but i've checked now the differences between my
code and reflection package, and there are some substantial ones.

I define Nat as

  data Nat = Z | S Nat

but they define only kind

> data Nat

Hm, well.. then we have similar definition of SNat class:

  class SNatClass (a :: Nat) where
      singN :: SNat a

> class KnownNat (n :: Nat) where
>     natSing :: SNat n

but very different definition of SNat itself:

  data SNat :: Nat -> * where
      SZ :: SNat 'Z
      SN :: SNat n -> SNat ('S n)

against

> newtype SNat (n :: Nat) = SNat Integer
> deriving instance Show (SNat n)

and from this follows another main difference: i've defined instances of
SNatClass:

  instance SNatClass 'Z where
      singN = SZ
  instance SNatClass n => SNatClass ('S n) where
      singN = SN singN

but they're not (and, if i'm correct, they can't, because there is no types
with kind Nat (remember, they've defined only kind)). And then the
identical code:

> data Proxy s = Proxy
>
> class Reifies s a | s -> a where
>   reflect :: p s -> a
>
> natVal :: forall n proxy. KnownNat n => proxy n -> Integer
> natVal _ = case natSing :: SNat n of
>              SNat x -> x
>
> instance KnownNat n => Reifies n Integer where
>     reflect = natVal
>
> newtype MagicNat r = MagicNat (forall (n :: Nat). KnownNat n => Proxy n -> r)
>
> reifyNat :: forall r. Integer -> (forall (n :: Nat). KnownNat n => Proxy n -> 
> r) -> r
> reifyNat x k = unsafeCoerce (MagicNat k :: MagicNat r) x Proxy
> {-# NOINLINE reifyNat #-}
>
> main = do
>         print $ reifyNat 4 reflect
>         print $ reifyNat 4 natVal
>         reifyNat 4 (print . asNatProxyTypeOf natSing)
>         --reifyNat 4 (print . asWrongNatProxyTypeOf natSing)
>
> -- Note the type: type argument in `SNat n` is the same as for Proxy. Thus, i
> -- will found exactly KnownNat instance, which i have defined in
> -- `reifyNat`.
> asNatProxyTypeOf :: KnownNat n => SNat n -> Proxy n -> SNat n
> asNatProxyTypeOf = const
>
> -- On the other hand, if type will be `KnownNat n => SNat r -> Proxy n ->
> -- SNat r`, then i won't be able to find correct instance of `KnownNat r` and
> -- thus can't e.g. print `SNat r` value.
> asWrongNatProxyTypeOf :: KnownNat n => SNat r -> Proxy n -> SNat r
> asWrongNatProxyTypeOf = const

So, you're right: `reifyNat` defines dictionary for `KnownNat n` (and
this is the only instance we have) as Integer. But though dictionary is a
function `natSing :: SNat n`, now SNat is newtype and its runtime
representation should indeed be equivalent to Integer and all is fine.

Well, ok, i think i understand how correct `reifyNat` works. Thanks!

But i still don't understand why mine works too, though is probably wrong.


On Thu, May 5, 2016 at 2:56 PM, Marcin Mrotek
<marcin.jan.mro...@gmail.com> wrote:
> Hello,
>
> My guess is that the Nat parameter in SNat gets erased, and both types
> end up with the same runtime representation. I'm not sure how reliable
> this is. Have you tried using a SNatClass that works more like
> KnownNat, that is, having a method that returns a Nat?
>
> Best regards,
> Marcin Mrotek
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


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

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 10
*****************************************

Reply via email to