[Haskell-cafe] The last decade: what has changed, was has stayed the same?

Albert Y. C. Lai trebla at vex.net
Mon Nov 16 00:06:19 UTC 2015


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



More information about the Haskell-Cafe mailing list