我想获取一个列表(或字符串)并将其拆分为N个元素的子列表。我如何在Haskell中完成?
示例:
mysteryFunction 2 "abcdefgh"
["ab", "cd", "ef", "gh"]
答案 0 :(得分:12)
答案 1 :(得分:11)
这是一个选项:
partition :: Int -> [a] -> [[a]]
partition _ [] = []
partition n xs = (take n xs) : (partition n (drop n xs))
这是该函数的尾递归版本:
partition :: Int -> [a] -> [[a]]
partition n xs = partition' n xs []
where
partition' _ [] acc = reverse acc
partition' n xs acc = partition' n (drop n xs) ((take n xs) : acc)
答案 2 :(得分:4)
您可以使用:
mysteryFunction :: Int -> [a] -> [[a]]
mysteryFunction n list = unfoldr takeList list
where takeList [] = Nothing
takeList l = Just $ splitAt n l
或者:
mysteryFunction :: Int -> [a] -> [[a]]
mysteryFunction n list = unfoldr (\l -> if null l then Nothing else Just $ splitAt n l) list
请注意,这会将所有剩余元素放在最后一个列表中,例如
mysteryFunction 2 "abcdefg" = ["ab", "cd", "ef", "g"]
答案 3 :(得分:1)
import Data.List
import Data.Function
mysteryFunction n = map (map snd) . groupBy ((==) `on` fst) . zip ([0..] >>= replicate n)
......开个玩笑......
答案 4 :(得分:1)
mysteryFunction x "" = []
mysteryFunction x s = take x s : mysteryFunction x (drop x s)
可能不是您想到的优雅解决方案。
答案 5 :(得分:1)
已经
了Prelude Data.List> :t either
either :: (a -> c) -> (b -> c) -> Either a b -> c
和
Prelude Data.List> :t maybe
maybe :: b -> (a -> b) -> Maybe a -> b
所以真的应该
list :: t -> ([a] -> t) -> [a] -> t
list n _ [] = n
list _ c xs = c xs
也是。有了它,
import Data.List (unfoldr)
g n = unfoldr $ list Nothing (Just . splitAt n)
没有它,
g n = takeWhile (not.null) . unfoldr (Just . splitAt n)
答案 6 :(得分:1)
一个奇特的答案。
在上面的答案中,你必须使用splitAt,它也是递归的。让我们看看如何从头开始构建递归解决方案。
Functor L(X)= 1 + A * X可以将X映射为1或将其拆分为一对A和X,并将List(A)作为其最小固定点:List(A)可以映射进入1 + A * List(A)并使用同构返回;换句话说,我们有一种方法来分解非空列表,只有一种方法来表示空列表。
Functor F(X)= List(A)+ A * X类似,但列表的尾部不再是空列表 - “1” - 所以仿函数能够提取值A或转X进入As列表。然后List(A)是它的固定点(但不再是最小的固定点),仿函数可以将任何给定的列表表示为List,或者作为一对元素和列表。实际上,任何余代数都可以“随意”“停止”分解列表。
{-# LANGUAGE DeriveFunctor #-}
import Data.Functor.Foldable
data N a x = Z [a] | S a x deriving (Functor)
(与添加以下简单实例相同):
instance Functor (N a) where
fmap f (Z xs) = Z xs
fmap f (S x y) = S x $ f y
考虑hylomorphism的定义:
hylo :: (f b -> b) -> (c -> f c) -> c -> b
hylo psi phi = psi . fmap (hylo psi phi) . phi
给定种子值,它使用phi生成f c,fmap递归地应用hylo psi phi,然后psi从fmapped结构f b中提取b。
这个仿函数的(共)代数对的同源性是splitAt:
splitAt :: Int -> [a] -> ([a],[a])
splitAt n xs = hylo psi phi (n, xs) where
phi (n, []) = Z []
phi (0, xs) = Z xs
phi (n, (x:xs)) = S x (n-1, xs)
这个代数提取头部,只要有一个头部要提取并且提取的元素的计数器不为零。这是因为仿函数是如何定义的:只要phi产生S x y,hylo就会将y作为下一个种子送入phi;一旦生成Z xs,仿函数就不再对它进行hylo psi phi,并且递归停止。
同时hylo会将结构重新映射为一对列表:
psi (Z ys) = ([], ys)
psi (S h (t, b)) = (h:t, b)
现在我们知道splitAt是如何工作的。我们可以使用apomorphism将它扩展到splitList:
splitList :: Int -> [a] -> [[a]]
splitList n xs = apo (hylo psi phi) (n, xs) where
phi (n, []) = Z []
phi (0, xs) = Z xs
phi (n, (x:xs)) = S x (n-1, xs)
psi (Z []) = Cons [] $ Left []
psi (Z ys) = Cons [] $ Right (n, ys)
psi (S h (Cons t b)) = Cons (h:t) b
这一次重新映射适合与apomorphism一起使用:只要它是正确的,apomorphism将继续使用hylo psi phi来生成列表的下一个元素;如果它是Left,它会在一个步骤中生成列表的其余部分(在这种情况下,只需使用[]完成列表。