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.  function application (mike h)
   2.  Haskell triangular loop (correct use of (++)) (rohan sumant)
   3. Re:  function application (Francesco Ariis)
   4. Re:  Haskell triangular loop (correct use of      (++))
      (Sumit Sahrawat, Maths & Computing, IIT (BHU))
   5. Re:  Haskell triangular loop (correct use of      (++)) (Silent Leaf)
   6. Re:  function application (Silent Leaf)


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

Message: 1
Date: Sun, 10 Apr 2016 17:16:24 +0100
From: mike h <mike_k_hough...@yahoo.co.uk>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: [Haskell-beginners] function application
Message-ID: <a911e435-49b0-4896-b269-a0abf101e...@yahoo.co.uk>
Content-Type: text/plain; charset=utf-8

Hi,

I?m looking at

mc :: (Integral a) => a -> a
mc x
  | x > 100 = x - 10 
  | otherwise = mc ( mc  ( x + 11 ) )

the  mc ( mc  ( x + 11 ) ) can also be written  as 

mc . mc  $ x + 11 

and I expected it could also be written as 

mc . mc ( x + 11 )

but the compiler error starts off with

Couldn't match expected type ?a? with actual type ?a0 -> c0?

so that is telling me, isn?t it (?) ,  that using parens is making the argument 
to the second mc into a function  ?a0 -> c0?

So is 
mc . mc  $ x + 11 

the only correct way to write this particular function in  ?.? style ?

Many Thanks

Mike





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

Message: 2
Date: Sun, 10 Apr 2016 22:29:51 +0530
From: rohan sumant <r.s.sum...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: [Haskell-beginners] Haskell triangular loop (correct use of
        (++))
Message-ID:
        <CAEHN=yakta2wsbvdxzj9pbjz6+dmajrxtkgbbr0bvxe8jud...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Suppose I have a list of distinct integers and I wish to generate all
possible unordered pairs (a,b) where a/=b.

Ex: [1,2,3,0] --> [(1,2),(1,3),(1,0),(2,3),(2,0),(3,0)]

 The approach I am following is this :-

mkpairs [] = []
mkpairs (x:xs) = (map (fn x) xs) ++ (mkpairs xs)

fn x y = (x,y)

It is generating the desired output but I am a bit unsure about the time
complexity of the function mkpairs. In an imperative language a nested
triangular for loop would do the trick in O(n^2) or more precisely
(n*(n-1)/2) operations. Does my code follow the same strategy? I am
particularly worried about the (++) operator. I think that (++) wouldn't
add to the time complexity since the initial code fragment (map (fn x) xs)
is to be computed anyway. Am I wrong here? Is this implementation running
O(n^2)? If not, could you please show me how to write a nested triangular
loop in Haskell?

Rohan Sumant
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160410/4f3fd80f/attachment-0001.html>

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

Message: 3
Date: Sun, 10 Apr 2016 19:11:55 +0200
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] function application
Message-ID: <20160410171155.ga14...@casa.casa>
Content-Type: text/plain; charset=utf-8

On Sun, Apr 10, 2016 at 05:16:24PM +0100, mike h wrote:
> So is 
> mc . mc  $ x + 11 
> 
> the only correct way to write this particular function in  ?.? style ?

Hello Mike,

    (mc . mc) (x + 11)

would do too.

Remember, function application (white-space) takes precedence over
*everything*, so:

    mc . mc ( x + 11 )
       ^   ^
       |   +------- whitespace
       |
       +----------- operator

is the same as:

    mc . (mc ( x + 11 ))



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

Message: 4
Date: Sun, 10 Apr 2016 22:48:12 +0530
From: "Sumit Sahrawat, Maths & Computing, IIT (BHU)"
        <sumit.sahrawat.ap...@iitbhu.ac.in>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Haskell triangular loop (correct use
        of      (++))
Message-ID:
        <CAJbEW8O=x8emy1tms00sxhuxvt63+3hl8mkcwuceva+89h8...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Haskell is a declarative language. The primary means of programming in a
declarative language is to provide definitions for stuff, similar to
mathematics. e.g. inc x = x + 1

If you want to define a value using an explicit sequence of steps, then you
have to use monads. The Haskell wikibook has a good tutorial on using the
state monad to generate random numbers. This allows mutation, preventing
which is one of Haskell's prime features, so I wouldn't recommend wiring
code like this.

Complexity analysis is usually tricky in Haskell. You can refer to the book
'purely functional days structures' to know more.

Regards,
  Sumit
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160410/d9b29134/attachment-0001.html>

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

Message: 5
Date: Sun, 10 Apr 2016 20:12:56 +0200
From: Silent Leaf <silent.le...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Haskell triangular loop (correct use
        of      (++))
Message-ID:
        <CAGFccjMaGP6Z=u7ZgbRvCap2gYyvLY2FCuX=8oqh7qg7avw...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Dunno if that's what you're interested in, or if it's best in terms of
efficiency, but there's syntax inside the language made just for this kind
of thing, called list comprehension. It comes from math's definition of
sets by comprehension, and since it's part of the language I'd have a
tendency to trust its efficiency, but I might be entirely wrong on this
aspect.

Anyways, for your problem, say I want to create the set of pairs of your
example:

let result = [(x,y) | let xs = [1,2,3,0], (x,ix) <- zip xs [1,2..], y <-
drop ix xs, x /= y]
in result == [(1,2),(1,3),(1,0),(2,3),(2,0),(3,0)]

Basically the syntax is: [ parameterized result element | conditions on the
parameters]
the conditions being a sequence of comma-separated items that are either:
local variable declarations without the 'in', example being (let input =
[1,2,3,0]), pattern-accepting generation of values from a list, or
conditions on the parameters (here x and y).

In order to build y's list I decided to zip xs with a list of indexes
starting to 1, thereby ensuring no pair is twice in, considering the order
doesn't matter.
I'd bet the syntax is monad/do related, with all those right-to left
arrows. Plus it fits the bill of what's actually happening here.

Of course if you want a function, you can still write thereafter
mkpairs :: Integral a => a -> [(a,a)]
mkpairs n = [(x,y) | let xs = [1..n] ++ [0], (x,ix) <- zip xs [1,2..], y <-
drop ix xs, x /= y]

If you don't care about the order, I guess xs = [0..n] will be much more
efficient, relatively speaking.
Pretty sure the function even works for n == 0, since y <- drop 1 [0] won't
have a thing to yield, hence, result = [].

If that interests you:
https://wiki.haskell.org/List_comprehension
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160410/e60594a9/attachment-0001.html>

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

Message: 6
Date: Sun, 10 Apr 2016 23:29:27 +0200
From: Silent Leaf <silent.le...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] function application
Message-ID:
        <cagfccjoon+_vf7sqndaxo+x_yfsia2-veryjritebp4ur_y...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Mike: If you seek as I think you do, to write the function mc (partially)
in point-free style, you must know this style implies no arguments, or at
least not all arguments, mentioned, that is for example here:
mc x | x < 100 = x - 10
mc = mc . mc . (+ 11)

The second line will only be checked for pattern matching if the first one
fails, so it amounts to the "otherwise" guard as here there's no pattern,
so it's a bit like the pattern that always matches (mc _ = ...)
You'll remark I did write (mc =) and not (mc x =). Point free style amounts
to describing a function through a composition of other functions, in an
arguments-free way, here for example, (mc . mc . (+11)) being the
composition of mc twice, with the "partially-applied" function (+11) == (\x
-> x + 11) == (11+). This partially applied notation works for all
operators by the way.

And for the record, the whitespace operator is a pure myth. First you can
remove all whitespace, it still works. Second, try using the same
whitespace-induced universal right-associativity with (f a b): does it
amount to (f (a b))?

The reason for this right-associativity interpretation in (mc . mc (x +
11)) is because (.) itself is right associative: right-directed greediness
could we say, in the vocabulary of regular expression. It's also the case
of ($), and that's why we use it to counter the natural left associativity
of function application:
f $ g a == f $ (g a) == ($) f (g a) == f (g a)   -- (using the definition
of ($) here)
instead of
f g a == (f g) a
without using ($).

The whitespace is just a meaningless character (I guess, a set of
characters) used to separate juxtaposed meaningful tokens of the language
when we have either (symbol,symbol) or (nonsymbol,nonsymbol), for example
respectively (!! $ /= !!$) and (f g /= fg). whenever it's a nonsymbol and a
symbol, whitespace is not necessary (a+, +a).
Then there's the automatic, implicit function application between two
juxtaposed non-symbolic tokens. But the whitespace has never been an
operator of any kind, and is totally meaningless (and optional) in (mc . mc
(x + 11)).

Especially too, it's clear no whitespace survives the tokenization during
the lexical phase of the (pre?) compilation, contrarily to all real
operators like (+).
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160410/75497f7a/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 94, Issue 6
****************************************

Reply via email to