Re: [Haskell-cafe] Re: Pickling HList

2005-11-22 Thread Keean Schupke
This function is already in the HList library (well early versions 
anyway)... I dont think
this is in the current distribution. Its  a generic constructor  
wrapper. For example:


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)

   Keean.

Joel Reymont wrote:


Credit goes to Cale:

class (HList l, HList p) = HLPU p l | p - l, l - p where
puHList :: p - PU l

instance HLPU HNil HNil where
puHList HNil = lift HNil

instance (HList l, HLPU p l) = HLPU (HCons (PU e) p) (HCons e l) where
puHList (HCons pe l) =
wrap (\(a, b) - HCons a b,
  \(HCons a b) - (a, b))
  (pair pe (puHList l))


On Nov 10, 2005, at 2:04 PM, Joel Reymont wrote:


Folks,

I'm having trouble creating a pickler for HLists and would  
appreciate a solution.


The code for (HCons e HNil) works fine but I get an error trying to  
implement puHList for (HCons e l) where l is supposed to be (HCons  e 
...), i.e. another HList.


Bar.hs:21:37:
Couldn't match the rigid variable e' against PU e'
`e' is bound by the instance declaration at Bar.hs:17:0

Expected type: HCons (PU e) l Inferred type: HCons e l
In the first argument of puHList', namely l'

In the second argument of pair', namely (puHList l)'

Failed, modules loaded: none.



--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
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


Re: [Haskell-cafe] Re: Pickling HList

2005-11-22 Thread Joel Reymont

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/





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


Re: [Haskell-cafe] Re: Pickling HList

2005-11-22 Thread Keean Schupke
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 

[Haskell-cafe] Re: Pickling HList

2005-11-10 Thread Joel Reymont

Credit goes to Cale:

class (HList l, HList p) = HLPU p l | p - l, l - p where
puHList :: p - PU l

instance HLPU HNil HNil where
puHList HNil = lift HNil

instance (HList l, HLPU p l) = HLPU (HCons (PU e) p) (HCons e l) where
puHList (HCons pe l) =
wrap (\(a, b) - HCons a b,
  \(HCons a b) - (a, b))
  (pair pe (puHList l))


On Nov 10, 2005, at 2:04 PM, Joel Reymont wrote:


Folks,

I'm having trouble creating a pickler for HLists and would  
appreciate a solution.


The code for (HCons e HNil) works fine but I get an error trying to  
implement puHList for (HCons e l) where l is supposed to be (HCons  
e ...), i.e. another HList.


Bar.hs:21:37:
Couldn't match the rigid variable e' against PU e'
`e' is bound by the instance declaration at Bar.hs:17:0

Expected type: HCons (PU e) l Inferred type: HCons e l
In the first argument of puHList', namely l'

In the second argument of pair', namely (puHList l)'

Failed, modules loaded: none.



--
http://wagerlabs.com/





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