0

I im trying to implement a small and simple open type component structure in Haskell.
The goal is to easily allow function and type extension by creating new components in other modules while preserving type safety at compile time.

I managed to implement a recursive search function by component type (find, in CompFinder), and it works well in the simple tests i tried. However i need to write trivial instances for CompFinder for non-composite components and multiple instances with the only difference being the component type for the CompFinder CompMix instance.

I am aware of Derive for automatic code generation for instance deriving but I would like a simpler solution if there is one, the compiler doing the code generation in the worst case, if possible.

So the questions are: How can I modify this system to simplify the writing of new Components?
or: How can I tell GHC to automatically generate CompFinder instances since only the type change in the different definitions?

Perhaps by doing something like this:

instance (Component a, CompFinder a T, Component b, CompFinder b T) => CompFinder (CompMix a b) T where
    find (CompMix x y ) = (find x :: [T]) ++ (find y :: [T])

where T would by a type parameter

Or maybe by writing CompFinder so it automatically works for all Components.

This is the full code:

--ghc 7.10
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}

-- Defined in the library module
class Component a

class ComponentMix a where -- Allow recursive component aggregation
    add :: b -> c -> a b c

class (Component a, Component b) => CompFinder a b where -- class that need a new instance for each new component type
    find :: a -> [b]
    find _ = []

-- Defined in the user module
data CompMix a b = CompMix a b deriving (Show, Eq)

instance ComponentMix CompMix where
    add x y = ( CompMix x y )

instance (Component a, Component b) => Component (CompMix a b)

-- Two simple component types that can be defined in another module
data Position = Pos Int Int deriving (Show, Eq, Ord)
data Name = Name String deriving (Show, Eq)          

instance Component Position
instance CompFinder Position Position where -- Trivial instance
    find x = [x]
instance CompFinder Position Name           -- Trivial instance

instance Component Name
instance CompFinder Name Name where -- Trivial instance
    find x = [x]
instance CompFinder Name Position   -- Trivial instance

instance (Component a, CompFinder a Name, Component b, CompFinder b Name) => CompFinder (CompMix a b) Name where
    find (CompMix x y ) = (find x :: [Name]) ++ (find y :: [Name])

instance (Component a, CompFinder a Position, Component b, CompFinder b Position) => CompFinder (CompMix a b) Position where
    find (CompMix x y ) = (find x :: [Position]) ++ (find y :: [Position])

main = print $ (find (CompMix (Name "Henri") (CompMix (Pos 1 2) (Name "Julie") ) ) :: [Position] ) -- Correctly outputs [Pos 1 2]
  • This looks a bit like the extensible record [question I answered a week or so ago](https://stackoverflow.com/a/44666983/3072788). Obviously not a duplicate but probably relevant. – Alec Jun 29 '17 at 15:05
  • 1
    It's unclear what you really want to achieve. Can you give an example of the code you would *like* to write? It seems like you want to generate boilerplate for the `Position` and `Name` types - if so, Template Haskell is probably the easiest way to do so. To me this is reminiscent of extensible records (for which there are a throng of libraries already - take your pick!), or generic programming idioms as implemented by e.g. `syb` or `uniplate`. In any case, don't write it yourself - research the available technology and see if any works for you. – user2407038 Jun 29 '17 at 17:11
  • I am still learning Haskell but after I learned about the expression problem, I thought I should try to solve it in a simple problem using what I already learned. @Alec That seems like the sort of structure I want to create indeed. But at the moment I don't even really understand the extensions you used for getting it to work. –  Jun 29 '17 at 18:31
  • @user2407038 Unfortunately, these tools like Template Haskell and syb seems too much complicated to resolve this (seemingly ?) simple problem. If these are the idiomatic/preferred way of getting this sort of problem to work, then I will look at them in detail. I only thought there was a solution that involved no code generation at all. –  Jun 29 '17 at 18:32
  • If you are looking for a Haskell solution to the expression problem (although I don't see that in the question) then [this](http://okmij.org/ftp/tagless-final/index.html) is a very powerful technique. Also, I think you've made this mistake of assuming that the expression problem is a simple problem (it's not - accept that hard problems have complicated solutions); and that technologies which you do not yet understand must be complicated. And my previous comment still stands: can you give an example of what you would like to write? – user2407038 Jun 29 '17 at 18:51
  • Finally, it seems to me this question is about learning - if so, then you must read the existing literature; trying to derive things from first principles yourself is at best tedious, and at worst takes you down the entirely incorrect path. By reading the literature, you find out whether the problem you are trying to solve has already been explored a thousand times over, or a slight variation on a well-known problem, or if you are trying to solve a brand new, nearly unknown problem. Then you will be in a good position to ask a more concrete question. – user2407038 Jun 29 '17 at 18:54
  • @user2407038 You're right, I only need to find the right documentation, beginning with the basics. Also, sorry for not being clear enough about this problem being in relation to the expression problem, I thought it was implied by the "Open" and "easy to extend" keywords. This [link](https://oleksandrmanzyuk.wordpress.com/2014/06/18/from-object-algebras-to-finally-tagless-interpreters-2/) is what I read before trying myself. This is concrete in a way because I'm trying to implement a concrete component system for a small video game. Now I guess I just need to read all of this papers. –  Jun 29 '17 at 19:28
  • Your link describes one technique ("finally tagless interpreters") which is precisely the same one described in one of my links (to be explicit, [this one](http://okmij.org/ftp/tagless-final/index.html)). That resource gives a derivation of the strategy from the ground up - which I think would be an excellent resource for your purposes. My recommendation would be to begin with the code examples, lecture slides, etc., and to end by reading the papers (as opposed to reading the papers first). Good luck! – user2407038 Jun 29 '17 at 19:37
  • @user2407038 I think you should put this as an answer so OP can accept it. – Julian Leviston Jul 01 '17 at 02:00

1 Answers1

0

After looking at some Generic Haskell, I finally found an easier way than automatic derivation to avoid writing each instance for Finder (formerly CompFinder). By doing this way, we only need to define instances of Finder for the structural types defined by the user.

Start with some pragmas

{-# LANGUAGE MultiParamTypeClasses #-} -- allows functions at the type level
{-# LANGUAGE FlexibleContexts #-} -- allows using data types in typeclass declarations

Then define a simple Component wrapper. This way we will write the instance for the Finder only once for all the simple components.

data Component a = Comp a

Then define the Finder class, we will use MultiParamTypeClasses without Functional dependencies because we want to specify the return type to get the desired components:

class Finder s c where -- s is the structure and c the component
    find :: s -> [c]
    find _ = [] -- provides empty list on search fail

We can implement this for our wrapper, first with actual component and searched component matching.

instance {-# OVERLAPABLE #-} Finder (Component a) (Component a) where
    find (Comp o) = [Comp o]

We take advantage of the OVERLAPPABLE pragma to provide an empty list if components differs:

instance Finder (Component a) (Component b) where
    find (Comp o) = []

We can structure our components with a simple Mix (2-Tuple) for instance:

data Mix a b = Mix a b deriving (Show,Eq,Ord)
instance (Finder a (Component c), Finder b (Component c) ) => Finder (Mix a b) (Component c) where
    find (Mix x y) = find x ++ (find y)

Now let's define some components:

data Velocity = Vel Int Int deriving (Show,Eq,Ord)
data Name = Name String deriving (Show,Eq,Ord)

And finally:

myStruct = Mix (Comp $ Name "Julien") (Comp $ Vel 5 2)

-- we can use the return type to ask for a list of components of that type
Prelude> find myStruct :: [Component Name]
  [Comp (Name "Julien")]

Prelude> find myStruct :: [Component Velocity]
  [Comp (Vel 5 2)]

Prelude> find (Comp $ Name "Marie") :: [Component Velocity]
  []

This works with nested Mix too! The only downside is the use of the Component wrapper but it's fine.