0

I'm trying to encode a type-level graph with some constraints on the construction of edges (via a typeclass) but I'm running into an "Illegal constraint in type" error when I try to alias a constructed graph. What's causing this issue? If it's unworkable, is there another way to encode the graph structure such that it can be built by type and folded over to yield a value-level representation of the graph?

Edit: Desiderata

I would like to be able to constrain the construction of a graph subject to the input and output nodes of any two operations.

For the sake of clarity, let's take the well-known case of length-indexed vectors.

An operation would take an input of some shape and potentially change it's length to the the length of output. An edge between two operations would need to ensure that the output of the first was compatible -- for some instance-defined notion of compatability -- with the input of the second. (Below, these constraints are omitted; the application requires dependently typed verification of the constraints and calculation of the types at compile.)

In order to define a new operation, S, that can be used with the existing operation(s) T (et al.), one should only need to add the data type S, the implementation of S _ and the necessary constraints for the function of S as an instance of the Edge typeclass.

--Pragmas are needed additionally for the project in which this snippet is included
{-# LANGUAGE TypeInType, DataKinds, PolyKinds, ScopedTypeVariables,
  FlexibleInstances, FlexibleContexts, GADTs, TypeFamilies,
  RankNTypes, LambdaCase, TypeOperators, TemplateHaskell,
  ConstraintKinds, PolyKinds, NoImplicitPrelude,
  UndecidableInstances, MultiParamTypeClasses, GADTSyntax,
  AllowAmbiguousTypes, InstanceSigs, DeriveFunctor,
  FunctionalDependencies #-}

-- Algebra.Graph is from the algebraic-graphs package
import qualified Algebra.Graph as AG
import Data.Singletons
import Data.Singletons.Prelude
import Data.Singletons.TypeLits
import Data.Kind


data T (ln::Nat) c = T c

class Edge operation n o 

instance 
  -- This would be something like: (LengthIsValidPrime x ~ True, y ~ DependentlyTypedCalculationForOpabc x) => 
  Edge (T l c) x y

data Flow :: * -> * where
        Empty :: Flow (a)
        Vertex :: (Edge a n o) => a -> Flow (a)
        Connect ::
            (Edge a x y, Edge a y z, Edge a x z) =>
            Flow (a) -> Flow (a) -> Flow (a)
        Overlay ::
            (Edge a x y, Edge a y z, Edge a x z) =>
            Flow (a) -> Flow (a) -> Flow (a)



type Test c = Connect (Vertex (T 24 c )) (Vertex (T 3 c))
--which fails with

--error:
--    • Illegal constraint in a type: Edge a0 x0 z0
--    • In the type ‘Connect (Vertex (T  24 c)) (Vertex (T 3 c))’
--      In the type declaration for ‘Test’

-- We want to be able to define a graph like so: 
type InputNode c = Vertex (T 100 c )
type ForkNode c = Vertex (T 10 c )
type NodeB c = Vertex (T 1  c )
type NodeC c = Vertex (T 1  c )
type PathA c = Connect (InputNode c) (ForkNode c)
type PathAB c = Connect (PathA c) (NodeB c)
type PathAC c = Connect (PathA c) (NodeC c)
type Output c = Vertex (T 2 c )
type Subgraph c = Overlay (Connect (PathAC c) (Output c)) (Connect (PathAB c) (Output c))

-- and eventually the trascription from the type-level graph to a value graph defined by Algebra.Graph
--foldFlow :: Flow a -> AG.Graph (Flow a)
--foldFlow Empty         = AG.empty
--foldFlow vt@(Vertex x) = AG.vertex vt
--foldFlow (Overlay x y) = AG.overlay  (foldFlow x) (foldFlow y)
--foldFlow (Connect x y) = AG.connect  (foldFlow x) (foldFlow y)
--runGraph :: Subgraph c
--runGraph = ...create a term-level Subgraph c so we can fold over it.

gist here

o1lo01ol1o
  • 440
  • 1
  • 5
  • 13
  • You'll have to be more specific about what you mean by "constraints on the construction of edges". The usual way of modelling graphs is to write down the set of nodes (eg `data Node = N1 | N2 | N3` for a graph of order 3, or `Fin n` for a graph of order `n` - types are sets, remember) and then write down the set of edges connecting those nodes (`data Edge from to where { E1 :: Edge N1 N2; E2 :: Edge N3 N2 }`). You can abstract over graphs by abstracting over the `Node` and `Edge` types (`data Graph n (e :: n -> n -> *) = Graph`). Then use a `class` to turn a `Graph` into an `AG.Graph`. – Benjamin Hodgson Jul 18 '17 at 18:41
  • What's causing the issue is that you can't promote GADT constructors with constraints other than equality constraints. – dfeuer Jul 18 '17 at 19:01
  • @dfeuer Sorry, import is added. It's from the algebraic-graphs package. I believe this should be sufficient to compile now (it's a simplification of the actual use case). – o1lo01ol1o Jul 18 '17 at 20:37
  • @dfeuer Ah, I didn't know that. – o1lo01ol1o Jul 18 '17 at 20:38
  • @BenjaminHodgson The order of the graph is not set; I'm looking to be able to define extensible nodes from the deep embedding represented by the GADT, which is an encoding derived from https://github.com/snowleopard/alga-paper – o1lo01ol1o Jul 18 '17 at 20:43
  • @dfeuer Yes, you were right, `Nat` and `Symbol` are defined in `singletons` and `*` is being obfuscated by something but ghc is happy enough with the one from `Data.Kind`. – o1lo01ol1o Jul 18 '17 at 21:01
  • I'm familiar with the Algebraic Graphs pearl. What do you mean by "extensible nodes"? Why are you trying to do this at the type level in the first place? – Benjamin Hodgson Jul 18 '17 at 21:06
  • @BenjaminHodgson The constraints on the `Edge` typeclass involve dependently typed shenanigans in order to make sure that two nodes can be joined in a compatible calculation. By "extensible" I mean the way one would desire a finite `AST` to be extensible: I want to be able to define new operations between nodes without knowledge of the whole `AST`. – o1lo01ol1o Jul 18 '17 at 21:13
  • It's going to be very difficult for us to help you with your design without concrete requirements. Could you give some examples, in code, of how you expect to use your system? Your use of terminology like "operations between nodes" is confusing without a clear example. – Benjamin Hodgson Jul 18 '17 at 21:24
  • @BenjaminHodgson I've added what I hope is some clarification. Let me know if I can be more clear. – o1lo01ol1o Jul 18 '17 at 22:25

0 Answers0