That all depends... In theory all the HList stuff happens at compile time, and what you are left with is normal function application... Of course compilers arn't that good yet, but as a reasonable idea, consider just that value level... Most of the extra work is the packing/unpacking of pairs "(,)". I have used HList for database schemas like the "Cow" example database (see attached) with no problems. The DB code includes code to generate the database from this "Schema" so is doesn't need to be entered twice, and it also typechecks the database against the schema in a one-way extensional manner on program start. The performance of the DB app is good, better than with scripting languages like perl/python, and type-safe.
This code uses records made from HLists (see the paper for examples).

   Keean.


Joel Reymont wrote:

Keean,

I sort of gave up on HList for the time being since I found easier ways to solve my problem.

Mainly, I could not estimate the impact it would have on run-time performance of my code and GHC not being able to compile the code was not a good indication. Simon PJ fixed that error since.

My idea was to, basically, create my own record sans labels. I wanted to specify picklers and default values for each field instead. I have over 250 records, though, and some have over 10 fields. There is a lot of sharing of fields between the records but I still think this is too much for GHC to handle.

Can you venture a guess on runtime performance of such code?

    Thanks, Joel


On Nov 22, 2005, at 4:07 PM, Keean Schupke wrote:

    hMarkAll Just hlist

   class HList l => HMarkAll c l m | c l -> m where
      hMarkAll :: (forall a . a -> c a) -> l -> m
   instance HMarkAll c HNil HNil where
      hMarkAll _ _ = HNil
instance HMarkAll c l m => HMarkAll c (HCons e l) (HCons (c e) m) where
      hMarkAll c (HCons e l) = HCons (c e) (hMarkAll c l)


--
http://wagerlabs.com/






{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-overlapping-instances #-}
{-# OPTIONS -fallow-undecidable-instances #-}

module Lib.Relational.FamDb where

import Char
import Lib.ODBC.Types
import Lib.TIR.HList
import Lib.TIR.HTypeGHC
import Lib.TIR.HRecord
import Lib.Relational.Types as SQL

-------------------------------------------------------------------------------
-- Foot and Mouth Database

famdb :: (FarmerTable:*:FarmTable:*:AnimalTable:*:ContaminatedTable:*: HNil)
famdb = (farmerTable.*.farmTable.*.animalTable.*.contaminatedTable.*.HNil)

-------------------------------------------------------------------------------
-- Domains

newtype DFarmerId = DFarmerId Int deriving (Show,Eq,ToSqlType SqlInteger,FromSqlType SqlInteger)
newtype DFarmerName = DFarmerName String deriving (Show,Eq,ToSqlType SqlVarchar,FromSqlType SqlVarchar)
newtype DFarmId = DFarmId Int deriving (Show,Eq,ToSqlType SqlInteger,FromSqlType SqlInteger)
newtype DFarmName = DFarmName String deriving (Show,Eq,ToSqlType SqlVarchar,FromSqlType SqlVarchar)
newtype DFarmCounty = DFarmCounty String deriving (Show,Eq,ToSqlType SqlVarchar,FromSqlType SqlVarchar)
newtype DAnimalId = DAnimalId Int deriving (Show,Eq,ToSqlType SqlInteger,FromSqlType SqlInteger)
newtype DAnimalName = DAnimalName String deriving (Show,Eq,ToSqlType SqlVarchar,FromSqlType SqlVarchar)
data DAnimalType = Cow | Sheep deriving (Show,Eq)
newtype DAnimalPrice = DAnimalPrice Float deriving (Show,Eq,ToSqlType SqlNumeric,FromSqlType SqlNumeric)
data DCntdType = BSE | FM deriving (Show,Eq)

instance FromSqlType SqlVarchar DAnimalType where
   fromSqlType _ s = case (map toLower s) of
      "cow" -> Just Cow
      "sheep" -> Just Sheep
      _ -> Nothing
                                                                                                                     
instance ToSqlType SqlVarchar DAnimalType where
   toSqlType Cow = SqlTyped (SqlExpressionConst $ sqlShow "cow" "")
   toSqlType Sheep = SqlTyped (SqlExpressionConst $ sqlShow "sheep" "")

instance FromSqlType SqlVarchar DCntdType where
	fromSqlType _ s = case (map toLower s) of
		"bse" -> Just BSE
		"fm" -> Just FM
		_ -> Nothing

instance ToSqlType SqlVarchar DCntdType where
	toSqlType BSE = SqlTyped (SqlExpressionConst $ sqlShow "BSE" "")
	toSqlType FM = SqlTyped (SqlExpressionConst $ sqlShow "FM" "")

-------------------------------------------------------------------------------
-- Farmer table

data FarmerId = FarmerId deriving Show
data FarmerName = FarmerName deriving Show

type FarmerTable = Table (
	FarmerId :=: Attribute DFarmerId SqlInteger :*:
	FarmerName :=: Attribute DFarmerName SqlVarchar :*:
	HNil)	

farmerTable :: FarmerTable
farmerTable =  newTable "Farmer" (
	FarmerId .=. Attribute (attr { attrName="farmerid", attrType="SERIAL" }) .*.
	FarmerName .=. Attribute (attr { attrName="name", attrSize=20 }) .*.
	HNil)

-------------------------------------------------------------------------------
-- Farm table

data FarmId = FarmId deriving Show
data FarmName = FarmName deriving Show
data FarmCounty = FarmCounty deriving Show
data FarmOwner = FarmOwner deriving Show

type FarmTable = Table (
	FarmId :=: Attribute DFarmId SqlInteger :*:
	FarmName :=: Attribute DFarmName SqlVarchar :*:
	FarmCounty :=: Attribute DFarmCounty SqlVarchar :*:
	FarmOwner :=: Attribute DFarmerId SqlInteger :*:
	HNil)

farmTable :: FarmTable
farmTable = newTable "Farm" (
	FarmId .=. Attribute (attr { attrName="farmid", attrType="SERIAL" }) .*.
	FarmName .=. Attribute (attr { attrName="farmname", attrSize=20 }) .*.
	FarmCounty .=. Attribute (attr { attrName="county", attrSize=15 }) .*.
	FarmOwner .=. Attribute (attr { attrName="owner" }) .*.
	HNil)

------------------------------------------------------------------------------
-- Animal table

data AnimalId = AnimalId deriving Show
data AnimalName = AnimalName deriving Show
data AnimalType = AnimalType deriving Show
data AnimalPrice = AnimalPrice deriving Show
data AnimalLocation = AnimalLocation deriving Show

type AnimalTable = Table (
	AnimalId :=: Attribute DAnimalId SqlInteger :*:
	AnimalName :=: Attribute DAnimalName SqlVarchar :*:
	AnimalType :=:	Attribute DAnimalType SqlVarchar :*:
	AnimalPrice :=: Attribute DAnimalPrice SqlNumeric :*:
	AnimalLocation :=: Attribute DFarmId SqlInteger :*:
	HNil)

animalTable :: AnimalTable
animalTable = newTable "Animal" (
	AnimalId .=. Attribute (attr { attrName="animalid", attrType="SERIAL" }) .*.
	AnimalName .=. Attribute (attr { attrName="name", attrSize=15 }) .*.
	AnimalType .=. Attribute (attr { attrName="type", attrSize=10 }) .*.
	AnimalPrice .=. Attribute (attr { attrName="price", attrPrecision=8, attrScale=2 }) .*. -- NUMERIC(8,2)?
	AnimalLocation .=. Attribute (attr { attrName="location" }) .*. HNil)

------------------------------------------------------------------------------
-- Contaminated table

data CntdFarm = CntdFarm deriving Show
data CntdAnimal = CntdAnimal deriving Show
data CntdType = CntdType deriving Show

type ContaminatedTable = Table (
	CntdFarm :=: Attribute DFarmId SqlInteger :*:
	CntdAnimal :=: Attribute DAnimalId SqlInteger :*:
	CntdType :=: Attribute DCntdType SqlVarchar :*:
	HNil)

contaminatedTable :: ContaminatedTable
contaminatedTable = newTable "Contaminated" (
	CntdFarm .=. Attribute (attr { attrName="farm" }) .*.
	CntdAnimal .=. Attribute (attr { attrName="animal" }) .*.
	CntdType .=. Attribute (attr { attrName="type", attrSize=4 }) .*.
	HNil)

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

Reply via email to