[Haskell-cafe] Could someone help me to understand funB?

Alex Hammel ahammel87 at gmail.com
Fri Dec 19 17:21:39 UTC 2014


I suspect that somebody has been abusing pointfree
<https://github.com/bmillwood/pointfree>.

On Thu, Dec 18, 2014 at 8:35 PM, Magicloud Magiclouds <
magicloud.magiclouds at gmail.com> wrote:
>
> Thank you. This will take some time for me to read.
>
> On Fri, Dec 19, 2014 at 12:32 PM, Lyndon Maydwell <maydwell at gmail.com>
> wrote:
>>
>> funB = flip takeWhile primes . ( . join (*)) . flip (<=)
>>
>> funB x = flip takeWhile primes ((( . join (*)) . flip (<=)) x)
>>
>> funB x = takeWhile ((( . join (*)) . flip (<=)) x) primes
>>
>> funB x = takeWhile (foo x) primes
>>
>>
>> foo x = (( . join (*)) . flip (<=)) x
>>
>> foo x = (( . join (*)) (flip (<=) x)
>>
>> foo x = flip (<=) x . join (*)
>>
>> foo x = (x <=) . join (*)
>>
>>
>> -- join :: Monad m => m (m a) -> m a
>> -- join (*) == (**2)
>>
>> foo x = (x <=) . (** 2)
>>
>> foo x y = x <= (y ** 2)
>>
>> isLessThanTheSquareOf = foo
>>
>> funB x = takeWhile (x `isLessThanTheSquareOf`) primes
>>
>>
>> Helpful?
>>
>>
>> On Fri, Dec 19, 2014 at 2:52 PM, Magicloud Magiclouds <
>> magicloud.magiclouds at gmail.com> wrote:
>>
>>> Hi,
>>>
>>>   Following code is to get a list of primes. Now it is hard for me to
>>> understand funB. I mean I can see what it does. But I cannot see the
>>> detailed process by every language part.
>>>
>>> import Control.Monad
>>>
>>> isPrime :: Integer -> Bool
>>> isPrime i = ap funA funB i
>>>
>>> funA :: Integer -> [Integer] -> Bool
>>> funA x xs = all (\x' -> (mod x x') /= 0) xs
>>>
>>> funB :: Integer -> [Integer]
>>> funB = flip takeWhile primes . ( . join (*)) . flip (<=)
>>>
>>> primes :: [Integer]
>>> primes = 2 : filter isPrime [3, 5 ..]
>>>
>>> main :: IO ()
>>> main = print $ take 10 primes
>>>
>>> --
>>> 竹密岂妨流水过
>>> 山高哪阻野云飞
>>>
>>> And for G+, please use magiclouds#gmail.com.
>>>
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>>>
>
> --
> 竹密岂妨流水过
> 山高哪阻野云飞
>
> And for G+, please use magiclouds#gmail.com.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20141219/cf0d2bde/attachment.html>


More information about the Haskell-Cafe mailing list