[Haskell-cafe] QuickCheck invariants for AST transformations

Joel Reymont joelr1 at gmail.com
Tue May 8 05:06:32 EDT 2007


I'm looking for suggestions on how to create invariants for the  
following AST transformation code. Any suggestions are appreciated!

I asked this question before and Lennart suggested abstract  
interpretation as a solution. This would require interpreters for  
both ASTs to determine that the result they achieve is the same. I  
don't fancy writing a C# interpreter, though, so I'm looking for an  
easier way out.

	Thanks, Joel

[1] http://tinyurl.com/368whq

---

instance SharpTransform C.Type Type where
     toSharp C.TyInt = return TyInt
     toSharp C.TyFloat = return TyFloat
     toSharp C.TyStr = return TyStr
     toSharp C.TyBool = return TyBool
     toSharp (C.TyArray x) = liftM2 TyArray (toSharp x) (return [])
     toSharp (C.TySeries C.TyFloat) = return $ TyCustom "DataSeries"
     toSharp (C.TySeries x) = error $ "Unsupported series type: " ++  
show x
     toSharp (C.TyProp x) = toSharp x
     toSharp C.TyUnit = return TyVoid

instance SharpTransform C.VarIdent VarIdent where
     toSharp (C.VarIdent x) = return $ VarIdent x

instance SharpTransform (Maybe C.Expr) (Maybe Expr) where
     toSharp Nothing = return Nothing
     toSharp (Just e) = liftM Just (toSharp e)

instance SharpTransform C.Subscript [Expr] where
     toSharp xs = mapM toSharp xs

instance SharpTransform C.BarsAgo Expr where
     toSharp C.Now = return $ Int 0
     toSharp (C.BarsAgo e) = toSharp e


--
http://wagerlabs.com/







More information about the Haskell-Cafe mailing list