haskell中的记录或简单ADT几乎等同于盒装元组。 有没有办法(理想情况下是一些花哨的扩展或来自haksell平台的lib)允许在这种类型和元组之间进行转换?
我(相当)是haskell的新手,我试图在Haskell中构建一些报告工具。这涉及读/写csv文件和数据库表。使用元组的事情非常简单,但在使用普通类时需要一些锅炉板。 样板接缝在两种方式上几乎完全相同,但我没有找到一种很好的方法只做一次,除了可能进行转换(数据< - > tuple)并使用从元组到CSV的本机转换/表。
到目前为止我得到的所有答案都假设我需要一些完全通用的东西,我想要元组。 我不想要元组,我有元组,我不想要它们,因此需要转换它们。 事实上,我只是想减少锅炉板(到0 :-)),但我不需要为每种类型都提供相同名称的功能。
例如,我可以通过取消其中一个构造函数来轻松地将元组转换为任何元素。 问题是我需要uncurryN,我无法在任何地方找到(除了模板haskell教程)。 反过来更难做到。
我没有要求解决方案(我得到的所有答案都很棒,因为我不熟悉Haskell中不同的元编程方式)但更多,因为我不喜欢如果车轮已经存在(例如这个不可靠的N,可以用手写到20并装在漂亮的包装中),就像重新发明轮子一样。
显然存在一个不成熟的包,但它仍然解决了一半的问题。
答案 0 :(得分:8)
您可能需要查看GHC.Generics。它基本上将每个ADT编码为产品((,)
)和总和(Either
)。例如,以下是使用泛型显示此表示的方法:
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
import GHC.Generics
class Tuple p where
showRepresentation :: p -> String
default showRepresentation :: (Generic p, GTuple (Rep p)) => p -> String
showRepresentation = gshowRepresentation . from
class GTuple p where
gshowRepresentation :: p x -> String
instance Tuple k => GTuple (K1 i k) where
gshowRepresentation (K1 t) = showRepresentation t
instance GTuple f => GTuple (M1 i c f) where
gshowRepresentation (M1 f) = gshowRepresentation f
instance (GTuple f, GTuple g) => GTuple (f :*: g) where
gshowRepresentation (f :*: g) = gshowRepresentation f ++ " * " ++ gshowRepresentation g
-- Some instances for the "primitive" types
instance Tuple Int where showRepresentation = show
instance Tuple Bool where showRepresentation = show
instance Tuple () where showRepresentation = show
--------------------------------------------------------------------------------
data Example = Example Int () Bool deriving Generic
instance Tuple Example
main :: IO ()
main = putStrLn $ showRepresentation $ Example 3 () False
-- prints: 3 * () * False
您可以在GHC.Generics模块中找到更多文档。我也找到了关于它的论文,A Generic Deriving Mechanism for Haskell非常易读(这是我读过的为数不多的论文之一)。
答案 1 :(得分:4)
模块lens和Control.Lens.Iso中的Control.Lens.Wrapped库有一些实用程序,可以更轻松地处理此类转换。不幸的是,目前此类案例的模板Haskell machinery不处理记录,只处理新类型,因此您必须自己定义实例。例如:
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
import Control.Lens
data Foo = Foo { baz :: Int, bar :: Int } deriving Show
instance Wrapped Foo where
type Unwrapped Foo = (Int,Int)
_Wrapped' = iso (\(Foo baz' bar') -> (baz',bar')) (\(baz',bar') -> Foo baz' bar')
现在我们可以轻松包装和打开包装:
*Main> (2,3) ^. _Unwrapped' :: Foo
Foo {baz = 2, bar = 3}
*Main> Foo 2 3 ^. _Wrapped'
(2,3)
我们还可以使用对元组起作用的函数修改Foo
:
*Main> over _Wrapped' (\(x,y)->(succ x,succ y)) $ Foo 2 5
Foo {baz = 3, bar = 6}
相反:
*Main> under _Wrapped' (\(Foo x y)->(Foo (succ x) (succ y))) $ (2,5)
(3,6)
答案 2 :(得分:1)
如果你想要真正的n元组(而不仅仅是其他一些语义上相同的数据),没有模板Haskell就会很麻烦。
例如,如果要转换
data Foo = Foo Int String Int
data Bar = Bar String String Int Int
到
type FooTuple = (Int, String, Int)
type BarTuple = (String, String, Int, Int)
GHC.Generics
和SYB
都会有问题,因为结果类型需要根据数据类型的字段而有所不同。尽管两者都是calle“元组”,但(Int, String, Int)
和(String, String, Int, Int)
是完全独立的类型,并且没有方便的方法以通用方式处理n-arity元组。以下是使用GHC.Generics
:
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DeriveGeneric #-}
-- Generic instance to turn generic g x into some n-tuple whose exact
-- type depends on g.
class GTuple g where
type NTuple g
gtoTuple :: g x -> NTuple g
-- Unwarp generic metadata
instance GTuple f => GTuple (M1 i c f) where
type NTuple (M1 i c f) = NTuple f
gtoTuple = gtoTuple . unM1
-- Turn individual fields into a Single type which we need to build up
-- the final tuples.
newtype Single x = Single x
instance GTuple (K1 i k) where
type NTuple (K1 i k) = Single k
gtoTuple (K1 x) = Single x
-- To combine multiple fields, we need a new Combine type-class.
-- It can take singular elements or tuples and combine them into
-- a larger tuple.
--
class Combine a b where
type Combination a b
combine :: a -> b -> Combination a b
-- It's not very convenient because it needs a lot of instances for different
-- combinations of things we can combine.
instance Combine (Single a) (Single b) where
type Combination (Single a) (Single b) = (a, b)
combine (Single a) (Single b) = (a, b)
instance Combine (Single a) (b, c) where
type Combination (Single a) (b, c) = (a, b, c)
combine (Single a) (b, c) = (a, b, c)
instance Combine (a,b) (c,d) where
type Combination (a,b) (c,d) = (a,b,c,d)
combine (a,b) (c,d) = (a,b,c,d)
-- Now we can write the generic instance for constructors with multiple
-- fields.
instance (Combine (NTuple a) (NTuple b), GTuple a, GTuple b) => GTuple (a :*: b) where
type NTuple (a :*: b) = Combination (NTuple a) (NTuple b)
gtoTuple (a :*: b) = combine (gtoTuple a) (gtoTuple b)
-- And finally the main function that triggers the tuple conversion.
toTuple :: (Generic a, GTuple (Rep a)) => a -> NTuple (Rep a)
toTuple = gtoTuple . from
-- Now we can test that our instances work like they should:
data Foo = Foo Int String Int deriving (Generic)
data Bar = Bar String String Int Int deriving (Generic)
fooTuple = toTuple $ Foo 1 "foo" 2
barTuple = toTuple $ Bar "bar" "asdf" 3 4
上述工作但需要大量工作(我无法快速弄清楚
如果可以在不使用UndecidableInstances
)的情况下完成。
现在 想要做的事情可能只是跳过元组并使用泛型
直接转换为CSV。我假设您正在使用csv-conduit
并希望生成ToRecord
类型类的实例。
这是
的一个例子{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics
import Data.ByteString (ByteString)
import Data.CSV.Conduit.Conversion
class GRecord g where
gToRecord :: g x -> [ByteString]
instance GRecord f => GRecord (M1 i c f) where
gToRecord = gToRecord . unM1
instance ToField k => GRecord (K1 i k) where
gToRecord (K1 x) = [toField x]
instance (GRecord a, GRecord b) => GRecord (a :*: b) where
gToRecord (a :*: b) = gToRecord a ++ gToRecord b
genericToRecord :: (Generic a, GRecord (Rep a)) => a -> Record
genericToRecord = record . gToRecord . from
现在您可以轻松为自定义类型创建实例。
data Foo = Foo Int String Int deriving (Generic)
data Bar = Bar String String Int Int deriving (Generic)
instance ToRecord Foo where
toRecord = genericToRecord
instance ToRecord Bar where
toRecord = genericToRecord
回答您的更新问题:您可能对tuple
包(尤其是Curry
)感兴趣,其中包含uncurryN
和curryN
的实现,用于最多的元组15个元素。
答案 3 :(得分:0)
在某些情况下,您可以使用unsafeCoerce。函数的名称应该是一个非常明确的警告,要非常小心。特别是,行为取决于编译器甚至编译器版本。
data Bar = Bar Text Text
tupleToBar :: (Text, Text) -> Bar
tupleToBar = unsafeCoerce