module Barrie.Packing where import Data.Dynamic import Data.Typeable class (Typeable a) => Packed a where unpack :: [a -> Dynamic] unpack = [toDyn] instance Packed Int where instance Packed Char where instance (Packed a) => Packed [a] where instance (Packed a, Packed b) => Packed (a,b) where unpack = [toDyn . fst, toDyn . snd] instance (Packed a, Packed b, Packed c) => Packed (a,b,c) where unpack = [toDyn . get31, toDyn . get32, toDyn . get33] where get31 (x,_,_) = x get32 (_,x,_) = x get33 (_,_,x) = x instance (Packed a, Packed b, Packed c, Packed d) => Packed (a,b,c,d) where unpack = [toDyn . get41, toDyn . get42, toDyn . get43, toDyn.get44] where get41 (x,_,_,_) = x get42 (_,x,_,_) = x get43 (_,_,x,_) = x get44 (_,_,_,x) = x instance (Packed a, Packed b, Packed c, Packed d, Packed e) => Packed (a,b,c,d,e) where unpack = [toDyn . get51, toDyn . get52, toDyn . get53, toDyn.get54, toDyn.get55] where get51 (x,_,_,_,_) = x get52 (_,x,_,_,_) = x get53 (_,_,x,_,_) = x get54 (_,_,_,x,_) = x get55 (_,_,_,_,x) = x