The last decade: what has changed, was has stayed the same?

Hi all, I used to be interested in Haskell roughly a decade ago, then life happened. Now that I'm setting up project work, I'm interested in what has been happening in the meantime. I read a bit on the usual pages, did a quick scan of the mailing list, didn't find out what the important questions of today are and what answers exist. Some ideas of relevant questions below. Feel free to pose and answer your own questions :-) After learning the bare language, how long does it take a competent programmer to become confident in the performance of his Haskell code? After learning the bare language, how long does it take a competent programmer to know when and when not to use strictness annotations/operators? I'm seeing a lot of typesystem golf happening. Is this teachable to the average competent programmer? Is it relevant to everyday programming such as business logic, database access, or webpage generation? (If no, for what programming endeavours is it relevant?) What's the status of debugging - I dimly remember a rough consensus that stack traces are hard to interpret in a meaningful way. (I know that debugging is far less important for a referentially transparent language than for others, but it would still be interesting.) What's the status of all the "boring stuff": - logging - profiling - dialog layout - input validation - database interaction - webpage generation, webflow - multi-tiered applications On the "instant to-do" side: What would a competent programmer need to do to become a competent Haskell programmer? (I suspect the usual set of toy projects will not work. Toy projects give you only so much mileage; in particular, you don't learn anything about what patterns will hold up for larger projects and what patterns won't scale.) Regards, Jo

On 2015-11-13 02:43 PM, Joachim Durchholz wrote:
After learning the bare language, how long does it take a competent programmer to become confident in the performance of his Haskell code?
After learning the bare language, how long does it take a competent programmer to know when and when not to use strictness annotations/operators?
These two questions unify into one; choosing the right strictness is part of making an efficient program. Confidence is a treacherous end; by the Dunning-Kruger effect, it only takes a month for one to be fully confident and totally wrong. (Under one week if the person has been competent in past things so they think they're infallible in all future things.) It is more objective and productive to ask: how long does it take to be measurably successful? I think it took me five years. But it was a hobbyist, intermittent, on-and-off kind of five years; my day job was procrastinating my PhD thesis and teaching formal methods in the imperative setting. (Then again, does anyone learn Haskell full-time?) It was also an unaided kind of five years. (I learned much of the Core->Cmm->asm translation by brute-force experimentation. It was uphill both ways.) The following aids are available now but not back then. If you start today, it may take you less time and puzzlement: http://www.vex.net/~trebla/haskell/lazy.xhtml (I wrote it after I really figured out lazy evaluation, so of course it didn't exist when I was learning) https://hackhands.com/guide-lazy-evaluation-haskell/ https://github.com/takenobu-hs/haskell-ghc-illustrated
I'm seeing a lot of typesystem golf happening. Is this teachable to the average competent programmer? Is it relevant to everyday programming such as business logic, database access, or webpage generation? (If no, for what programming endeavours is it relevant?)
I am not fond of most of their advanced type-level games which are far-fetched encodings of dependent types in a non-dependent type system. They remind me of how I felt enlightened for five minutes when I first realized how to simulate malloc and free in BASIC. It lasted for only five minutes because it was false enlightenment. The true enlightenment should be: This is why you ditch BASIC for Pascal or C. But a very elementary use of GADTs and phantom types improves safety of databasee access a lot. At a low level, of course you still have the very unsafe and very vulnerable raw_query :: ByteString -> IO [[ByteString]] -- I omit a Connection parameter for this sketch -- also perhaps it should be IO (Either SQLError [[ByteString]]) But you can say you don't use it directly; you use a safer, higher level wrapper, less vulnerable to type errors. The higher level can go like this: {-# LANGUAGE GADTs #-} import Data.ByteString (ByteString) import qualified Data.ByteString.Char8 as B -- Apology: Char8 interface for SQL syntax and column names only. -- Not going to inflict this on all data. data Selectee a where Column :: ByteString -> Selectee a Plus :: Selectee Int -> Selectee Int -> Selectee Int Len :: Selectee ByteString -> Selectee Int name_column, email_column :: Selectee ByteString name_column = Column (B.pack "name") email_column = Column (B.pack "email") concretize :: Selectee a -> ByteString concretize (Column c) = c concretize (Len e) = B.concat [B.pack "len(", concretize e, B.pack ")"] concretize (Plus e1 e2) = B.concat [B.pack "(", concretize e1, B.pack ")+(", concretize e2, B.pack ")"] -- select1 is a select with single-column answer -- It's single-column, and I hardcode the table name, for this sketch. select1 :: SQLtype a => Selectee a -> IO [a] select1 s = do map (sqlread . head) <$> raw_query query where query = B.concat [B.pack "select ", concretize s, B.pack " from addressbook"] class SQLtype a where sqlread :: ByteString -> a instance SQLtype Int where sqlread s = case B.readInt s of Just (n, _) -> n example = select1 (Len name_column `Plus` Len email_column) -- select len(name)+len(email) from addressbook

Thanks Albert! Am 16.11.2015 um 01:06 schrieb Albert Y. C. Lai:
On 2015-11-13 02:43 PM, Joachim Durchholz wrote:
After learning the bare language, how long does it take a competent programmer to become confident in the performance of his Haskell code?
After learning the bare language, how long does it take a competent programmer to know when and when not to use strictness annotations/operators?
These two questions unify into one; choosing the right strictness is part of making an efficient program.
I meant the first question to be "how well can I predict the performance of my code". The second question was "if performance is insufficient, how well can people wield the tool that they have for it". If the optimizer is good enough, the second question would rarely matter enough.
Confidence is a treacherous end; by the Dunning-Kruger effect, it only takes a month for one to be fully confident and totally wrong. (Under one week if the person has been competent in past things so they think they're infallible in all future things.)
Oh, a competent programmer can see whether he's under Dunning-Kruger or not: If haskell-cafe is talking about issues and problems he hasn't seen yet, he isn't good enough yet. That's easy enough if you're training to watch out for these things.
It is more objective and productive to ask: how long does it take to be measurably successful?
That's a bit too open-ended because everybody's definition of "success" varies. Some people feel successful if their code compiles, others feel successful only if they can control cache locality across asymmetric MP cores. It's still an interesting question.
The following aids are available now but not back then. If you start today, it may take you less time and puzzlement:
http://www.vex.net/~trebla/haskell/lazy.xhtml (I wrote it after I really figured out lazy evaluation, so of course it didn't exist when I was learning) https://hackhands.com/guide-lazy-evaluation-haskell/ https://github.com/takenobu-hs/haskell-ghc-illustrated
I'll take a look at these. I'm a bit sceptical that I'll be able to become competent just by reading them though :-)
I'm seeing a lot of typesystem golf happening. Is this teachable to the average competent programmer? Is it relevant to everyday programming such as business logic, database access, or webpage generation? (If no, for what programming endeavours is it relevant?)
I am not fond of most of their advanced type-level games which are far-fetched encodings of dependent types in a non-dependent type system. They remind me of how I felt enlightened for five minutes when I first realized how to simulate malloc and free in BASIC. It lasted for only five minutes because it was false enlightenment. The true enlightenment should be: This is why you ditch BASIC for Pascal or C.
Heh. I can understand that sentiment. My knee-jerk reaction to the first experiments (encoding integers in the type system to get stuff like square matrices typed) was "gee, we should really unify all this stuff in general assertions about types&values and have the compiler check these as far as possible!" (Unfortunately, that would not be Haskell anymore.) Still, not being competent with Haskell in any way, I need to listen to divergent views. (I regret having written "typesystem golf", it can be seen as derogatory and shapes the answers.)
But a very elementary use of GADTs and phantom types improves safety of databasee access a lot.
Yeah, that's really important. I'm pretty much in the same boat with you on that issue; the usefulness of a type system trick (or any language trick) needs to be multiplied by the percentage of people able to understand and use it in practice.
At a low level, of course you still have the very unsafe and very vulnerable
raw_query :: ByteString -> IO [[ByteString]] -- I omit a Connection parameter for this sketch -- also perhaps it should be IO (Either SQLError [[ByteString]])
You can also have warnings. Or errors AND a result. (I happen to know that after half a decade of doing Oracle via JDBC.)
But you can say you don't use it directly; you use a safer, higher level wrapper, less vulnerable to type errors.
Everybody is doing that :-) Including the Java guys. Some of the Java guys are even doing pretty declarative designs even if imperative. Try a look at Jooq, it's built to deal with database incompatibilities AND be easy to use: http://jooq.org/ (Disclaimer: It was on my shortlist once, but never made it into production use for me, so I don't know how well the approach holds up in real use.) Thanks! Jo (Hope somebody takes the time to look at the other aspects of the question...)
participants (2)
-
Albert Y. C. Lai
-
Joachim Durchholz