Dear,

I will try to explain what I'm trying to achieve, below you can find the code demonstrating where I'm at currently, and where I would like to ideally get, as well as the current compilation error.

Basically I'm working on a minilanguage that I would like to simulate. This language is based on a core concept which can in the example below is "Foo". Now there is a 'primitive' instance of Foo that is the list.
What I now want to do is make FooF an instance as well. FooF being a record based on a map that contains some other instances of Foo by name as well as code that will use this lookup table.

For instance (this is not definite syntax):
my pseudoproglanguage:
A = [1..10] (aka refer to the 'primitive' instance of Foo)
B = [1..10] (aka refer to the 'primitive' instance of Foo)
bar C = if dum B then bar A else bar B
dum C = dum A && dum B

I realize I need existentials for this, but I'm afraid that my type-fu is lacking in this area. Perhaps one of you could point me in the right direction.

With regards,
Christophe

------------------------------------------------------------------------------------------------------------
{-# OPTIONS_GHC -fglasgow-exts #-}
module FooBar where
import qualified Data.Map as M

class Foo f b | f -> b where
foo :: f a -> b
bar :: f a -> b -> b
dum :: f a -> b -> Bool

instance Foo [] Int where
foo c = 0
bar c i = i+1
dum c i = (length c == i)


data F b a = forall f. Foo f b => F (f a)

instance Foo (F b) b where
foo (F c) = F . foo $ c
bar (F c) i = bar c i
dum (F c) i = dum c i

data FooF b a = FooF {
cols :: M.Map String (F b a),
barC :: M.Map String (F b a) -> b -> b,
dumC :: M.Map String (F b a) -> b -> Bool
}


instance Foo (FooF b) b where
foo c = fmap (foo) c
bar c i = barC c (cols c) i
dum c i = dumC c (cols c) i

makeFooF cols barC dumC = FooF {cols = cols, barC = barC, dumC = dumC}

-- Example:
-- makeFooF
-- [("A", [1..10]), ("B", [1..8])]
-- (\t -> if dum (M.lookup "A" t)
-- then bar (M.lookup "B" t)
-- else bar (M.lookup "A" t)
-- (\t -> dum (M.lookup "A" t) && dum (M.lookup "B" t)

-- Ideally this system would also allow to make some FooF that is based on another FooF, hence the reason for existentials



-- FooBar.hs:19:16:
-- Couldn't match the rigid variable `b' against `F b1 a'
-- `b' is bound by the instance declaration at FooBar.hs:18:0
-- Expected type: b
-- Inferred type: F b1 a
-- In the _expression_: (F . foo) $ c
-- In the definition of `foo': foo (F c) = (F . foo) $ c
-- 
-- FooBar.hs:31:12:
-- Couldn't match the rigid variable `b' against `f b1'
-- `b' is bound by the instance declaration at FooBar.hs:30:0
-- Expected type: b
-- Inferred type: f b1
-- In the application `fmap (foo) c'
-- In the definition of `foo': foo c = fmap (foo) c
-- Failed, modules loaded: none.
-- 
-----------------------------------------

-- 
Christophe Poucet
Ph.D. Student
Phone:+32 16 28 87 20
E-mail: Christophe (dot) Poucet (at) imec (dot) be
Website: http://notvincenz.com/  IMEC vzw – Register of Legal Entities Leuven VAT BE 0425.260.668 – Kapeldreef 75, B-3001 Leuven, Belgium – www.imec.be
*****DISCLAIMER*****
This e-mail and/or its attachments may contain confidential information. It is intended solely for the intended addressee(s).
Any use of the information contained herein by other persons is prohibited. IMEC vzw does not accept any liability for the contents of this e-mail and/or its attachments.
**********


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to