Local type alias

Hi,

I am looking for a way to declare type alias in where section.

  where
    type Columns = '["start_ts", "rule_id", "rule_version", "matched", "ack"]
    joinedColumnNames :: String
    joinedColumnNames = symbolVal (Proxy @(JoinWith ", " Columns))
    columns :: Proxy Columns 
    columns = Proxy
   

As far as I know type cannot be in where, though I hope it is possible to bind a list of symbols to a type variable somehow.
I don’t want to put type alias above the class instance, because it contains lots of code.

I’ve wanted this from time to time, but it’s just not possible.

How about:

where
    joinedColumnNames :: String
    joinedColumnNames = symbolVal (joinWith (Proxy @", ") columns))
    columns :: Proxy ["start_ts", "rule_id", "rule_version", "matched", "ack"]
    columns = Proxy

joinWith :: Proxy x -> Proxy xs -> Proxy (JoinWith x xs)
joinWith _ _ = Proxy

Saying “bind” suggests you’re thinking about this procedurally; perhaps as a macro-like expansion. Rather say the type variable is ‘equivalent’ to the list of symbols.

You don’t give the code above your where: presumably it uses columns and joinedColumnNames. Perhaps they appear in the result of the outer expression? Perhaps that result is exported to other modules? Then the type of that result had better travel along with it. That’s why everything to do with types must be global scope.

In general type synonyms might have parameters, so the compiler can’t infer a specific type until it sees the synonym applied – which might be many modules away.

It turns out it is possible to introduce an extra type variable in
a class method instance, constrained with a literal!

class FooClass where
  foo :: String

instance FooClass () where
  foo :: 
    forall projCols. projCols ~
      '["start_ts", "rule_id", "rule_version", "matched", "ack"] => String
  foo = symbolVal (Proxy @(JoinWith ", " projCols))

type family JoinWith s xs where
  JoinWith s '[] = ""
  JoinWith s (e ': '[]) = e
  JoinWith s (x ': xs) = AppendSymbol x (AppendSymbol s (JoinWith s xs))

4 Likes

Thanks @yaitskov. Errm … yeuch!

1 Like