Re: [Haskell-cafe] How to fold on types?

Magiclouds asked how to build values of data types with many components from a list of components. For example, suppose we have data D3 = D3 Int Int Int deriving Show v3 = [1::Int,2,3] How can we build the value D3 1 2 3 using the list v3 as the source for D3's fields? We can't use (foldl ($) D3 values) since the type changes throughout the iteration: D3 and D3 1 have different type. The enclosed code shows the solution. It defines the function fcurry such that t1 = fcurry D3 v3 -- D3 1 2 3 gives the expected result (D3 1 2 3). The code is the instance of the general folding over heterogeneous lists, search for HFoldr in http://code.haskell.org/HList/Data/HList/HList.hs {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts #-} {-# LANGUAGE TypeFamilies, DataKinds, PolyKinds, ScopedTypeVariables #-} {-# LANGUAGE UndecidableInstances #-} -- `Folding' over the data type: creating values of data types -- with many components from a list of components -- UndecidableInstances is a bit surprising since everything is decidable, -- but GHC can't see it. -- Extensions DataKinds, PolyKinds aren't strictly needed, but -- they make the code a bit nicer. If we already have them, -- why suffer avoiding them. module P where -- The example from MagicCloud's message data D3 = D3 Int Int Int deriving Show v3 = [1::Int,2,3] type family IsArrow a :: Bool type instance IsArrow (a->b) = True type instance IsArrow D3 = False -- add more instances as needed for other non-arrow types data Proxy a = Proxy class FarCurry a r t where fcurry :: (a->t) -> [a] -> r instance ((IsArrow t) ~ f, FarCurry' f a r t) => FarCurry a r t where fcurry = fcurry' (Proxy::Proxy f) class FarCurry' f a r t where fcurry' :: Proxy f -> (a->t) -> [a] -> r instance r ~ r' => FarCurry' False a r' r where fcurry' _ cons (x:_) = cons x instance FarCurry a r t => FarCurry' True a r (a->t) where fcurry' _ cons (x:t) = fcurry (cons x) t -- Example t1 = fcurry D3 v3 -- D3 1 2 3 -- Let's add another data type data D4 = D4 Int Int Int Int deriving Show type instance IsArrow D4 = False t2 = fcurry D4 [1::Int,2,3,4] -- D4 1 2 3 4
participants (1)
-
oleg@okmij.org