Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/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. Re:  No accumulation of partially applied functions allowed?
      (ARJANEN Lo?c Jean David)
   2. Re:  No accumulation of partially applied functions allowed?
      (Brent Yorgey)


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

Message: 1
Date: Wed, 27 Jun 2012 14:01:10 +0200
From: ARJANEN Lo?c Jean David <arjanen.l...@gmail.com>
Subject: Re: [Haskell-beginners] No accumulation of partially applied
        functions allowed?
To: beginners@haskell.org
Message-ID:
        <cab2q81ax8fy6xq5kvwweacq5ovdxj27ym+wrmbjgsh70g7-...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

It is easy, but inconvenient to define applyTo on tuples, which are
Haskell's standard container for heterogeneous collections (that would
basically be an extension of Prelude's uncurry), but they would be
inconvenient to define and quite unwieldy to use.

If you limit yourself to homogeneous collections (that is, lists), it's
possible but using typeclass hackery and you shouldn't do so unless you
need to. for an example of such techniques, see
HaXR<http://www.haskell.org/haskellwiki/HaXR>
or hs-json-rpc <http://hackage.haskell.org/package/hs-json-rpc> where this
kind of tricks are used to implement remote calls.

2012/6/27  Jay Sulzberger:
>
> On Tue, 26 Jun 2012, Alec Story <av...@cornell.edu> wrote:
>
>> Because of Haskell's type system, there are some expressions that you
>> simply cannot compile.  Most of them you don't *want* to compile because
>> they do bad things (like add two strings, for example).  Some things are
>> legal in Lisp but don't typecheck in Haskell for exactly the reasons that
>> Brent pointed out.  They might make sense in some contexts, but the
>> compiler isn't able to reason about them.
>
>
> Thanks, Alec.
>
> What is a formalized version of
>
>  It is not possible in Haskell to define `applyTo`.*
>  * At least not without crazy type class hackery.
>
> I think the difficulty must arise mainly from the *, meaning I
> think, "any type" in the above `applyTo`.*.  Would it be
> easy/convenient to define `applyTo`.(a, b, c) where a is a "type
> variable"?  In general can we, for any finite number n, where n > 2,
> easily/conveniently define `applyTo`.(a1, a2, ..., an) ?
>
> Ah, I see that the problem is for lists of length 3, so for the
> type, if it be such, that I might write as [a, a, a], ah, OK, I
> will fire up GHCi and have a look.
>
> oo--JS.
>
>
>>
>> On Tue, Jun 26, 2012 at 5:19 PM, Jay Sulzberger <j...@panix.com> wrote:
>>
>>>
>>>
>>> On Tue, 26 Jun 2012, Brent Yorgey <byor...@seas.upenn.edu> wrote:
>>>
>>>  On Tue, Jun 26, 2012 at 10:08:49PM +0200, Obscaenvs wrote:
>>>>
>>>>
>>>>> Sorry if this is a less than stellar question.
>>>>>
>>>>> The problem:
>>>>> Given a function f :: a -> a -> a -> b, make it work on a list
>>>>> instead: f `applyTo`[x,y,z] where [x,y,z] :: [a].
>>>>> My stab at a general solution was
>>>>> `
>>>>> applyTo f [] = error "no arg"
>>>>> applyTo f (x:xs) = go (f x) xs
>>>>>   where
>>>>>     go acc [] = acc
>>>>>     go acc (y:[]) = acc y
>>>>>     go acc (y:ys) = go (acc $ y) ys
>>>>> `
>>>>>
>>>>> I thought this would work, functions being "first class citizens" but
>>>>> ghci complains:
>>>>>   "Occurs check: cannot construct the infinite type: t1 = t0 -> t1
>>>>>   In the return type of a call of `acc'
>>>>>   Probable cause: `acc' is applied to too many arguments
>>>>>   In the expression: acc y
>>>>>   In an equation for `go': go acc (y : []) = acc y"
>>>>>
>>>>> The 'probable cause' isn't the real cause here, but something to do
>>>>> with the fact that it's impossible to accumulate functions in this
>>>>> way...
>>>>> Or am I just too tired too make it work? I can see that the type of
>>>>> `go` could be a problem, but is it insurmountable?
>>>>>
>>>>
>>>> The type of `go` is exactly the problem.  In particular, the type of
>>>> acc's first parameter.  In the third clause of go's definition, we can
>>>> see that `acc` and (acc $ y) are both used as the first argument to
>>>> go, hence they must have the same type.  However, this is impossible
>>>> -- if acc has type (t0 -> t1), then y must have type t0, and (acc $ y)
>>>> has type t1, so it would have to be the case that t1 = t0 -> t1 --
>>>> hence the error message.
>>>>
>>>> It is not possible in Haskell to define `applyTo`.* I know this
>>>> function gets used a lot in lisp/scheme, but Haskell style is
>>>> different.  If you explain the context in which you wanted this
>>>> function, perhaps we can help you figure out a better way to structure
>>>> things so it is not needed.
>>>>
>>>> -Brent
>>>>
>>>> * At least not without crazy type class hackery.
>>>>
>>>
>>> What is the difficulty?
>>>
>>> Is the difficulty at the level of "syntax"?
>>>
>>> Or is it that the type "Haskell expression", perhaps "Haskell
>>> form", to use an old and often confusing Lisp term, does not
>>> exist in the Haskell System of Expression?  Here "exist" should be
>>> read as "exist at the right level", right level for attaining
>>> some objective.
>>>
>>> These alternatives, I think, need not be disjoint.
>>>
>>> I am ignorant of Haskell, but sometimes I write Perl in Lisp, and
>>> the blurb for my last public rant mentioned a specific lambda
>>> expression:
>>>
>>>  http://lists.gnu.org/archive/**html/gnu-misc-discuss/2012-03/**
>>> msg00036.html<
http://lists.gnu.org/archive/html/gnu-misc-discuss/2012-03/msg00036.html>
>>>
>>> oo--JS.
>>>
>>>
>>> ______________________________**_________________
>>> Beginners mailing list
>>> Beginners@haskell.org
>>> http://www.haskell.org/**mailman/listinfo/beginners<
http://www.haskell.org/mailman/listinfo/beginners>
>>>
>>
>>
>>
>> --
>> Alec Story
>> Cornell University
>> Biological Sciences, Computer Science 2012
>>
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
ARJANEN Lo?c Jean David
http://blog.luigiscorner.com
---
"Computer science is no more about computers than astronomy is about
telescopes, biology is about microscopes, or chemistry is about beakers and
test tubes. Science is not about tools. It is about how we use them, and
what we find out when we do."
Michael R. Fellows and Ian Parberry
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120627/e2efa09b/attachment-0001.htm>

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

Message: 2
Date: Wed, 27 Jun 2012 14:26:49 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] No accumulation of partially applied
        functions allowed?
To: beginners@haskell.org
Message-ID: <20120627182649.ga30...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Tue, Jun 26, 2012 at 06:39:11PM -0400, Jay Sulzberger wrote:
> 
> 
> On Tue, 26 Jun 2012, Alec Story <av...@cornell.edu> wrote:
> 
> >Because of Haskell's type system, there are some expressions that you
> >simply cannot compile.  Most of them you don't *want* to compile because
> >they do bad things (like add two strings, for example).  Some things are
> >legal in Lisp but don't typecheck in Haskell for exactly the reasons that
> >Brent pointed out.  They might make sense in some contexts, but the
> >compiler isn't able to reason about them.
> 
> Thanks, Alec.
> 
> What is a formalized version of
> 
>   It is not possible in Haskell to define `applyTo`.*
>   * At least not without crazy type class hackery.
> 
> I think the difficulty must arise mainly from the *, meaning I
> think, "any type" in the above `applyTo`.*.  Would it be
> easy/convenient to define `applyTo`.(a, b, c) where a is a "type
> variable"?  In general can we, for any finite number n, where n > 2,
> easily/conveniently define `applyTo`.(a1, a2, ..., an) ?

Haha, sorry, it seems my meta-notation was confusing. `applyTo`.* is
`applyTo`, followed by a period (indicating the end of the sentence),
followed by an asterisk (indicating the presence of a footnote).  It
is not a technical notation at all. =)

In any case, yes, you can define `applyTo` for any specific number
of parameters.  For example,

  applyTo3 :: (a -> a -> a -> b) -> [a] -> b
  applyTo3 f [x,y,z] = f x y z

(although I do not recommend even this, because applyTo3 will crash if
you pass it a list of the wrong length). But you cannot define a
single `applyTo` which works for any number of parameters.  The
problem is that every expression in Haskell must have a type, and
Haskell's type system is not expressive enough to write down a valid
type for applyTo. (What would the type of its first argument be?)

-Brent



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

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 48, Issue 29
*****************************************

Reply via email to