Hello everyone, and welcome to yet another recreational programming session with who?
No mom, I’m gonna BE a girl for Christmas. puts on programming socks
I don’t think “programmer” fully captures the reality of being an emacs-based programmer.
This kind of text hits differently when you’re a lesbian.
Wouldn’t it hit the same as a it would a straight male?
He won’t be done debugging her by then. She’ll be ready for beta testing next year.
There are far more male programmers… As a programmer, be gay or stay alone… Choose!
Can programmers only be with other programmers or am I missing something?
But you kind of have to leave the house for that… I mean… We talk about programmers…
/s
“JSON parser 100% from scratch in Haskell in 110 lines” doesn’t get you horny? I guess some people are just wired differently.
I’m a programmer myself but my wife isn’t a programmer, that was my motivation for questioning.
Oh that explains why my wife is gay
If she was around the same cs students as me then yeah
Ouch!
She sleeps with men, that’s pretty gay
There are a lot of things she does but that aint one of them
There are those who transition, so a significant chunk of that male programmer population is “male” as in quotation marks, only that some transition earlier than others. Does not guarantee that you can get the transgender autistic puppygirl (or other variations) of your dreams, since many of them are lesbians.
But also feel free to look outside your field for a partner. It’s okay to date an artist as a programmer.
I think programmer should be seen as a gender itself.
I’m currently transitioning myself, already have a homeserver and a Linux PC, can’t wait to be a real programmer.
and gender confirmation would not be getting called sir/ma’am at the starbucks but people asking you for IT help?
I detransitioned from being a programmer and all I have is depression since, maybe I should retransission into being a programmer
It’s not gay if I’m wearing programming socks.
Jokes on her, I’ve transitioned since last Christmas.
You can still bring a girl though
I am the girl! Hmm, but maybe I’ll bring another one too? 🤔
The more the merrier!
it’s yuletide! everyone (except that person. they know what they did) is welcome and celebrated!
Who needs a girl when you have monads to keep you warm?
Or become a girl with gonads
You gotta admit though, Haskell is crazy good for parsing and marshaling data
serde has entered the chat
From Scratch (as much as I like Rust, it’s very likely more verbose from scratch). Haskell is perfect for these kinds of things.
I will concede that implementing the first version in Haskell would be better.
Mostly so that we can then fulfil the meme of reimplementing it Rust!
Yes. I’m divided into “hum… 100 lines is larger than I expected” and “what did he mean ‘from scratch’? did he write the parser combinators? if so, 100 lines is crazy small!”
But I’m settling in believing 80 of those lines are verbose type declarations.
I decided to write it myself for fun. I decided that “From Scratch” means:
- No parser libraries (parsec/happy/etc)
- No using
read
from Prelude - No hacky meta-parsing
Here is what I came up with (using my favourite parsing method: parser combinators):
import Control.Monad ((>=>)) import Control.Applicative (Alternative (..), asum, optional) import Data.Maybe (fromMaybe) import Data.Functor (($>)) import Data.List (singleton) import Data.Map (Map, fromList) import Data.Bifunctor (second) import Data.Char (toLower, chr) newtype Parser i o = Parser { parse :: i -> Maybe (i, o) } deriving (Functor) instance Applicative (Parser i) where pure a = Parser $ \i -> Just (i, a) a <*> b = Parser $ parse a >=> \(i, f) -> second f <$> parse b i instance Alternative (Parser i) where empty = Parser $ const Nothing a <|> b = Parser $ \i -> parse a i <|> parse b i instance Monad (Parser i) where a >>= f = Parser $ parse a >=> \(i, b) -> parse (f b) i instance Semigroup o => Semigroup (Parser i o) where a <> b = (<>) <$> a <*> b instance Monoid o => Monoid (Parser i o) where mempty = pure mempty type SParser = Parser String charIf :: (a -> Bool) -> Parser [a] a charIf cond = Parser $ \i -> case i of (x:xs) | cond x -> Just (xs, x) _ -> Nothing char :: Eq a => a -> Parser [a] a char c = charIf (== c) one :: Parser i a -> Parser i [a] one = fmap singleton str :: Eq a => [a] -> Parser [a] [a] str (c:cs) = one (char c) <> str cs str _ = pure [] sepBy :: Parser i a -> Parser i b -> Parser i [a] sepBy a b = (one a <> many (b *> a)) <|> mempty data Decimal = Decimal { mantissa :: Integer, exponent :: Int } deriving Show data JSON = Object (Map String JSON) | Array [JSON] | Bool Bool | Number Decimal | String String | Null deriving Show whitespace :: SParser String whitespace = many $ asum $ map char [' ', '\t', '\r', '\n'] digit :: Int -> SParser Int digit base = asum $ take base [asum [char c, char (toLower c)] $> n | (c, n) <- zip (['0'..'9'] <> ['A'..'Z']) [0..]] unsignedInteger :: Int -> SParser Integer unsignedInteger base = foldl (\acc x -> acc * fromIntegral base + fromIntegral x) 0 <$> some (digit base) integer :: SParser Integer integer = do sign <- fromIntegral <$> asum [char '-' $> (-1), char '+' $> 1, str "" $> 1] (sign *) <$> unsignedInteger 10 -- This is the ceil of the log10 and also very inefficient log10 :: Integer -> Int log10 n | n < 1 = 0 | otherwise = 1 + log10 (n `div` 10) jsonNumber :: SParser Decimal jsonNumber = do whole <- integer fraction <- fromMaybe 0 <$> optional (str "." *> unsignedInteger 10) e <- fromIntegral <$> fromMaybe 0 <$> optional ((str "E" <|> str "e") *> integer) pure $ Decimal (whole * 10^(log10 fraction) + signum whole * fraction) (e - log10 fraction) escapeChar :: SParser Char escapeChar = char '\\' *> asum [ str "'" $> '\'', str "\"" $> '"', str "\\" $> '\\', str "n" $> '\n', str "r" $> '\r', str "t" $> '\t', str "b" $> '\b', str "f" $> '\f', str "u" *> (chr . fromIntegral <$> unsignedInteger 16) ] jsonString :: SParser String jsonString = char '"' *> many (asum [charIf (\c -> c /= '"' && c /= '\\'), escapeChar]) <* char '"' jsonObjectPair :: SParser (String, JSON) jsonObjectPair = (,) <$> (whitespace *> jsonString <* whitespace <* char ':') <*> json json :: SParser JSON json = whitespace *> asum [ Object <$> fromList <$> (char '{' *> jsonObjectPair `sepBy` char ',' <* char '}'), Array <$> (char '[' *> json `sepBy` char ',' <* char ']'), Bool <$> asum [str "true" $> True, str "false" $> False], Number <$> jsonNumber, String <$> jsonString, Null <$ str "null" ] <* whitespace main :: IO () main = interact $ show . parse json
This parses numbers as my own weird
Decimal
type, in order to preserve all information (converting toDouble
is lossy). I didn’t bother implementing any methods on theDecimal
, because there are other libraries that do that and we’re just writing a parser.It’s also slow as hell but hey, that’s naive implementations for you!
It ended up being 113 lines. I think I could reduce it a bit more if I was willing to sacrifice readability and/or just inline things instead of implementing stdlib typeclasses.
So, ARE you bringing a girl?
I’m not coming to my parents for this new year’s because I might get arrested and/or sent to die in a war. But once Putin dies, yes, I am
Just looking at the image, yeah he’s a little parser combinator library entirely from scratch.
Not sure what you mean by verbose type declarations. It looks to be 2 type declarations in a few lines of code (a newtype for the parser and a sum type to represent the different types of JSON values). It’s really not much at all.
Haskell is succinct.
You could probably write a very basic parser combinator library, enough to parse JSON, in 100 lines of Haskell
Judging by the Parser newtype, he did.
With recursive list comprehensions you can cram quite some complexity into one line of code.
You just need to find a girl that also likes Tsoding! Then, you can ask her “Hey, do you have plans for Christmas? I’d love it if we could do AoC (Advent of Code) in a language we both hate!”
Well shit, I’ve never seen AoC before - I’m not usually very interested in programming just for fun, but I might give that a try!
NOTE: no proper error reporting
Add those few lines, will ya?
But that would break the 111 line rule.
There’s a rule?
Not anymore.
Prisoner of war?
Paucity of waifu
Pupil of Women
not sure if it’s sarcastic: point of view
Title is edited
I did consider taking a screenshot before the edit from POW to POV, but eh.
ohhhh, I’m stupid… because it made me think that POV had two meanings possible… like… Prisoner Of Var…
Prisoner of Vore? Seems kinda hot
I wouldn’t trust a guy letting their battery go that low either
Prisoner Of War:
There was no ESL moment in Ba Sing Se!
Eastern Sign Language?
English Second Language
A JSON parser in Haskell, what a day to have eyes
?
Haskell’s incredibly good for writing parsers.
But oh boy is it difficult. We started with Haskell in the first semester CS and it was a pain. Kudos to anyone seriously developing in Haskell.
Eh, it’s just different. Other languages are hard in other ways. Haskell’s at least have very good reason behind them.
I write Haskell professionally and and am teaching to people without any experience, and it’s really no different than anything else. Though I will say that my experience is that university professors are often pretty clueless about the language and don’t teach it well.
I think it’s the paradigm change. Most people including myself learnt some kind of procedural language in school, shifting towards functional thinking is just very difficult. But of course that’s a skill a computer scientist must have and one of the reasons I didn’t graduate.