[Haskell-cafe] Selda, type operators and heterogeneous lists

Jake jake.waksbaum at gmail.com
Thu Apr 19 17:01:57 UTC 2018


I would argue that in this case existential types actually are the correct
tool. What you want to do is hide some amount of type information, which is
exactly what existential types do. Then, because createTable can handle any
Table a when you unwrap the Table from the existential type you can still
pass it to createTable.

Here's a sort of mock example:

```{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE LambdaCase #-}

import Control.Monad (forM_)

data Table a

data a :*: b where
  (:*:) :: a -> b -> a :*: b
infixr 1 :*:

type RowID = Int
type Text = String

categories :: Table (RowID :*: Text)
categories = undefined

expenses :: Table (RowID:*:Text:*:Double:*:RowID)
expenses = undefined

createTable :: Table a -> IO ()
createTable _ = return ()

data ExTable = forall a. ExTable (Table a)

main :: IO ()
main = forM_ [ExTable categories, ExTable expenses] (\case ExTable t ->
createTable t)
```

In your example this requires more boilerplate and doesn't seem much better
than [createTable categories, createTable expenses], but this provides a
way to actually have a list of tables of differing types without applying
createTable to them first and I think that's closer to what you were going
for.

On Sun, Apr 15, 2018 at 12:35 PM Marc Busqué <marc at lamarciana.com> wrote:

> Thanks for both answers. It wasn't what I had in mind, but surely it is
> just that I have to get used to Haskell strong typing. Until now I think
> I'm used to apply DRY beyond types :)
>
> So, from you answers, I can conclude that there is no way to tell
> something like the following in a type signature: "any type build with that
> type operators". Isn't it?
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20180419/fe6e04c0/attachment.html>


More information about the Haskell-Cafe mailing list