Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Automatic conversion between tuples and Record

Record or simple ADT in haskell are pretty much equivalent to boxed tuples. Is there a way (ideally some fancy extensions or a lib from the haksell platform) which allow conversion between such type and tuples ?

I'm (fairly ) new to haskell and I'm trying to build some reporting tool in Haskell. This involves reading/writing csv files and database tables. Things are pretty much straight forward using tuples, but involve a bit of boiler plate when using plain class. The boilerplate seams nearly identical in both way, but I didn't find a nice way to do it only once, except maybe from doing a conversion (data <-> tuple) and use the native conversion from tuple to CSV/table.

Update

All the answer I got back so far, assumes that I need something totally generic and I want tuple. I don't want tuple, I have tuple and I don't want them, therefore the need to convert them. In fact I just want to reduce the boiler plate (to 0 :-)) but I don't need necessarily the function(s) to have the same name for every types.

For example I can easily convert a tuple to anything by uncurrying one of its constructors. The problem is I need uncurryN which I can't find anywhere (except in a template haskell tutorial). The reverse is harder to do.

I'm not asking for a solution (althout all the answers I got are greats because I'm not familiar whith the different way of meta-programming in Haskell) but more, as I don't like to reinvent the wheel, if the wheel existed already (for example this uncurryN, could have been written by hand till 20 and packed in nice package)

Updated2

Apparently a uncurry package exists, but it stills solves half the problem.

like image 524
mb14 Avatar asked Apr 27 '14 10:04

mb14


3 Answers

You might want to look at GHC.Generics. It basically encodes each ADT as products ((,)) and sums (Either). As an example, here is how you could show this representation using generics:

{-# 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

You can find more documentation in the GHC.Generics module. I also found the paper about it, A Generic Deriving Mechanism for Haskell to be quite readable (it was one of the few papers I read).

like image 100
bennofs Avatar answered Nov 09 '22 07:11

bennofs


The lens library, in modules Control.Lens.Iso and Control.Lens.Wrapped, has a few utilities that make working with such conversions easier. Unfortunately, at the moment the Template Haskell machinery for such cases does not handle records, only newtypes, so you'll have to define the instances yourself. For example:

{-# 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')

Now we can wrap and unwrap easily:

*Main> (2,3) ^. _Unwrapped' :: Foo
Foo {baz = 2, bar = 3}

*Main> Foo 2 3 ^. _Wrapped'
(2,3)

We can also modify a Foo using a function that works on the tuple:

*Main> over _Wrapped' (\(x,y)->(succ x,succ y))  $ Foo 2 5
Foo {baz = 3, bar = 6}

And the reverse:

*Main> under _Wrapped' (\(Foo x y)->(Foo (succ x) (succ y)))  $ (2,5)
(3,6)
like image 40
danidiaz Avatar answered Nov 09 '22 05:11

danidiaz


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.

like image 44
shang Avatar answered Nov 09 '22 07:11

shang