
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.