[proposal] Design syntax like Haskell's where
#1634
Replies: 16 comments
-
This would, perhaps in an unwelcome way, permit multiple |
Beta Was this translation helpful? Give feedback.
-
|
@macrologist What are your thoughts on the idea more broadly? |
Beta Was this translation helpful? Give feedback.
-
I'm generally in favor of it. I like seeing the intended effect of a computation first. However, I'm even more in favor of conventions, idioms, and syntactic support that disfavors long function bodies. Because Coalton auto-curries applications, I think there is slightly less of a benefit to this kind of thing than there would be in, say, Common Lisp. In CL, crowding the top of a actually seems useful. But in Coalton, we might as well just or something like that. But, again, Im generally in favor of it. E.g, being able to do this would be nice |
Beta Was this translation helpful? Give feedback.
-
|
I don't like this idea since it allows two different shapes to a function and can take more time to understand how to read it, and I don't see any real benefit. If the top of a function is crowded with let bindings maybe the user should define auxiliary functions instead. |
Beta Was this translation helpful? Give feedback.
-
I'm sympathetic to this critique too. In general I prefer small function bodies with few binding and "parceling" forms. What I think such a proposal has going for it is that, when somebody decides to define a gaggle of auxiliaries in the body of their function, this syntax makes it easier to see what the auxiliaries are meant to do before having to wade through all of their messy definitions. In short, I think it makes code easier to read and write under those circumstances when somebody has already decided that module-wise sibling definitions are not the right choice. |
Beta Was this translation helpful? Give feedback.
-
What if the shape were announced: |
Beta Was this translation helpful? Give feedback.
-
I read a lot of Lisp code that ends up being 4–5 useless utilities with no practical independent value above the "real" function. It feels good we have more functions, but to me it's like filling our vocabulary with words that only make sense in context. Haskell code uses this comb :: Int -> [a] -> [[a]]
comb m xs = combsBySize xs !! m
where
combsBySize = foldr f ([[]] : repeat [])
f x next =
zipWith
(<>)
(fmap (x :) <$> ([] : next))
next
--
average :: [PixelRGB8] -> PixelRGB8
average pixels = PixelRGB8 (avg red) (avg green) (avg blue)
where
len = toInteger $ length pixels
avg c = fromIntegral $ (sum $ map (toInteger . c) pixels) `div` len
--
step rule a = listArray (l,r) res
where (l,r) = bounds a
res = [rule (a!r) (a!l) (a!(l+1)) ] ++
[rule (a!(i-1)) (a!i) (a!(i+1)) | i <- [l+1..r-1] ] ++
[rule (a!(r-1)) (a!r) (a!l) ]
--
fft [] = []
fft [x] = [x]
fft xs = zipWith (+) ys ts ++ zipWith (-) ys ts
where n = length xs
ys = fft evens
zs = fft odds
(evens, odds) = split xs
split [] = ([], [])
split [x] = ([x], [])
split (x:y:xs) = (x:xt, y:yt) where (xt, yt) = split xs
ts = zipWith (\z k -> exp' k n * z) zs [0..]
exp' k n = cis $ -2 * pi * (fromIntegral k) / (fromIntegral n)
--
isColorful :: Int -> Bool
isColorful n
| n < 0 = error "Only non-negative integers are allowed"
| n == 0 || n == 1 = True
| 0 `elem` digits = False
| 1 `elem` digits = False
| not (distinct digits) = False
| not (distinct subpros) = False
| otherwise = True
where
digits = map digitToInt (show n)
subpros = [(prods !! i) `div` (prods !! j) |j <- [0..length(digits)], i <- [(j+1)..length(digits)]]
prods = scanl (*) 1 digitsContrast with Lisp-style convexHull
:: (Floating a, Ord a)
=> [[a]] -> [[a]]
convexHull points =
let o = minimum points
presorted = sortBy (compareFrom o) (filter (/= o) points)
collinears = groupBy (((EQ ==) .) . compareFrom o) presorted
outmost = maximumBy (comparing (distanceFrom o)) <$> collinears
in dropConcavities [o] outmost
--
findCycleLength :: Eq a => [a] -> Maybe Int
findCycleLength [] = Nothing
findCycleLength (x:xs) =
let loop _ _ _ [] = Nothing
loop pow lam x (y:ys)
| x == y = Just lam
| pow == lam = loop (2*pow) 1 y ys
| otherwise = loop pow (1+lam) x ys
in loop 1 1 x xsOne reason this works very well in Haskell is because it's lazy. In Coalton, eagerness means the bindings would be evaluated first, which means the program's execution flow is no longer left-to-right, top-to-bottom. (The problem may be theoretical, and if not, is somewhat alleviated if all bindings are required to be functions.) |
Beta Was this translation helpful? Give feedback.
-
|
It is appealing that this might allow you to look at the first few lines of a function to understand what it does without looking at the following bindings, but I am dubious about adding another way to bind things with syntax that isn't very "lispy" and that doesn't provide much practical value. |
Beta Was this translation helpful? Give feedback.
-
|
I would rather have scheme-style lexical define, which could maybe even be SCC'd from the bottom of a function body or something idk |
Beta Was this translation helpful? Give feedback.
-
I like it Though maybe a different token could be chosen instead of
Or alternatively, we could just make a new |
Beta Was this translation helpful? Give feedback.
-
Yes this is a good idea, since users might want to grep "define" for toplevel things. I still don't see myself using it much in a bottom-to-top manner but this example makes me less dubious. |
Beta Was this translation helpful? Give feedback.
-
|
I think
I was surprised to see Scheme-like internal tl;dr summary: Don't add a |
Beta Was this translation helpful? Give feedback.
-
|
Addendum: What happens with: There is only one sensible option I think: It illustrates that we will have ambiguity with functions which are defined out of order with the other forms if we allow multiple of the same name. (Scheme doesn't have this problem because all internal |
Beta Was this translation helpful? Give feedback.
-
|
The danger, from a code-thats-nice-to-look-at perspective, with internal When considering a feature like this - a purely cosmetic one that adds no new algorithmically expressive capabilities to the language, but only stylistically expressive possibilities - questions of code-thats-nice-to-look-at-ness are of principle importance, imo. (People, I find, systematically undervalue code-thats-nice-to-look-at-ness in the design of their programming languages.) Regarding danger (a): One of the advantages, for what its worth, of a It is not that you cannot do but you have to really decide if you can live with yourself when choose to. And danger (b): I find inner Codicil to danger (b): As an old person, I very much prefer for visual distinctiveness to clue me in to the environment of a binding - whether it is local or global or other. |
Beta Was this translation helpful? Give feedback.
-
|
I agree with much of the above. I also think that limiting syntax is a great way to promote readability. So for instance, (As an aside, this isn't a definite feature I want to implement, it's more that I wanted to discuss it.) |
Beta Was this translation helpful? Give feedback.
-
|
My take on this is that I like using Coalton syntactically as close to Common Lisp style as possible. For me, one of the reasons I like Coalton over something like Haskell or OCAML is the simpler LISP syntax that's easier to read. I also might use macros more heavily than most when writing coalton (citation needed), and I could see that as Coalton gets more features like this, writing macros could become harder and less intuitive overtime. (The existing |
Beta Was this translation helpful? Give feedback.
Uh oh!
There was an error while loading. Please reload this page.
-
The Lisp tradition of stacking bindings top-down is reasonably well understood, but in some cases, it's a distraction from the meat of the program. I think we should give an option to put bindings after an expression. Maybe we can use PROGN?
A big negative with this example is that it's just very different than the rest of the syntax of Coalton.
Anyway, something to consider.
Beta Was this translation helpful? Give feedback.
All reactions