Excel 列到 Int,反之亦然 - 寻求改进

Excel column to Int and vice-versa - improvements sought

在下面的代码中,我对功能感到满意,即代码产生了我期望的输出。但是,将 toCol 的长度与 toInt 的长度进行比较 - 我很想知道您是否可以为 trim 提供一些东西(即 toCol ) 向下。非常感谢!

-- given a spreadsheet column as a string
-- returns integer giving the position of the column
-- ex:
-- toInt "A" = 1
-- toInt "XFD" = 16384
toInt :: String -> Int
toInt = foldl fn 0
  where
    fn = \a c -> 26*a + ((ord c)-64)

-- given a integer returns
-- the column to be found at that position as a [Char]
-- ex:
-- toCol 1 = "A"
-- toCol 16384 = "XFD"
toCol :: Int -> [Char]
toCol n = toCol' n []
  where
    toCol' 0 a = a
    toCol' n a =
      let r = mod n 26 in
        case (r == 0) of
          True -> toCol' (div (n-1) 26) ('Z':a)
          False -> toCol' (div n 26) (chr(r + 64) : a)

每当递归地构建有限列表时,想想 unfoldr :: (b -> Maybe (a, b)) -> b -> [a] from Data.List (although because it unfolds from the wrong direction, we end up needing to reverse the list too). The syntax extension MultiWayIf 也有助于让事情变得更好。

{-# LANGUAGE MultiWayIf #-}

toCol :: Int -> [Char]
toCol = reverse . unfoldr (\n -> let r = n `mod` 26 in
          if | n == 0    -> Nothing
             | r == 0    -> Just ('Z'         , n-1 `div` 26)
             | otherwise -> Just (chr (r + 64), n   `div` 26))

请注意,这也会使 toCol 免分。如果您不想启用扩展程序而更喜欢模式匹配,您也可以这样做:

toCol :: Int -> [Char]
toCol = reverse . unfoldr (\n -> case (n, n `mod` 26) of 
                                   (0, _) -> Nothing
                                   (n, 0) -> Just ('Z'         , n-1 `div` 26)
                                   (n, r) -> Just (chr (r + 64), n   `div` 26))