• balsoft@lemmy.ml
    link
    fedilink
    arrow-up
    101
    ·
    9 days ago

    You gotta admit though, Haskell is crazy good for parsing and marshaling data

    • marcos@lemmy.world
      link
      fedilink
      arrow-up
      43
      ·
      9 days ago

      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.

      • balsoft@lemmy.ml
        link
        fedilink
        arrow-up
        22
        ·
        9 days ago

        You could probably write a very basic parser combinator library, enough to parse JSON, in 100 lines of Haskell

      • balsoft@lemmy.ml
        link
        fedilink
        arrow-up
        16
        ·
        edit-2
        7 days ago

        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 ((>=>), replicateM)
        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 (first, 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 = mapM char
        
        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..]]
        
        collectDigits :: Int -> [Int] -> Integer
        collectDigits base = foldl (\acc x -> acc * fromIntegral base + fromIntegral x) 0
        
        unsignedInteger :: SParser Integer
        unsignedInteger = collectDigits 10 <$> some (digit 10)
        
        integer :: SParser Integer
        integer = asum [char '-' $> (-1), char '+' $> 1, str "" $> 1] >>= \sign -> (sign *) <$> unsignedInteger
        
        -- 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)
          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 . collectDigits 16 <$> replicateM 4 (digit 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 to Double is lossy). I didn’t bother implementing any methods on the Decimal, 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.

      • join@lemmy.ml
        link
        fedilink
        arrow-up
        9
        ·
        9 days ago

        With recursive list comprehensions you can cram quite some complexity into one line of code.

      • expr@programming.dev
        link
        fedilink
        arrow-up
        3
        ·
        8 days ago

        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.

        • jenesaisquoi@feddit.org
          link
          fedilink
          English
          arrow-up
          4
          ·
          edit-2
          3 days ago

          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 in Rust!

      • balsoft@lemmy.ml
        link
        fedilink
        arrow-up
        2
        ·
        8 days ago

        Personally I’m more partial to nom. Serde is quite verbose and complex for a parser.

  • yetAnotherUser@lemmy.ca
    link
    fedilink
    arrow-up
    40
    arrow-down
    1
    ·
    9 days ago

    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!”

    • Gumby@lemmy.world
      link
      fedilink
      English
      arrow-up
      10
      ·
      9 days ago

      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!

    • psud@aussie.zone
      link
      fedilink
      English
      arrow-up
      4
      ·
      7 days ago

      It’s odd in the Australian public service, with COBOL programmers. They’ve been in the job long enough that they started when the public service was the only employer who would employ women as programmers. I’m on the systems analyst side of the fence, the programmers I have worked with include a bit more than 60% women

      I think all the programmers I know are married or gay or not interested. I think the gay ones are mostly married too.

    • ZILtoid1991@lemmy.worldOP
      link
      fedilink
      arrow-up
      18
      ·
      9 days ago

      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.

      • andioop@programming.dev
        link
        fedilink
        English
        arrow-up
        3
        ·
        edit-2
        6 days ago

        Feels weird reading this as the only single woman programmer in my friend group who likes men

      • rucksack@feddit.org
        link
        fedilink
        English
        arrow-up
        10
        arrow-down
        1
        ·
        9 days ago

        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.

        • lessthanluigi@lemmy.sdf.org
          link
          fedilink
          arrow-up
          9
          ·
          9 days ago

          I detransitioned from being a programmer and all I have is depression since, maybe I should retransission into being a programmer

        • shoki@lemmy.world
          link
          fedilink
          arrow-up
          7
          ·
          8 days ago

          and gender confirmation would not be getting called sir/ma’am at the starbucks but people asking you for IT help?

  • Rose@slrpnk.net
    link
    fedilink
    arrow-up
    13
    ·
    8 days ago

    I’m a girl. I’m not interested in Haskell, that’s too frigging endofunctiorific. Erlang! That’s what all the cool guys are doing.

      • gigachad@piefed.social
        link
        fedilink
        English
        arrow-up
        1
        ·
        8 days ago

        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.

        • expr@programming.dev
          link
          fedilink
          arrow-up
          3
          ·
          8 days ago

          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.

          • gigachad@piefed.social
            link
            fedilink
            English
            arrow-up
            3
            ·
            8 days ago

            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.