[Haskell-cafe] Does Haskell have this SML syntax?

Galaxy Being borgauf at gmail.com
Fri Mar 26 20:01:03 UTC 2021


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 <david.feuer at gmail.com> wrote:

> 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 <borgauf at gmail.com> 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 <kindaro at gmail.com> 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.
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20210326/9ce25c88/attachment.html>


More information about the Haskell-Cafe mailing list