If you want real n-tuples (and not just some other data that is semantically equivalent) it's going to be cumbersome without Template Haskell.
For example, if you want to convert
data Foo = Foo Int String Int
data Bar = Bar String String Int Int
into
type FooTuple = (Int, String, Int)
type BarTuple = (String, String, Int, Int)
both GHC.Generics
and SYB
will be problematic because the result type needs to be different depending on the fields of the datatype. Even though both are calle "tuples", (Int, String, Int)
and (String, String, Int, Int)
are completely separate types and there are no convenient ways to work with n-arity tuples in a generic fashion. Here's one way to achieve the above using 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
The above works but it requires a lot of work (and I couldn't quickly figure out
if it could be done without using UndecidableInstances
).
Now what you really want to do is probably just skip the tuples and use generics
to convert directly to CSV. I'm assuming you are using csv-conduit
and want to generate instances of the ToRecord
type-class.
Here's an example of that
{-# 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
And now you can easily make instances for your custom types.
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
In response to your updated question: you might be interested in the tuple
package (and especially Curry
) which contains implementations for uncurryN
and curryN
for tuples up to 15 elements.
deriving (Data)
– Up