
Dear, I am writing a compiler (as you may have gathered from some previous messages). Anyways I am stuck with a small monadic issue. I mostly use indirect composite as this gives me the most flexibility with regards taking out parts of the AST, or decorating at whim. Basically the question regards how to implement a certain instance. Currently I have the code that can be seen below. What I would like to do is combine HasVars and Type (mostly because in my framework the two concepts shouldn't be divided from a design perspective) into one type class to clean it up a bit. However I fail to see how I would implement toType and fromType for the given instance. Is this feasible without resorting to ugly hacks? --- Types data MonoType mt = TyVar Var | TyConst Const [mt] deriving (Eq, Show) data PolyType mt = TyPoly [Var] mt deriving (Show) class Type mt where toType :: mt -> MonoType mt fromType :: MonoType mt -> mt class HasVars a where freeVars :: a -> [Var] occurs :: Var -> a -> Bool toPoly :: (HasVars a) => a -> PolyType a toPoly x = TyPoly (freeVars x) x instance HasVars a => HasVars (MonoType a) where freeVars (TyVar x) = [x] freeVars (TyConst _ xs) = nub . concatMap freeVars $ xs occurs x (TyVar y) = x == y occurs x (TyConst _ xs) = or . map (occurs x) $ xs Cheers, Christophe(vincenz) -- 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. **********

Christophe Poucet wrote:
What I would like to do is combine HasVars and Type (mostly because in my framework the two concepts shouldn't be divided from a design perspective) into one type class to clean it up a bit. However I fail to see how I would implement toType and fromType for the given instance. Is this feasible without resorting to ugly hacks?
{-# OPTIONS -fglasgow-exts #-} -- Multiparameter type classes? import List type Var = String type Const = String data MonoType mt = TyVar Var | TyConst Const [mt] deriving (Eq, Show) data PolyType mt = TyPoly [Var] mt deriving (Show) class Type a b where toType :: b -> a b fromType :: a b -> b freeVars :: a b -> [Var] occurs :: Var -> a b -> Bool instance Type MonoType Int -- yada, yada, yada... instance Type MonoType (MonoType Int) where freeVars (TyVar x) = [x] freeVars (TyConst _ xs) = nub . concatMap freeVars $ xs occurs x (TyVar y) = x == y occurs x (TyConst _ xs) = or . map (occurs x) $ xs

Hello Greg, The idea however is that MonoType is going to be used in a recursive way. For instance: newtype FMT = FMT MonoType FMT instance FMT where... And this definition will have to reside on recursive definitions. In the style of how HasVars was instantiated: instance HasVars a => HasVars (MonoType a) where freeVars (TyVar x) = [x] freeVars (TyConst _ xs) = nub . concatMap freeVars $ xs occurs x (TyVar y) = x == y occurs x (TyConst _ xs) = or . map (occurs x) $ xs So for Type instance Type a => Type (MonoType a) where ... That's where it becomes rather troublesome. Greg Buchholz wrote:
Christophe Poucet wrote:
What I would like to do is combine HasVars and Type (mostly because in my framework the two concepts shouldn't be divided from a design perspective) into one type class to clean it up a bit. However I fail to see how I would implement toType and fromType for the given instance. Is this feasible without resorting to ugly hacks?
{-# OPTIONS -fglasgow-exts #-}
-- Multiparameter type classes?
import List
type Var = String type Const = String
data MonoType mt = TyVar Var | TyConst Const [mt] deriving (Eq, Show)
data PolyType mt = TyPoly [Var] mt deriving (Show)
class Type a b where toType :: b -> a b fromType :: a b -> b freeVars :: a b -> [Var] occurs :: Var -> a b -> Bool
instance Type MonoType Int -- yada, yada, yada...
instance Type MonoType (MonoType Int) where freeVars (TyVar x) = [x] freeVars (TyConst _ xs) = nub . concatMap freeVars $ xs occurs x (TyVar y) = x == y occurs x (TyConst _ xs) = or . map (occurs x) $ xs
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- 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. **********

Christophe Poucet wrote:
The idea however is that MonoType is going to be used in a recursive way. For instance:
newtype FMT = FMT MonoType FMT
instance FMT where...
Er, I'll ignore this part.
And this definition will have to reside on recursive definitions. In the style of how HasVars was instantiated:
instance HasVars a => HasVars (MonoType a) where freeVars (TyVar x) = [x] freeVars (TyConst _ xs) = nub . concatMap freeVars $ xs occurs x (TyVar y) = x == y occurs x (TyConst _ xs) = or . map (occurs x) $ xs
So for Type
instance Type a => Type (MonoType a) where ...
That's where it becomes rather troublesome.
Yeah, after a certain point of complexity with type classes, it starts to look like C++ templates. How about something like... {-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-} import List type Var = String type Const = String data MonoType mt = TyVar Var | TyConst Const [mt] deriving (Eq, Show) data PolyType mt = TyPoly [Var] mt deriving (Show) class Type a b where toType :: b -> a b fromType :: a b -> b freeVars :: a b -> [Var] occurs :: Var -> a b -> Bool data Nil = Nil instance Type MonoType Nil where freeVars (TyVar x) = [x] freeVars (TyConst _ xs) = ["???"] instance (Type a b) => Type MonoType (a b) where freeVars (TyVar x) = [x] freeVars (TyConst _ xs) = nub . concatMap freeVars $ xs occurs x (TyVar y) = x == y occurs x (TyConst _ xs) = or . map (occurs x) $ xs main = print $ freeVars $ TyConst "foo" [TyConst "bar" [Nil], TyConst "baz" [Nil], TyVar "quux" ]

Im trying to use parsec to split a file, using the null character as a separator. Works fine with very small files but fails if they are a little bit larger. I guess parsec is trying to parse everthing first and print the results last. Am I doing something wrong or parsec is just not the right tool to the job? Atila module Main where import Text.ParserCombinators.Parsec import Data.Char email = do email <- anyChar `manyTill` char(chr(00)) return email emails = do emails <- many email return emails main = do input <- getContents parseTest emails input _______________________________________________________ Novo Yahoo! Messenger com voz: Instale agora e faça ligações de graça. http://br.messenger.yahoo.com/

On Thu, 2006-06-08 at 11:49 -0300, Atila Romero wrote:
Im trying to use parsec to split a file, using the null character as a separator. Works fine with very small files but fails if they are a little bit larger. I guess parsec is trying to parse everthing first and print the results last.
I think so.
Am I doing something wrong or parsec is just not the right tool to the job?
Right. In this case I would use lazy byte strings. module main where import qualified Data.ByteString.Lazy as B main = do input <- B.getContents let emails = B.split 0 input ... This lazily reads and splits into chunks using a 0 byte as separator. However this needs a fairly recent version of the 'fps' package. (In ghc 6.6 Data.ByteString and Data.ByteString.Lazy will be provided in the base package.) Duncan

Yes, with FPS it works! And is so elegant! Thanks! Atila Duncan Coutts wrote:
On Thu, 2006-06-08 at 11:49 -0300, Atila Romero wrote:
Im trying to use parsec to split a file, using the null character as a separator. Works fine with very small files but fails if they are a little bit larger. I guess parsec is trying to parse everthing first and print the results last.
I think so.
Am I doing something wrong or parsec is just not the right tool to the job?
Right. In this case I would use lazy byte strings.
module main where
import qualified Data.ByteString.Lazy as B
main = do input <- B.getContents let emails = B.split 0 input ...
This lazily reads and splits into chunks using a 0 byte as separator.
However this needs a fairly recent version of the 'fps' package. (In ghc 6.6 Data.ByteString and Data.ByteString.Lazy will be provided in the base package.)
Duncan
_______________________________________________________ Novidade no Yahoo! Mail: receba alertas de novas mensagens no seu celular. Registre seu aparelho agora! http://br.mobile.yahoo.com/mailalertas/

I'm not certain but I think this will still fail for exactly the piece that
you ignored, which is the crux of the problem.
On 6/8/06, Greg Buchholz
Christophe Poucet wrote:
The idea however is that MonoType is going to be used in a recursive way. For instance:
newtype FMT = FMT MonoType FMT
instance FMT where...
Er, I'll ignore this part.
And this definition will have to reside on recursive definitions. In the style of how HasVars was instantiated:
instance HasVars a => HasVars (MonoType a) where freeVars (TyVar x) = [x] freeVars (TyConst _ xs) = nub . concatMap freeVars $ xs occurs x (TyVar y) = x == y occurs x (TyConst _ xs) = or . map (occurs x) $ xs
So for Type
instance Type a => Type (MonoType a) where ...
That's where it becomes rather troublesome.
Yeah, after a certain point of complexity with type classes, it starts to look like C++ templates. How about something like...
{-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-} import List
type Var = String type Const = String
data MonoType mt = TyVar Var | TyConst Const [mt] deriving (Eq, Show)
data PolyType mt = TyPoly [Var] mt deriving (Show)
class Type a b where toType :: b -> a b fromType :: a b -> b freeVars :: a b -> [Var] occurs :: Var -> a b -> Bool
data Nil = Nil
instance Type MonoType Nil where freeVars (TyVar x) = [x] freeVars (TyConst _ xs) = ["???"]
instance (Type a b) => Type MonoType (a b) where freeVars (TyVar x) = [x] freeVars (TyConst _ xs) = nub . concatMap freeVars $ xs occurs x (TyVar y) = x == y occurs x (TyConst _ xs) = or . map (occurs x) $ xs
main = print $ freeVars $ TyConst "foo" [TyConst "bar" [Nil], TyConst "baz" [Nil], TyVar "quux" ]
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Christophe Poucet wrote:
I'm not certain but I think this will still fail for exactly the piece that you ignored, which is the crux of the problem.
-- You're not looking for this solution, right? import List type Var = String type Const = String data MonoType mt = TyVar Var | TyConst Const [mt] deriving (Eq, Show) data PolyType mt = TyPoly [Var] mt deriving (Show) newtype FMT = FMT (MonoType FMT) class Types a where freeVars :: a -> [Var] instance Types FMT where freeVars (FMT (TyVar x)) = [x] freeVars (FMT (TyConst _ xs)) = nub . concatMap freeVars $ xs main = print $ freeVars (FMT (TyConst "foo" [(FMT (TyVar "abc")), (FMT (TyVar "123")), (FMT (TyConst "bar" [(FMT (TyVar "www"))]))]))

I don't quite understand the problem, but maybe an example involving an explicit recursion operator will help. class Foo a where foo :: a instance Foo a => Foo (Maybe a) where foo = Just foo data Rec f = In (f (Rec f)) instance Foo (f (Rec f)) => Foo (Rec f) where foo = In foo compile with -fglasgow-exts and -fallow-undecidable-instances, and Rec Maybe will be an instance of Foo. I can't find the discussion, but if I recall correctly, ghc was extended as a result to allow regular instance deriviations rather than just finite one. I think Simon Peyton-Jones said it just required switching two lines. Brandon Christophe Poucet wrote:
I'm not certain but I think this will still fail for exactly the piece that you ignored, which is the crux of the problem.
On 6/8/06, *Greg Buchholz* < haskell@sleepingsquirrel.org mailto:haskell@sleepingsquirrel.org> wrote:
Christophe Poucet wrote: > The idea however is that MonoType is going to be used in a recursive > way. For instance: > > newtype FMT = FMT MonoType FMT > > instance FMT where...
Er, I'll ignore this part. > > And this definition will have to reside on recursive definitions. In the > style of how HasVars was instantiated: > > instance HasVars a => HasVars (MonoType a) where > freeVars (TyVar x) = [x] > freeVars (TyConst _ xs) = nub . concatMap freeVars $ xs > occurs x (TyVar y) = x == y > occurs x (TyConst _ xs) = or . map (occurs x) $ xs > > So for Type > > instance Type a => Type (MonoType a) where > ... > > That's where it becomes rather troublesome.
Yeah, after a certain point of complexity with type classes, it starts to look like C++ templates. How about something like...
{-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-} import List
type Var = String type Const = String
data MonoType mt = TyVar Var | TyConst Const [mt] deriving (Eq, Show)
data PolyType mt = TyPoly [Var] mt deriving (Show)
class Type a b where toType :: b -> a b fromType :: a b -> b freeVars :: a b -> [Var] occurs :: Var -> a b -> Bool
data Nil = Nil
instance Type MonoType Nil where freeVars (TyVar x) = [x] freeVars (TyConst _ xs) = ["???"]
instance (Type a b) => Type MonoType (a b) where freeVars (TyVar x) = [x] freeVars (TyConst _ xs) = nub . concatMap freeVars $ xs occurs x (TyVar y) = x == y occurs x (TyConst _ xs) = or . map (occurs x) $ xs
main = print $ freeVars $ TyConst "foo" [TyConst "bar" [Nil], TyConst "baz" [Nil], TyVar "quux" ]
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Brandon Moore wrote:
I don't quite understand the problem, but maybe an example involving an explicit recursion operator will help.
-- Maybe he's looking for something like... {-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-} import List type Var = String type Const = String data MonoType mt = TyVar Var | TyConst Const [mt] deriving (Eq, Show) newtype Fix f = In { out :: f (Fix f) } class Types a where freeVars :: a -> [Var] instance Types (a (Fix a)) => Types (Fix a) where freeVars (In x) = freeVars x instance Types a => Types (MonoType a) where freeVars (TyVar x) = [x] freeVars (TyConst _ xs) = nub . concatMap freeVars $ xs main = do print $ freeVars (TyConst "foo" [(In (TyVar "abc")), (In (TyVar "123")), (In (TyConst "bar" [(In (TyVar "www"))]))]))
participants (5)
-
Atila Romero
-
Brandon Moore
-
Christophe Poucet
-
Duncan Coutts
-
Greg Buchholz