WorldSEnder
WorldSEnder

Reputation: 5054

Type juggling with GADTs at runtime

I'm designing a typed formal language, that is, a formal language where each letter has a representation of a specific type. So far, I have the following:

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE GADTs                 #-}
{-# LANGUAGE InstanceSigs          #-}
{-# LANGUAGE RankNTypes            #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE TypeInType            #-}
{-# LANGUAGE TypeFamilies          #-}

import Data.Kind

data Typey (s :: c) = Marker

class Character c where
  showVal :: Typey (s :: c a) -> a -> ShowS

class Character (Letter l) => Alphabet l where
  data family Letter l :: * -> *

data Symbol l (a :: Letter l s) where
  Terminal :: (Alphabet l) => s -> Symbol l (a :: Letter l s)

instance (Alphabet l) => Show (Symbol l a) where
  showsPrec d (Terminal val) = showVal (Marker :: Typey a) val

-- Example language
data ExampleLanguage = ExampleLanguage

instance Alphabet ExampleLanguage where
  data Letter ExampleLanguage a where
    Variable :: Letter ExampleLanguage String
    Comment :: Letter ExampleLanguage String
    EqualSign :: Letter ExampleLanguage ()
    Deref :: Letter ExampleLanguage ()

instance Character (Letter ExampleLanguage) where
--    showVal (_ :: Typey Variable) = showString
--    showVal (_ :: Typey Comment) = showString
--    showVal (_ :: Typey EqualSign) = const $ showString "="
--    showVal (_ :: Typey Deref) = const $ showString "*"
    showVal _ = const $ showString "error"
test :: Symbol ExampleLanguage Comment
test = Terminal "some comment"

You might have seen that I started to implement showVal but here, I have problems finishing the implementation. When I try uncommenting the lines in instance Letter (Character ExampleLanguage) the compiler is quick to complain:

main.hs:40:14: error:
    • Couldn't match type ‘a1’ with ‘()’
      ‘a1’ is a rigid type variable bound by
        the type signature for:
          showVal :: forall k (a :: k) a1 (s :: Character
                                                  ExampleLanguage a1).
                     Typey s -> a1 -> ShowS
        at main.hs:38:5
      Expected type: Typey 'EqualSign
        Actual type: Typey s
    • When checking that the pattern signature: Typey 'EqualSign
        fits the type of its context: Typey s
      In the pattern: _ :: Typey EqualSign
      In an equation for ‘showVal’:
          showVal (_ :: Typey EqualSign) = const $ showString "="
    • Relevant bindings include
        showVal :: Typey s -> a1 -> ShowS (bound at main.hs:38:5)

I'm not sure I understand what the compiler is complaining about. From the GADT definition of Character ExampleLanguage is could be clear that I'm trying to pattern match the different constructors, outputting a different String depending on the Letter.

How can I make this work? The data format is not fixed, feel free to modify it a little bit as long as a Symbol contains type information about the alphabet, letter and the letter's representational type.

Upvotes: 0

Views: 126

Answers (1)

Cirdec
Cirdec

Reputation: 24166

Pattern match on the constructors of the GADT, not on their types

{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE GADTs                 #-}
{-# LANGUAGE TypeFamilies          #-}

class Character c where
  showVal :: c a -> a -> ShowS

class Character (Letter l) => Alphabet l where
  data family Letter l :: * -> *

-- Example language
data ExampleLanguage = ExampleLanguage

instance Alphabet ExampleLanguage where
  data Letter ExampleLanguage a where
    Variable :: Letter ExampleLanguage String
    Comment :: Letter ExampleLanguage String
    EqualSign :: Letter ExampleLanguage ()
    Deref :: Letter ExampleLanguage ()

instance Character (Letter ExampleLanguage) where
    showVal Variable = showString
    showVal Comment = showString
    showVal EqualSign = const $ showString "="
    showVal Deref = const $ showString "*"

Include this tag in the Symbol so you can pattern match on it later.

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE TypeInType            #-}

data Symbol l (a :: Letter l s) where
  Terminal :: Letter l s -> s -> Symbol l (a :: Letter l s)

instance (Alphabet l) => Show (Symbol l a) where
  showsPrec d (Terminal tag val) = showVal tag val

test :: Symbol ExampleLanguage Comment
test = Terminal Comment "some comment"

Upvotes: 2

Related Questions