[Haskell-cafe] surprised by type class binding -- is this a bug?
Greg Meredith
lgreg.meredith at biosimilarity.com
Fri Dec 7 02:11:50 EST 2007
Haskellians,
i'm sure i don't understand type classes, yet. Still, i was surprised at
ghci's response to the code below. Clues gratefully accepted.
Best wishes,
--greg
-- transcript
-- Prelude> :l grn
-- [1 of 1] Compiling GeneticRegulatoryNetwork ( grn.hs, interpreted )
-- grn.hs:33:35:
-- Couldn't match expected type `b1' (a rigid variable)
-- against inferred type `b' (a rigid variable)
-- `b1' is bound by the type signature for `sequence' at grn.hs:25:36
-- `b' is bound by the instance declaration at grn.hs:31:0
-- Expected type: [b1]
-- Inferred type: [b]
-- In the expression: molecules
-- In the definition of `sequence':
-- sequence (Site l1 molecules) = molecules
-- Failed, modules loaded: none.
-- Prelude>
{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}
-- -*- mode: Haskell;-*-
-- Filename: grn.hs
-- Authors: lgm
-- Creation: Thu Dec 6 15:38:26 2007
-- Copyright: Not supplied
-- Description:
-- ----------------------------------------------------------------
module GeneticRegulatoryNetwork
where
data Segment p =
Nil
| Section [p] (Segment p)
deriving (Eq, Show)
class BindingMolecule b l | b -> l where
name :: b -> l
complement :: b -> b
complements :: b -> Bool
class Locale s l1 l2 | s -> l1 l2 where
label :: s -> l1
sequence :: (BindingMolecule b l2) => s -> [b]
provides :: (BindingMolecule b l2) => s -> [b] -> Bool
matches :: (BindingMolecule b l2) => s -> [b] -> Bool
data (BindingMolecule b l2) => Site b l1 l2 = Site l1 [b] deriving (Eq,
Show)
instance (BindingMolecule b l2) => Locale (Site b l1 l2) l1 l2 where
label (Site l1 _) = l1
sequence (Site l1 molecules) = molecules
provides (Site l1 molecules) molecules' = False -- tbd
matches (Site l1 molecules) molecules' = False -- tbd
--
L.G. Meredith
Managing Partner
Biosimilarity LLC
505 N 72nd St
Seattle, WA 98103
+1 206.650.3740
http://biosimilarity.blogspot.com
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20071206/5a8c1edd/attachment.htm
More information about the Haskell-Cafe
mailing list