[Haskell-beginners] No accumulation of partially applied functions allowed?

Alec Story avs38 at cornell.edu
Tue Jun 26 23:25:36 CEST 2012


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.

On Tue, Jun 26, 2012 at 5:19 PM, Jay Sulzberger <jays at panix.com> wrote:

>
>
> On Tue, 26 Jun 2012, Brent Yorgey <byorgey at 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 at 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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20120626/cd9520c3/attachment.htm>


More information about the Beginners mailing list