• 0 Posts
  • 12 Comments
Joined 2 years ago
cake
Cake day: June 10th, 2024

help-circle


  • Depends on what you need from your computer. If it’s just web browsing and some light “office-like” tasks, it’s very easy, especially if you’ve interacted with a computer before. If you need some specialized hardware support or rely on some complicated proprietary app (looking at you Adobe), it can get complicated quickly.

    In any case there will be some pain as you get accustomed to the new OS. But overall it’s not as bad as it used to be.





  • The default standard power limit is still the same as it ever was on each USB version

    Nah, the default power limit started with 100 mA or 500 mA for “high power devices”. There are very few devices out there today that limit the current to that amount.

    It all begun with non-spec host ports which just pushed however much current the circuitry could muster, rather than just the required 500 mA. Some had a proprietary way to signal just how much they’re willing to push (this is why iPhones used to be very fussy about the charger you plug them in to), but most cheapy ones didn’t. Then all the device manufacturers started pulling as much current as the host would provide, rather than limiting to 500 mA. USB-BC was mostly an attempt to standardize some of the existing usage, and USB-PD came much later.


  • I don’t generally disagree, but

    You don’t just double the current you send over USB and expect cable manufacturers to adapt

    That’s pretty much how we got to the point where USB is the universal charging standard: by progressively pushing the allowed current from the initially standardized 100 mA all the way to 5 A of today. A few of those pushes were just manufacturers winging it and pushing/pulling significantly more current than what was standardized, assuming the other side will adapt.



  • 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.