
I saw this in *The Little MLer*, a book on SML datatype 'a list = Empty | Cons of 'a * 'a list fun subst_c (pred) = fn (n,Empty) => Empty | (n,Cons(e,t)) => if pred (e) then Cons (n,subst_c (pred) (n,t)) else Cons (e,subst_c (pred) (n,t)) The data type is just a homemade list, and the function subst_c takes a predicate ('a -> Bool) and determines whether an incoming list's elements pass or fail. What is interesting is the fn ... => ... part which takes in more parameters, namely an 'a and an 'a list. Technically this fn... is an anonymous, nameless function, and it seems bizarre to me that it's nested inside the named function but still taking in parameters as if it were at the top level. Here's a previous version showing all three parameters at the top level fun subst_c (pred) (n,Empty) = Empty ... The purpose of the first function was to demonstrate currying. IOW, what the second unnamed function is doing behind the scenes can be broken down to two-stages (currying) of the first with named, then unnamed functions. So my question is, is there anything like this in Haskell where a function inside a function -- named or anonymous -- can take incoming parameters as if it were top level? LB

Hello Galaxy Being! You can do this: module Y where substitute ∷ (α → Bool) → (α, [α]) → [α] substitute predicate = \ thing → case thing of (_, [ ]) → [ ] (substitution, (x: xs)) → let remainder = substitute predicate (substitution, xs) in if predicate x then substitution: remainder else x: remainder It is even nicer since we can factor out the common part of the `if` block into a `let … in`. You can also enable the `LambdaCase` language extension and it will let you elide the `thing` thing. I am not sure if this is what your question is really about… In principle, of course Haskell has currying. Actually, functions are usually written in curried form in Haskell. Please let me know if I missed the substance of your question!

I'm sure you've answered my question, but I'm too much of a beginner to
fathom it. If you could explain, that would be great, but I could also go
off and try to grok it myself. Again, thanks.
On Fri, Mar 26, 2021 at 12:09 AM Ignat Insarov
Hello Galaxy Being!
You can do this:
module Y where
substitute ∷ (α → Bool) → (α, [α]) → [α] substitute predicate = \ thing → case thing of (_, [ ]) → [ ] (substitution, (x: xs)) → let remainder = substitute predicate (substitution, xs) in if predicate x then substitution: remainder else x: remainder
It is even nicer since we can factor out the common part of the `if` block into a `let … in`. You can also enable the `LambdaCase` language extension and it will let you elide the `thing` thing.
I am not sure if this is what your question is really about… In principle, of course Haskell has currying. Actually, functions are usually written in curried form in Haskell. Please let me know if I missed the substance of your question!

Let's start with the basics: lambda expressions.
ML says
fn x => blah blah
Haskell spells that
\x -> blah blah
Suppose you want to pattern match on the argument. If you only need one
pattern, that's cool:
\(x,y) -> blah blah
But what if you need more than one pattern? Well, standard ("Report")
Haskell makes you use a case expression:
\mx -> case mx of
Just x -> blah
Nothing -> etcetera
But GHC has a widely used language extension to get something more like ML.
If you put
-- The "language" is case insensitive.
-- The LambdaCase is case sensitive.
{-# language LambdaCase #-}
at the very tippy top of your .hs file, or pass -XLambdaCase to GHCi, then
you can write that last one
\case
Just x -> blah
Nothing -> etcetera
There has been some discussion of trying to expand that syntax to support
anonymous functions of multiple arguments, but no proposal has been
accepted as yet.
On Fri, Mar 26, 2021, 1:27 AM Galaxy Being
I'm sure you've answered my question, but I'm too much of a beginner to fathom it. If you could explain, that would be great, but I could also go off and try to grok it myself. Again, thanks.
On Fri, Mar 26, 2021 at 12:09 AM Ignat Insarov
wrote: Hello Galaxy Being!
You can do this:
module Y where
substitute ∷ (α → Bool) → (α, [α]) → [α] substitute predicate = \ thing → case thing of (_, [ ]) → [ ] (substitution, (x: xs)) → let remainder = substitute predicate (substitution, xs) in if predicate x then substitution: remainder else x: remainder
It is even nicer since we can factor out the common part of the `if` block into a `let … in`. You can also enable the `LambdaCase` language extension and it will let you elide the `thing` thing.
I am not sure if this is what your question is really about… In principle, of course Haskell has currying. Actually, functions are usually written in curried form in Haskell. Please let me know if I missed the substance of your question!
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

This has been very helpful. I plugged in the version VD above gave and it
works. Now, what might be the purpose of this \ case? In SML the code I
gave simply looks like a trick to simulate a curry where the function takes
a parameter, then morphs into a new function that takes the next parameter.
What would be the main use of this \ case ploy? I can't believe it was
dreamt up just to fake currying. What's still strange to me is how the
system knows to reach past the pred
data MyList a = Empty | Cons a (MyList a) deriving (Eq, Ord, Show)
subst_c :: (a -> Bool) -> (a, MyList a) -> MyList a
subst_c pred = \ case
(_, Empty) -> Empty
(n, Cons e t)
| pred e -> Cons n $ subst_c pred (n, t)
| otherwise -> Cons e $ subst_c pred (n, t)
and pattern match on the (a, MyList a) inside the function. So again, how
can it do this and why would I want to?
On Fri, Mar 26, 2021 at 12:37 AM David Feuer
Let's start with the basics: lambda expressions.
ML says
fn x => blah blah
Haskell spells that
\x -> blah blah
Suppose you want to pattern match on the argument. If you only need one pattern, that's cool:
\(x,y) -> blah blah
But what if you need more than one pattern? Well, standard ("Report") Haskell makes you use a case expression:
\mx -> case mx of Just x -> blah Nothing -> etcetera
But GHC has a widely used language extension to get something more like ML. If you put
-- The "language" is case insensitive. -- The LambdaCase is case sensitive. {-# language LambdaCase #-}
at the very tippy top of your .hs file, or pass -XLambdaCase to GHCi, then you can write that last one
\case Just x -> blah Nothing -> etcetera
There has been some discussion of trying to expand that syntax to support anonymous functions of multiple arguments, but no proposal has been accepted as yet.
On Fri, Mar 26, 2021, 1:27 AM Galaxy Being
wrote: I'm sure you've answered my question, but I'm too much of a beginner to fathom it. If you could explain, that would be great, but I could also go off and try to grok it myself. Again, thanks.
On Fri, Mar 26, 2021 at 12:09 AM Ignat Insarov
wrote: Hello Galaxy Being!
You can do this:
module Y where
substitute ∷ (α → Bool) → (α, [α]) → [α] substitute predicate = \ thing → case thing of (_, [ ]) → [ ] (substitution, (x: xs)) → let remainder = substitute predicate (substitution, xs) in if predicate x then substitution: remainder else x: remainder
It is even nicer since we can factor out the common part of the `if` block into a `let … in`. You can also enable the `LambdaCase` language extension and it will let you elide the `thing` thing.
I am not sure if this is what your question is really about… In principle, of course Haskell has currying. Actually, functions are usually written in curried form in Haskell. Please let me know if I missed the substance of your question!
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Fri, Mar 26, 2021 at 03:01:03PM -0500, Galaxy Being wrote:
Now, what might be the purpose of this \ case?
It is just a short-hand: \ case pat1 -> e1 pat2 -> e2 ... is identical to: \ x -> case x of pat1 -> e1 pat2 -> e2 ... In other words, a concise function taking a single argument that is immediately the verbatim subject of some pattern matches. maybe fallback extract = \ case Just av -> extract av Nothing -> fallback
In SML the code I gave simply looks like a trick to simulate a curry where the function takes a parameter, then morphs into a new function that takes the next parameter.
This is not a trick, it is elementary mathematical logic, In set theory, we have an isomorphism: A x B -> C <---> A -> (B -> C) this was eventually formalised in Churches Lambda Calculus. λ(x,y). mumble <---> λx. (λy. mumble) -- mumble = ..., some formula in x and y
What would be the main use of this \ case ploy? I can't believe it was dreamt up just to fake currying.
I don't understand why you're using words like "fake" and "ploy". This is just a shorthand that avoids having to introduce a superfluous intermediate variable that adds nothing to the clarity of the code.
What's still strange to me is how the system knows to reach past the pred
That's just the same isomorphism, for fixed pred, (subst_c pred) is a function of (a, MyList a). But we can also view the same subst_c as a function of two arguments (pred, (a, MyList a)). The two viewpoints are isomorphic. The notation for anonymous functions allows us to avoid having to name the restriction of `subst_c` to a given value of `pred`. subst_c pred = \ (a, MyList a) -> mumble <---> subst_c pred (a, MyList a) = mumble
data MyList a = Empty | Cons a (MyList a) deriving (Eq, Ord, Show) subst_c :: (a -> Bool) -> (a, MyList a) -> MyList a subst_c pred = \ case (_, Empty) -> Empty (n, Cons e t) | pred e -> Cons n $ subst_c pred (n, t) | otherwise -> Cons e $ subst_c pred (n, t)
and pattern match on the (a, MyList a) inside the function.
Well "closures" that capture a context, are immensely useful in writing reusable software building blocks. You can e.g. name "subst_c pred" specialised for a particular predicate and use it repeatedly, or pass it as a function to be used in some higher-order function.
So again, how can it do this and why would I want to?
When working with higher-order functions, the function-valued arguments passed to them are often partially-applied general-purpose "combinators". Functional programming would be much more tediously verbose, if we couldn't write function-valued expressions by partially applying existing functions. Instead of: map (* 2) [1,2,3,4] we'd have to always write: map double [1,2,3,4] where double x = 2 * x or similar. Often the expression is at least as clear as any name you might give it. -- Viktor.

On Thu, Mar 25, 2021 at 11:34:58PM -0500, Galaxy Being wrote:
I saw this in *The Little MLer*, a book on SML
datatype 'a list = Empty | Cons of 'a * 'a list
fun subst_c (pred) = fn (n,Empty) => Empty | (n,Cons(e,t)) => if pred (e) then Cons (n,subst_c (pred) (n,t)) else Cons (e,subst_c (pred) (n,t))
The Haskell version is: {-# LANGUAGE LambdaCase #-} data List a = Empty | Cons a (List a) deriving (Eq, Ord, Show) infixr 5 `Cons` -- | Substitute list elements matching a predicate with a given value. -- subst_c :: (a -> Bool) -- ^ Predicate for elements to replace -> (a, List a) -- ^ (Replacement element, input list) -> List a subst_c pred = \ case (_, Empty) -> Empty (n, Cons e t) | pred e -> Cons n $ subst_c pred (n, t) | otherwise -> Cons e $ subst_c pred (n, t) λ> :load subst_c.hs λ> subst_c odd (42::Int, 1 `Cons` 2 `Cons` 3 `Cons` Empty) Cons 42 (Cons 2 (Cons 42 Empty)) See also the table at: https://github.com/ghc-proposals/ghc-proposals/pull/302#issuecomment-7912094... (my favourite is option 2) which proposes alternatives for new syntax generalising "\ case" (LambdaCase) to allow anonymous functions to pattern match multiple arguments. That new syntax is not yet available, so for now "\ case" requires currying, such as seen in the SML code and the Haskell equivalent above. -- Viktor.
participants (4)
-
David Feuer
-
Galaxy Being
-
Ignat Insarov
-
Viktor Dukhovni