lwhjp

joined 3 weeks ago
[–] lwhjp@piefed.blahaj.zone 2 points 19 hours ago

I forgot that "weekdays" for a US website means something different for me here in UTC+9.

This was surprisingly fiddly, but I think I managed to do it reasonably neatly.

import Control.Arrow  
import Data.Foldable  
import Data.List (sortBy)  
import Data.List.Split  
import Data.Maybe  
import Data.Ord  

data Fishbone  
  = Fishbone (Maybe Int) Int (Maybe Int) Fishbone  
  | Empty  
  deriving (Eq)  

instance Ord Fishbone where  
  compare = comparing numbers  

readInput :: String -> [(Int, Fishbone)]  
readInput = map readSword . lines  
  where  
    readSword = (read *** build) . break (== ':')  
    build = foldl' insert Empty . map read . splitOn "," . tail  

insert bone x =  
  case bone of  
    (Fishbone l c r next)  
      | isNothing l && x < c -> Fishbone (Just x) c r next  
      | isNothing r && x > c -> Fishbone l c (Just x) next  
      | otherwise -> Fishbone l c r $ insert next x  
    Empty -> Fishbone Nothing x Nothing Empty  

spine (Fishbone _ c _ next) = c : spine next  
spine Empty = []  

numbers :: Fishbone -> [Int]  
numbers (Fishbone l c r next) =  
  (read $ concatMap show $ catMaybes [l, Just c, r])  
    : numbers next  
numbers Empty = []  

quality :: Fishbone -> Int  
quality = read . concatMap show . spine  

part1, part2, part3 :: [(Int, Fishbone)] -> Int  
part1 = quality . snd . head  
part2 = uncurry (-) . (maximum &&& minimum) . map (quality . snd)  
part3 = sum . zipWith (*) [1 ..] . map fst . sortBy (flip compareSwords)  
  where  
    compareSwords =  
      comparing (quality . snd)  
        <> comparing snd  
        <> comparing fst  

main =  
  forM_  
    [ ("everybody_codes_e2025_q05_p1.txt", part1),  
      ("everybody_codes_e2025_q05_p2.txt", part2),  
      ("everybody_codes_e2025_q05_p3.txt", part3)  
    ]  
    $ \(input, solve) -> readFile input >>= print . solve . readInput  
[–] lwhjp@piefed.blahaj.zone 2 points 22 hours ago

I liked this one!

import Control.Arrow  
import Control.Monad  
import Data.List  
import Data.Ratio  

simpleTrain = uncurry (%) . (head &&& last) . map read  

compoundTrain input =  
  let a = read $ head input  
      z = read $ last input  
      gs =  
        map  
          ( uncurry (%)  
              . (read *** read . tail)  
              . break (== '|')  
          )  
          $ (tail . init) input  
   in foldl' (/) (a % z) gs  

part1, part2, part3 :: [String] -> Integer  
part1 = floor . (2025 *) . simpleTrain  
part2 = ceiling . (10000000000000 /) . simpleTrain  
part3 = floor . (100 *) . compoundTrain  

main =  
  forM_  
    [ ("everybody_codes_e2025_q04_p1.txt", part1),  
      ("everybody_codes_e2025_q04_p2.txt", part2),  
      ("everybody_codes_e2025_q04_p3.txt", part3)  
    ]  
    $ \(input, solve) -> readFile input >>= print . solve . lines  
[–] lwhjp@piefed.blahaj.zone 1 points 22 hours ago

I thought this was going to be the knapsack problem, but no.

import Control.Monad  
import Data.List.Split  
import qualified Data.Set as Set  
import qualified Data.Multiset as MSet  

part1, part2, part3 :: [Int] -> Int  
part1 = sum . Set.fromList  
part2 = sum . Set.take 20 . Set.fromList  
part3 = maximum . MSet.toCountMap . MSet.fromList  

main =  
  forM_  
    [ ("everybody_codes_e2025_q03_p1.txt", part1),  
      ("everybody_codes_e2025_q03_p2.txt", part2),  
      ("everybody_codes_e2025_q03_p3.txt", part3)  
    ]  
    $ \(input, solve) ->  
      readFile input >>= print . solve . map read . splitOn ","  
[–] lwhjp@piefed.blahaj.zone 4 points 4 days ago* (last edited 4 days ago) (1 children)

It's gradually coming back to me. The Haskell Complex type doesn't work particularly nicely as an integer, plus the definition of division is more like "scale", so I just went with my own type.

Then I forgot which of div and quot I should use, and kept getting nearly the right answer :/

import Data.Ix  

data CNum = CNum !Integer !Integer  

instance Show CNum where  
  show (CNum x y) = "[" ++ show x ++ "," ++ show y ++ "]"  

cadd, cmul, cdiv :: CNum -> CNum -> CNum  
(CNum x1 y1) `cadd` (CNum x2 y2) = CNum (x1 + x2) (y1 + y2)  
(CNum x1 y1) `cmul` (CNum x2 y2) = CNum (x1 * x2 - y1 * y2) (x1 * y2 + y1 * x2)  
(CNum x1 y1) `cdiv` (CNum x2 y2) = CNum (x1 `quot` x2) (y1 `quot` y2)  

part1 a = iterate op (CNum 0 0) !! 3  
  where  
    op x = ((x `cmul` x) `cdiv` CNum 10 10) `cadd` a  

countEngraved = length . filter engrave  
  where  
    engrave p =  
      let rs = take 100 $ tail $ iterate (op p) (CNum 0 0)  
       in all (\(CNum x y) -> abs x <= 1000000 && abs y <= 1000000) rs  
    op p r = ((r `cmul` r) `cdiv` CNum 100000 100000) `cadd` p  

part2 a =  
  countEngraved  
    . map (\(y, x) -> a `cadd` CNum (x * 10) (y * 10))  
    $ range ((0, 0), (100, 100))  

part3 a =  
  countEngraved  
    . map (\(y, x) -> a `cadd` CNum x y)  
    $ range ((0, 0), (1000, 1000))  

main = do  
  print $ part1 $ CNum 164 56  
  print $ part2 $ CNum (-21723) 67997  
  print $ part3 $ CNum (-21723) 67997  
[–] lwhjp@piefed.blahaj.zone 4 points 4 days ago* (last edited 4 days ago) (2 children)

Ooh, challenges! Here we go!

I haven't really written any Haskell since last year's AoC, and boy am I rusty.

import Control.Monad  
import Data.List  
import Data.List.Split  
import Data.Vector qualified as V  

readInput s =  
  let [names, _, moves] = splitOn "," <$> lines s  
   in (names, map readMove moves)  
  where  
    readMove (d : s) =  
      let n = read s :: Int  
       in case d of  
            'L' -> -n  
            'R' -> n  

addWith f = (f .) . (+)  

part1 names moves =  
  names !! foldl' (addWith $ clamp (length names)) 0 moves  
  where  
    clamp n x  
      | x < 0 = 0  
      | x >= n = n - 1  
      | otherwise = x  

part2 names moves =  names !! (sum moves `mod` length names)  

part3 names moves =  
  V.head  
    . foldl' exchange (V.fromList names)  
    $ map (`mod` length names) moves  
  where  
    exchange v k = v V.// [(0, v V.! k), (k, V.head v)]  

main =  
  forM_  
    [ ("everybody_codes_e2025_q01_p1.txt", part1),  
      ("everybody_codes_e2025_q01_p2.txt", part2),  
      ("everybody_codes_e2025_q01_p3.txt", part3)  
    ]  
    $ \(input, solve) ->  
      readFile input >>= putStrLn . uncurry solve . readInput  
[–] lwhjp@piefed.blahaj.zone 3 points 5 days ago (1 children)

Hugs <3 I hope he comes around soon.

When I come across stubbornly wrong people I try to remind myself that it's not my responsibility to correct their misapprehensions, even when they're about me.

It's great that he's talking to you, anyway. Best wishes to you and your fiancΓ©(e?).

[–] lwhjp@piefed.blahaj.zone 2 points 6 days ago (1 children)
[–] lwhjp@piefed.blahaj.zone 5 points 6 days ago

Yeah, I pretty much gave up on makeup for the first six months or so, outside of a little mascara, for exactly the same reason.

Fortunately, estrogen is capable of wildly transforming your face, and makeup will suddenly start looking amazing once it starts accentuating feminine features!

[–] lwhjp@piefed.blahaj.zone 2 points 1 week ago (1 children)

Do you mean TeX (not GNU though)?

The related package METAFONT converges on e, as well.

[–] lwhjp@piefed.blahaj.zone 19 points 1 week ago (1 children)

Yeah, it's scary, right? Your whole life has been turned inside out.

Your wife being supportive will make things so much easier as you figure out what you want to do going forward.

There's no rush. You can take things as slow as you need; do as little or as much as you feel comfortable with. It's also possible your feelings about what you want will change going forward. That's pretty normal.

It's also very normal for the pressure (do you know what I mean?) that caused your egg to crack to suddenly ease up, and make you start doubting yourself: whether you really want or deserve this. So be ready for that. Don't forget that you've felt this way all your life!

And welcome to the fold! We've all been through exactly where you are right now.

[–] lwhjp@piefed.blahaj.zone 8 points 2 weeks ago

Still waiting for approval for surgery here, but thank you so much as always for talking about your experiences. It's really helpful to know what I might have to face going forward.

It does sound like your brain is playing tricks. Hope things calm down soon <3

[–] lwhjp@piefed.blahaj.zone 8 points 2 weeks ago

Marriage went from "I guess we'll figure this out" to "who gets the house" rather quickly...

Oh well, maybe I can find someone new who's into women.

 

It's nice, but it's a pain to set so I mostly just have it in a ponytail. Plus it takes forever to grow out.

51
submitted 3 weeks ago* (last edited 3 weeks ago) by lwhjp@piefed.blahaj.zone to c/mtf@lemmy.blahaj.zone
 

It'll put something on your chest, but it probably isn't hair.

(This is a joke: don't actually eat estradiol gel)

 
view more: next β€Ί