Lynx's recent activity

  1. Comment on Day 19: Monster Messages in ~comp

    Lynx
    (edited )
    Link
    Haskell Yo dawg, I heard you like parsers, so I built a parser for your parser! day19.hs I first use a set of ReadPs to parse the rules themselves, then construct a new ReadP from these rules and...

    Haskell

    Yo dawg, I heard you like parsers, so I built a parser for your parser!

    day19.hs

    I first use a set of ReadPs to parse the rules themselves, then construct a new ReadP from these rules and run it against the input strings to see which match.

    Funnily enough, this approach was robust enough that I didn't have to change anything at all for part 2 (other than appending the new rules to the list of rules, overwriting the previous definitions).

    module Day19 where
    
    import AoC
    
    import Control.Applicative
    import Data.Char
    import Data.Foldable
    import Data.Map (Map, (!))
    import qualified Data.Map as M
    import Data.Maybe
    import Data.Tuple
    import Text.ParserCombinators.ReadP
    import Text.Read.Lex
    
    data RuleElement = Literal String | Reference Int
    
    parseElement :: ReadP RuleElement
    parseElement = parseRef <|> parseLit
        where parseRef = Reference <$> readDecP
              parseLit = Literal <$> between (char '"') (char '"') (many1 $ satisfy isAlphaNum)
    
    parseRule :: ReadP (Int, [[RuleElement]])
    parseRule = do ruleNum <- readDecP
                   string ": "
                   alternatives <- parseAlternatives
                   return (ruleNum, alternatives)
        where parseAlternatives = parseSequence `sepBy` string " | "
              parseSequence = parseElement `sepBy` char ' '
    
    buildParser :: Map Int [[RuleElement]] -> Int -> ReadP String
    buildParser m i = buildAlternatives $ m ! i
        where buildAlternatives = asum . map buildSequence
              buildSequence = foldl1 (liftA2 (++)) . map buildElement
              buildElement (Literal s) = string s
              buildElement (Reference j) = buildParser m j
    
    countRootMatches :: [String] -> Map Int [[RuleElement]] -> Int
    countRootMatches input rules = length . filter (isJust . oneCompleteResult rootParser) $ input
        where rootParser = buildParser rules 0
    
    main = runAoC splitInput run (run . withExtraRules)
        where splitInput = swap . fmap tail . break (=="") . lines
              withExtraRules = fmap (++ ["8: 42 | 42 8", "11: 42 31 | 42 11 31"])
              run = uncurry countRootMatches . fmap parseRules
              parseRules = M.fromList . map (fromJust . oneCompleteResult parseRule)
    
    AoC.hs (runner and utility functions)
    module AoC
        ( (.:)
        , enumerate
        , oneCompleteResult
        , splitOnEmptyLines
        , runAoC
        )
    where
    
    import Data.Function (on)
    import Data.List (groupBy)
    import Text.ParserCombinators.ReadP
    
    (.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
    f .: g = (f .) . g
    infixl 8 .:
    
    enumerate :: Enum i => i -> [a] -> [(i, a)]
    enumerate _ [] = []
    enumerate i (x:xs) = (i, x) : enumerate (succ i) xs
    
    oneCompleteResult :: ReadP a -> String -> Maybe a
    oneCompleteResult p s = case readP_to_S (p <* eof) s of
                              [(x, "")] -> Just x
                              _ -> Nothing
    
    splitOnEmptyLines :: String -> [[String]]
    splitOnEmptyLines = filter (not . any null) . groupBy ((==) `on` null) . lines
    
    runAoC :: (Show r1, Show r2) => (String -> i) -> (i -> r1) -> (i -> r2) -> IO ()
    runAoC inputTransform part1 part2 = do
        contents <- inputTransform <$> getContents
        print $ part1 contents
        print $ part2 contents
    
    4 votes
  2. Comment on Day 16: Ticket Translation in ~comp

    Lynx
    (edited )
    Link
    Haskell Yep, this one was fun. Unlike some of the previous ones, it was a breeze to implement in haskell. Repo link day16.hs {-# LANGUAGE NamedFieldPuns #-} module Day16 where import AoC import...

    Haskell

    Yep, this one was fun. Unlike some of the previous ones, it was a breeze to implement in haskell.

    Repo link

    day16.hs
    {-# LANGUAGE NamedFieldPuns #-}
    
    module Day16 where
    
    import AoC
    
    import Data.List
    import Data.Maybe
    import qualified Data.Set as S
    import Data.Set (Set)
    import Text.ParserCombinators.ReadP
    import Text.Read.Lex
    
    data Field = Field { name :: String
                       , valids :: Set Int
                       } deriving (Show)
    
    type Ticket = [Int]
    
    data Input = Input { fields :: [Field]
                       , myTicket :: Ticket
                       , otherTickets :: [Ticket]
                       } deriving (Show)
    
    line :: ReadP a -> ReadP a
    line p = p <* char '\n'
    
    parseField :: ReadP Field
    parseField = do
        name <- many1 $ satisfy (/=':')
        string ": "
        ranges <- parseRange `sepBy` string " or "
        let valids = S.fromList . concat . map (uncurry enumFromTo) $ ranges
        return $ Field { name, valids }
        where parseRange = do
                n1 <- readDecP
                char '-'
                n2 <- readDecP
                return (n1, n2)
    
    parseTicket :: ReadP Ticket
    parseTicket = readDecP `sepBy` char ','
    
    parseInput :: ReadP Input
    parseInput = do
        fields <- many1 $ line parseField
        line $ string ""
        line $ string "your ticket:"
        myTicket <- line parseTicket
        line $ string ""
        line $ string "nearby tickets:"
        otherTickets <- many1 $ line parseTicket
        return $ Input {fields, myTicket, otherTickets }
    
    matchesAnyField :: [Field] -> Int -> Bool
    matchesAnyField fields n = any (n `S.member`) . map valids $ fields
    
    iterateUntilDone :: (a -> Maybe a) -> a -> a
    iterateUntilDone f x = case f x of
                             Just x' -> iterateUntilDone f x'
                             Nothing -> x
    
    data Resolve a = Resolved a | Choice (Set a) deriving (Show)
    
    resolve :: Ord a => [[a]] -> Maybe [a]
    resolve = sequence . map fromResolved . iterateUntilDone resolve' . map (Choice . S.fromList)
        where fromResolved (Resolved x) = Just x
              fromResolved _ = Nothing
    
    findSingletonChoice :: [Resolve a] -> Maybe (a, [Resolve a])
    findSingletonChoice (c@(Choice s):xs) | S.size s == 1 = let [x] = S.elems s
                                                            in Just (x, Resolved x:xs)
                                          | otherwise = (fmap.fmap) (c:) $ findSingletonChoice xs
    findSingletonChoice (x:xs) = (fmap.fmap) (x:) $ findSingletonChoice xs
    findSingletonChoice _ = Nothing
    
    resolve' :: Ord a => [Resolve a] -> Maybe [Resolve a]
    resolve' xs = do
        (x, xs') <- findSingletonChoice xs
        return $ map (dropChoice x) xs'
        where dropChoice x (Choice s) = Choice (S.delete x s)
              dropChoice _ r = r
    
    part1 :: Input -> Int
    part1 Input { fields, otherTickets } = sum . filter (not . matchesAnyField fields) . concat $ otherTickets
    
    part2 :: Input -> Int
    part2 Input { fields, myTicket, otherTickets } = product departureValues
        where validTickets = filter (all $ matchesAnyField fields) otherTickets
              columns = transpose validTickets
              fieldNames = fromJust . resolve . map findPossibleFields $ columns
              departureIndices = findIndices ("departure" `isPrefixOf`) fieldNames
              departureValues = map (myTicket !!) departureIndices
              findPossibleFields col = map name . filter (\field -> all (`S.member` valids field) col) $ fields
    
    main = runAoC (fromJust . oneCompleteResult parseInput) part1 part2
    
    AoC.hs (utility functions)
    module AoC
        ( (.:)
        , enumerate
        , oneCompleteResult
        , splitOnEmptyLines
        , runAoC
        )
    where
    
    import Data.Function (on)
    import Data.List (groupBy)
    import Text.ParserCombinators.ReadP
    
    (.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
    f .: g = (f .) . g
    infixl 8 .:
    
    enumerate :: Enum i => i -> [a] -> [(i, a)]
    enumerate _ [] = []
    enumerate i (x:xs) = (i, x) : enumerate (succ i) xs
    
    oneCompleteResult :: ReadP a -> String -> Maybe a
    oneCompleteResult p s = case readP_to_S (p <* eof) s of
                              [(x, "")] -> Just x
                              _ -> Nothing
    
    splitOnEmptyLines :: String -> [[String]]
    splitOnEmptyLines = filter (not . any null) . groupBy ((==) `on` null) . lines
    
    runAoC :: (Show r1, Show r2) => (String -> i) -> (i -> r1) -> (i -> r2) -> IO ()
    runAoC inputTransform part1 part2 = do
        contents <- inputTransform <$> getContents
        print $ part1 contents
        print $ part2 contents
    
    2 votes
  3. Comment on Day 6: Custom Customs in ~comp

    Lynx
    Link
    haskell again today, nice and concise. day6.hs Knowing about some data structures really pays off here - these are just set operations (union and intersection), so converting all the lines to sets...

    haskell again today, nice and concise.

    day6.hs Knowing about some data structures really pays off here - these are just set operations (union and intersection), so converting all the lines to sets and then folding them (in blank-line-separated groups) is really all it needs.
    import Data.Function (on)
    import Data.List (groupBy)
    import qualified Data.Set as S
    import           Data.Set (Set)
    
    splitOnEmptyLines :: String -> [[String]]
    splitOnEmptyLines = filter (not . any null) . groupBy ((==) `on` null) . lines
    
    main = do
        answerSets <- ((fmap . fmap) S.fromList . splitOnEmptyLines) <$> getContents
        let countSetsFolded f = sum $ map (S.size . foldr1 f) answerSets
        print $ countSetsFolded S.union
        print $ countSetsFolded S.intersection
    
    3 votes
  4. Comment on Day 2: Password Philosophy in ~comp

    Lynx
    Link
    After finishing a fairly boring python implementation, I decided to implement this as a digital electronic circuit, described in VHDL. The problem is perfect for this, since solving it needs only...

    After finishing a fairly boring python implementation, I decided to implement this as a digital electronic circuit, described in VHDL. The problem is perfect for this, since solving it needs only a small, fixed amount of state.

    The design consists of three main parts:

    • A parser that extracts the fields from the policy header, converts the ASCII-encoded decimal numbers to binary, and marks the start of actual password data for the verifier:
    parser.vhd
    library ieee;
    use ieee.std_logic_1164.all;
    
    entity parser is
    	port (
    		clk : in std_logic;
    		reset : in std_logic;
    		is_record : in std_logic;
    		is_data   : out std_logic;
    
    		char : in character;
    
    		num1, num2 : out natural range 0 to 99;
    		letter : out character
    	);
    end entity;
    
    architecture behaviour of parser is
    	type state_t is (S_NUM1, S_NUM2, S_LETTER, S_COLON, S_END_SPACE, S_DATA);
    	signal state : state_t := S_NUM1;
    
    	subtype digit is natural range 0 to 9;
    	type multiples_lookup_t is array(digit) of natural range 0 to 90;
    	constant TEN_MULTIPLES : multiples_lookup_t := (0, 10, 20, 30, 40, 50, 60, 70, 80, 90);
    
    	-- most significant digit of number
    	signal prev_digit : digit := 0;
    	signal current_digit : digit;
    	signal complete_num : natural range 0 to 99;
    
    	function char_to_digit(input : in character) return digit is
    	begin
    		if not (input < '0') and input <= '9' then
    			return character'pos(input) - character'pos('0');
    		else
    			return 0;
    		end if;
    	end function;
    begin
    	current_digit <= char_to_digit(char);
    	complete_num <= TEN_MULTIPLES(prev_digit) + current_digit;
    
    	process(clk)
    	begin
    		if rising_edge(clk) then
    			if reset then
    				prev_digit <= 0;
    				state <= S_NUM1;
    			else
    				prev_digit <= 0;
    
    				case state is
    					when S_NUM1 =>
    						if is_record then
    							if char = '-' then
    								state <= S_NUM2;
    							else
    								num1 <= complete_num;
    								prev_digit <= current_digit;
    							end if;
    						end if;
    					when S_NUM2 =>
    						if char = ' ' then
    							state <= S_LETTER;
    						else
    							num2 <= complete_num;
    							prev_digit <= current_digit;
    						end if;
    					when S_LETTER =>
    						letter <= char;
    						state <= S_COLON;
    					when S_COLON =>
    						state <= S_END_SPACE;
    					when S_END_SPACE =>
    						state <= S_DATA;
    					when S_DATA =>
    						if not is_record then
    							state <= S_NUM1;
    						end if;
    				end case;
    			end if;
    		end if;
    	end process;
    
    	is_data <= '1' when state = S_DATA else '0';
    end architecture;
    
    • A verifier that takes the policy information and a password stream and evaluates whether the password matches the policy (with two implementations, one for each part)
    verifier.vhd
    library ieee;
    use ieee.std_logic_1164.all;
    
    entity verifier is
    	port (
    		clk : in std_logic;
    		reset : in std_logic;
    		is_data : in std_logic;
    
    		num1, num2 : in natural range 0 to 99;
    		letter : in character;
    
    		char : in character;
    
    		verified : out std_logic
    	);
    end entity;
    
    architecture step1 of verifier is
    	signal count : natural range 0 to 99;
    begin
    	process(clk)
    	begin
    		if rising_edge(clk) then
    			if reset then
    				count <= 0;
    			elsif is_data then
    				if char = letter then
    					count <= count + 1;
    				end if;
    			end if;
    		end if;
    	end process;
    
    	verified <= '1' when num1 <= count and count <= num2 else '0';
    end architecture;
    
    architecture step2 of verifier is
    	signal count : natural range 1 to 99;
    	signal parity : std_logic;
    begin
    	process(clk)
    	begin
    		if rising_edge(clk) then
    			if reset then
    				count <= 1;
    				parity <= '0';
    			elsif is_data then
    				count <= count + 1;
    				if (count = num1 or count = num2) and char = letter then
    					parity <= not parity;
    				end if;
    			end if;
    		end if;
    	end process;
    
    	verified <= parity;
    end architecture;
    
    • A top entity that ties the previous parts together and counts the amount of successfully verified passwords
    top.vhd
    library ieee;
    use ieee.std_logic_1164.all,
        ieee.numeric_std.all;
    
    entity top is
    	generic (
    		COUNTER_WIDTH : positive;
    		STEP : natural range 1 to 2
    	);
    	port (
    		clk : in std_logic;
    		reset : in std_logic;
    		char  : in character;
    		is_record : in std_logic;
    		num_verified : out unsigned(COUNTER_WIDTH-1 downto 0)
    	);
    end entity;
    
    architecture behaviour of top is
    	signal is_data : std_logic;
    	signal num1, num2 : natural range 0 to 99;
    	signal letter : character;
    
    	signal prev_is_record : std_logic;
    	signal record_ended : std_logic;
    
    	signal verified : std_logic;
    begin
    	record_ended <= prev_is_record and not is_record;
    
    	parser_inst: entity work.parser
    		port map (
    			clk   => clk,
    			reset => reset,
    			is_record => is_record,
    			is_data   => is_data,
    			char   => char,
    
    			num1   => num1,
    			num2   => num2,
    			letter => letter
    		);
    
    	generate_verifier: if step = 1 generate
    		verifier_inst: entity work.verifier(step1)
    			port map (
    				clk => clk,
    				reset => reset or record_ended,
    				is_data => is_data,
    				num1   => num1,
    				num2   => num2,
    				letter => letter,
    				char   => char,
    				verified => verified
    			);
    	elsif step = 2 generate
    		verifier_inst: entity work.verifier(step2)
    			port map (
    				clk => clk,
    				reset => reset or record_ended,
    				is_data => is_data,
    				num1   => num1,
    				num2   => num2,
    				letter => letter,
    				char   => char,
    				verified => verified
    			);
    	else generate
    		assert false report "Bad value for ""step""" severity failure;
    	end generate;
    
    	process(clk)
    	begin
    		if rising_edge(clk) then
    			prev_is_record <= is_record;
    			if reset then
    				prev_is_record <= '0';
    				num_verified <= (others => '0');
    			elsif record_ended and verified then
    				num_verified <= num_verified + 1;
    			end if;
    		end if;
    	end process;
    end architecture;
    

    To actually use the design without having to set it up in hardware and toggling a bunch of switches for hours, there's also a simulation testbench that feeds a file into the circuit character-by-character, adds some framing information, and prints out the final number of verified passwords. VHDL isn't exactly an application programming language, so all the non-synthesizable constructs are a bit weird and quite Ada-y, but it's not actually all that bad.

    sim.vhd
    library ieee;
    use ieee.std_logic_1164.all,
        ieee.numeric_std.all;
    
    use std.textio.all;
    
    entity sim is
    	generic (
    		FILENAME : string := "input.txt";
    		COUNTER_WIDTH : positive := 12;
    		STEP : natural range 1 to 2
    	);
    end entity;
    
    architecture a of sim is
    	file file_handle : text open read_mode is FILENAME;
    	signal char_in : character;
    	signal clk, reset, is_record : std_logic;
    	signal num_verified : unsigned(COUNTER_WIDTH-1 downto 0);
    
    	procedure print(s: string) is
    		variable l : line;
    	begin
    		write(l, s);
    		writeline(output, l);
    	end procedure;
    begin
    	process
    		variable current_line : line;
    		variable current_char : character;
    		variable good : boolean;
    
    		procedure cycle_clock is
    		begin
    			wait for 10 ns;
    			clk <= '0';
    			wait for 10 ns;
    			clk <= '1';
    			wait for 0 ns;
    		end procedure;
    	begin
    		clk <= '0';
    		is_record <= '0';
    		char_in <= NUL;
    
    		reset <= '1';
    		cycle_clock;
    		reset <= '0';
    		cycle_clock;
    
    		lines_loop: loop
    			exit lines_loop when endfile(file_handle);
    			readline(file_handle, current_line);
    
    			is_record <= '1';
    
    			chars_loop: loop
    				read(current_line, current_char, good);
    				exit chars_loop when not good;
    
    				char_in <= current_char;
    				cycle_clock;
    			end loop;
    
    			is_record <= '0';
    			cycle_clock;
    		end loop;
    
    		cycle_clock;
    
    		print(to_string(to_integer(num_verified)));
    
    		wait;
    	end process;
    
    	top: entity work.top
    		generic map (
    			COUNTER_WIDTH => COUNTER_WIDTH,
    			STEP => STEP
    		)
    		port map (
    			clk => clk,
    			reset => reset,
    			char => char_in,
    			is_record => is_record,
    			num_verified => num_verified
    		);
    end architecture;
    
    3 votes
  5. Comment on Day 5: Binary Boarding in ~comp

    Lynx
    Link
    Started with haskell this time because it seemed like a good tool for the job; it was, but the whole parser business made it a bit more complicated than I would've liked. day5.hs import Data.List...

    Started with haskell this time because it seemed like a good tool for the job; it was, but the whole parser business made it a bit more complicated than I would've liked.

    day5.hs
    import Data.List (sort)
    import Data.Maybe (fromJust)
    import Numeric (readInt)
    import Text.ParserCombinators.ReadP
    
    -- utils
    
    oneCompleteResult :: ReadP a -> String -> Maybe a
    oneCompleteResult p s = case readP_to_S (p <* eof) s of
                              [(x, "")] -> Just x
                              _ -> Nothing
    
    runAoC :: (Show r1, Show r2) => (String -> i) -> (i -> r1) -> (i -> r2) -> IO ()
    runAoC inputTransform part1 part2 = do
        contents <- inputTransform <$> getContents
        print $ part1 contents
        print $ part2 contents
    
    -- end utils
    
    binarify :: String -> Maybe Int
    binarify = oneCompleteResult . readS_to_P $ readInt 2 (`elem` "BFLR") digitValue
        where digitValue 'F' = 0
              digitValue 'B' = 1
              digitValue 'L' = 0
              digitValue 'R' = 1
    
    findHole :: (Enum a, Eq a) => [a] -> Maybe a
    findHole (x:y:ys) | y == next = findHole $ y:ys
                      | otherwise = Just next
                      where next = succ x
    findHole _ = Nothing
    
    main = runAoC (fmap (fromJust . binarify) <$> lines) part1 part2
        where part1 = foldr1 max
              part2 = fromJust . findHole . sort
    
    5 votes
  6. Comment on Google confirms it's letting third parties scan your Gmail in ~tech

    Lynx
    Link Parent
    For something more easily associated with the site where it was used, there's also Subaddressing - with Gmail and a lot of others, user+something@example.com is the same as user@example.com.

    For something more easily associated with the site where it was used, there's also Subaddressing - with Gmail and a lot of others, user+something@example.com is the same as user@example.com.

    4 votes
  7. Comment on What if app stores were federated? in ~tech

    Lynx
    Link Parent
    Eh, not really. Usually repositories are created/managed by the distribution, and many people around the world host mirrors of that master. Ubuntu PPAs might be similar from what I've seen, not...

    Eh, not really. Usually repositories are created/managed by the distribution, and many people around the world host mirrors of that master. Ubuntu PPAs might be similar from what I've seen, not totally sure though.

    4 votes
  8. Comment on GPS monitoring of great white sharks reveals previously unknown feeding ground and strange diving behaviors in ~science

  9. Comment on How do you keep pypi programs up to date? in ~comp

    Lynx
    Link Parent
    The AUR are just user produced build files, and they usually get updated (or flagged out-of-date) as soon as a new upstream version is out. Arch in general is rolling-release, so most software in...

    The AUR are just user produced build files, and they usually get updated (or flagged out-of-date) as soon as a new upstream version is out. Arch in general is rolling-release, so most software in the repositories is at most a week or two out of date. Debian tends to be more on the scale of months or years.

    5 votes
  10. Comment on How do you keep pypi programs up to date? in ~comp

    Lynx
    Link Parent
    Personally I've only ever found one python package that wasn't in the AUR, so I added it. Maintainers are usually pretty good at keeping up to date with releases too. But sure, if you need...

    System python based packages are almost always far too limited/old for my use cases.

    Personally I've only ever found one python package that wasn't in the AUR, so I added it. Maintainers are usually pretty good at keeping up to date with releases too. But sure, if you need something actually bleeding-edge (i.e. git master), or need to develop your own python software, use a virtualenv, possibly with a wrapper like Conda.

    2 votes
  11. Comment on How do you keep pypi programs up to date? in ~comp

    Lynx
    Link
    for pip, there are a few suggestions here: https://stackoverflow.com/questions/2720014/upgrading-all-packages-with-pip I just use pacman and AUR packages though, one package manager on a system is...

    for pip, there are a few suggestions here: https://stackoverflow.com/questions/2720014/upgrading-all-packages-with-pip

    I just use pacman and AUR packages though, one package manager on a system is plenty.

    2 votes
  12. Comment on I'm new to Tildes. What must I know ? in ~tildes

    Lynx
    Link
    First of all, read the docs. Not yet, as far as I know (other than the several competing ways to address the users of the site - "Tildoes", "Tilderinos", etc.) There are no mods, just @Deimos...

    First of all, read the docs.

    • Are there any private jokes or slang I should know to understand everything ? (like reddit's "/s", "FBI open up" or the verb "lurk")

    Not yet, as far as I know (other than the several competing ways to address the users of the site - "Tildoes", "Tilderinos", etc.)

    • Are "mods" uncompromising ?

    There are no mods, just @Deimos really. As long as you don't blatantly violate the code of conduct, it's unlikely that anything will be removed or anyone banned.

    • There's no downvote. Do I need to make a thoughtful comment every time I disagree ?

    Good thing there's no downvote then, seeing how you'd abuse it as a "disagree button" ;) yes, if you want to add your opinion, write a comment.

    16 votes
  13. Comment on Factorio Friday Facts #259 - Scan-codes, prototype IDs, HR worm in ~games

    Lynx
    Link
    I read over it multiple times but still don't understand what they did to the ID mapping system. It's just written in such a confusing way. at first it's mentioned that the "ID mapping" maps...

    I read over it multiple times but still don't understand what they did to the ID mapping system. It's just written in such a confusing way.

    • at first it's mentioned that the "ID mapping" maps string names to numeric IDs, but everything after shows it the other way around. Yeah, they're equivalent if both are mathematical sets, but "setting the ID to 0" definitely breaks that requirement.
    • "Any time something was removed it was signalled by setting the ID at that location in the mapping to 0." - the graphic afterwards shows the name string set to nil, with the ID untouched, which is it now?
    • with the new system, "[IDs] are never allowed to change for the lifetime of the program", the graphic afterwards promptly shows IDs changing to completely different names.

    Oh well, I get what the end result was: enabling migrating from one ID mapping to another.

    2 votes
  14. Comment on Tact filters in ~humanities

    Lynx
    Link Parent
    Oh yeah, I missed that. But if we ignore the author's shitty attitude, those are actually pretty amazing guidelines and more people should read them before posting "it doesn't work"-style issues.

    Oh yeah, I missed that. But if we ignore the author's shitty attitude, those are actually pretty amazing guidelines and more people should read them before posting "it doesn't work"-style issues.

    2 votes
  15. Comment on Tact filters in ~humanities

    Lynx
    Link Parent
    I'm curious, why do you think so? I just read over it again and couldn't find anything out of place, other than the answers in the "Q&A" section (no need to get snarky, just ignore it).

    How To Ask Questions The Smart Way, one the most obnoxious essays in contemporary history

    I'm curious, why do you think so? I just read over it again and couldn't find anything out of place, other than the answers in the "Q&A" section (no need to get snarky, just ignore it).

    3 votes
  16. Comment on Flight simulators: Do you play any? Which planes do you pilot the most? Do you have a home cockpit? in ~games

    Lynx
    Link
    I own FSX, but have never really played much. Bought a used HOTAS a few years ago, but it was broken, haven't really bothered since. X-Plane 11 looks promising, if expensive, and it's even on...

    I own FSX, but have never really played much. Bought a used HOTAS a few years ago, but it was broken, haven't really bothered since.

    X-Plane 11 looks promising, if expensive, and it's even on Linux natively. I might give that a go some time.

    1 vote
  17. Comment on Learna project reverts blacklisting in license in ~comp

    Lynx
    Link Parent
    That just sounds unenforceable, useless and maybe even harmful (because it makes the whole license kinda iffy). What's "good" and "evil" in the eye of the law?

    The Software shall be used for Good, not Evil.

    That just sounds unenforceable, useless and maybe even harmful (because it makes the whole license kinda iffy). What's "good" and "evil" in the eye of the law?

    4 votes
  18. Comment on Experiences with aphantasia or what does visualizing look/feel like? in ~talk

    Lynx
    Link Parent
    Haven't had time to watch it yet, but I'm pretty sure I'm not face blind. I don't have much trouble recognizing people, just with visualizing faces.

    Haven't had time to watch it yet, but I'm pretty sure I'm not face blind. I don't have much trouble recognizing people, just with visualizing faces.

    1 vote
  19. Comment on Fixing a broken popcorn machine in ~hobbies

    Lynx
    Link
    Imgur links are broken for me on Android Firefox, they just redirect to the main imgur page.

    Imgur links are broken for me on Android Firefox, they just redirect to the main imgur page.

  20. Comment on Experiences with aphantasia or what does visualizing look/feel like? in ~talk

    Lynx
    Link Parent
    No, not really, funnily enough. It's not that I can't remember faces, or can't process them (face blindness), but just that I can't recall them. I can pretty much always tell that I've seen...

    No, not really, funnily enough. It's not that I can't remember faces, or can't process them (face blindness), but just that I can't recall them. I can pretty much always tell that I've seen someone before, but anything more than that (name, story, where I met them, etc) is hard. I guess it's similar to Alzheimer's/dementia, where you just lose access to memories, not the memories themselves? With a few pointers normally it all comes back.

    The only thing I'm quite good at recalling are spacial and "photographic" memory (if you can all it that, nothing crazy like pages of numbers, just imagery in general). I should probably look into mind palaces.