
Quoting Felipe Almeida Lessa
On Sun, Oct 2, 2011 at 4:26 PM, Edward Z. Yang
wrote: What are you actually trying to do? This seems like a rather unusual function.
If you're new to the language, most likely you're doing something wrong if you need this kind of function. =)
-- Felipe.
{-# LANGUAGE TypeFamilies,FlexibleInstances #-} module RicherListOp ( generalizedFilter,generalizedMap,generalizedFilterMap ) where import Data.List generalizedFilter pred = impl.expand3 where impl (dL,dR,step) = generalizedFilterMap tf (dL+dR+1,step) where tf s = if pred s then [s !! dL] else [] generalizedMap tf = generalizedFilterMap $ \x->[tf x] generalizedFilterMap tf ns ls = impl {-$ expand2-} ns where impl (len,step) = f ls where f xs | length xs >=len = (tf $ genericTake len xs) ++ (f $ genericDrop step xs) f _ = [] class Expand3 t where type Result3 t expand3 :: t->Result3 t instance (Integral a,Integral b)=>Expand3 (a,b) where type Result3 (a,b) = (a,b,Int) expand3 (l,r) = (l,r,1) instance (Integral a,Integral b,Integral c)=>Expand3 (a,b,c) where type Result3 (a,b,c) = (a,b,c) expand3 = id --instance (Integral a)=>Expand3 a where -- type Result3 a = (a,a,a) -- expand3 r = (0,r,1) --class Expand2 t where -- type Result2 t -- expand2 :: t->Result2 t --instance (Integral a)=>Expand2 (a,a) where -- type Result2 (a,a) = (a,a) -- expand2 = id --instance (Integral a)=>Expand2 a where -- type Result2 a = (a,a) -- expand2 a = (a,1) examples:
generalizedFilterMap (\[x,y,z]-> if(x==1&&z==1)then [y*10] else [0]) (3,1) [1,2,3,4,1,2,1,3,1,4,1,5,2] [0,0,0,0,20,0,30,0,40,0,0] it :: [Integer] generalizedFilter (\[x,y,z] -> x==1&&z==1) (1,1) [1,2,3,4,1,2,1,3,1,4,1,5,2] [2,3,4] it :: [Integer]
The code commented out is what I still can't get working. (I'm no longer trying to finish them. They are included just to illustrate my idea). Of course, I could have simply used [Int] , (Num a)=>[a] or (Int,Int,Int), but I'm trying to write code as generic as possible.