我一直在努力使用一个应该返回嵌套元组的函数 - 具体来说,函数的输入给了我很多问题。简化版如下:
tupfnc :: ?????
tupfnc [a] = (a,())
tupfnc (a:as) = (a,tupfnc as)
这个想法是接受一个项目列表(比如[0,1,5,3])并将它们嵌入到这样的元组中:(0,(1,(5,(3,())) ))。
我的初衷是按照这样的声明:
tupfnc :: [a] -> (a,b)
但是,第三行(本例)会引发错误
Solver.hs:56:17: error:
• Couldn't match expected type ‘(a, b)’
with actual type ‘[(a, (a, b0))]’
• In the expression: [(a, tupfnc as)]
In an equation for ‘tupfnc’: tupfnc (a : as) = [(a, tupfnc as)]
• Relevant bindings include
as :: [a]
a :: a
tupfnc :: [a] -> (a, b)
有什么建议吗?
答案 0 :(得分:1)
除非您有关于列表长度的类型级别信息,否则这是不可能的。想象一下名为Vector
的列表变体,在这种情况下,您可以执行以下操作:
{-# LANGUAGE GADTs, PolyKinds, DataKinds, TypeFamilies, TypeOperators #-}
-- | Peano natural numbers
data Nat = Z | S Nat
-- Just for convenience...
type N0 = Z
type N1 = S N0
type N2 = S N1
type N3 = S N2
type N4 = S N3
type N5 = S N4
type N6 = S N5
type N7 = S N6
type N8 = S N7
type N9 = S N8
-- | Equivalent to a list, but carries information about its length with it
data Vector (n :: Nat) a where
Nil :: Vector Z a
(:-) :: a -> Vector n a -> Vector (S n) a
infixr 5 :-
现在,我们可以定义一个类型系列,将一个数字转换为适当的嵌套元组:
type family NestedTuple (n :: Nat) (a :: *) where
NestedTuple Z a = ()
NestedTuple (S n) a = (a, NestedTuple n a)
最后我们可以定义一个将Vector n a
转换为嵌套元组形式的函数。
toList :: Vector n a -> NestedTuple n a
toList Nil = ()
toList (x :- xs) = (x, toList xs)
你可以在GHCi上测试一下:
ghci> :set -XFlexibleContexts
ghci> toList ("foo" :- "bar" :- "baz" :- Nil)
("foo",("bar",("baz",())))