module Main where
import Control.Monad
import Control.Concurrent
class Processor p where
ready :: p b c → [b → c]
instance Processor (→) where
ready = repeat
--instance Processor [b → c] where
--ready = id
newtype FunList b c = FunList [b → c]
instance Processor FunList where
ready (FunList fl) = fl
broadcast :: Processor p ⇒ p b c → [b] → [c]
broadcast p bs = bcast ps bs []
where
ps = ready p
bcast [] _ cs = cs
bcast _ [] cs = cs
bcast ps bs cs =
let (cp,nps) = rotate [] ps
(cb,nbs) = rotate [] bs in
bcast nps nbs (cp cb:cs)
rotate :: [a] → [a] → (a,[a])
rotate os (x:[]) = (x,os)
rotate os (x:xs) = (x,xs)
main :: IO ()
main = do
let pid = id
let ppm = FunList [ (x +) | x ← [1..10] ]
print $ broadcast ppm [1..10]
------
Thank you for your answer!
This comes close to solving the problem but in the last line of the above I want to be able to say:
either
> print $ broadcast id [1..10]
or
> print $ broadcast [ (x +) | x ← [1..10] ] [1..10]
both need to be possible*.
So is there a way to make the FunList disappear completely?
Regards,
Cetin
P.S.: * broadcast is a dummy function, I need this for tidying up the interface of a little experiment: http://corsis.blogspot.com/
Cetin Sert schrieb:
> Hi,> ...
>
> class Processor a where
> ready :: (forall b c. a → [b → c])
>
> instance Processor (b → c) where
> ready = repeat
> -------------------------------Hi Cetin,
> Why can I not declare the above instances and always get:
in your class declaration you state that a (Processor T) provides a function
> ready :: T -> [b -> c]
so
> ready (t::T)
has type (forall b c. [b -> c]), a list of functions from arbitrary
types b to c.
The error messages tell you that e.g.
> repeat (f :: t1 -> t2)
has type
> (t1->t2) -> [t1->t2]
and not the required type
> (t1->t2) -> [a -> b]
With your declarations,
> head (ready negate) "hi"
has to typecheck, that's probably not what you want.
Maybe you meant
> Is there a way around this?
> class Processor a where
> ready :: a b c -> [b -> c]
> instance Processor (->) where
> ready = repeat
> newtype FunList b c = FunList [b->c]
> instance Processor FunList where
> ready (FunList fl) = fl
I think the newtype FunList is neccessary here.
benedikt
> ------------------------------------------------------------------------
>
> message.hs:229:10:
> Couldn't match expected type `b' against inferred type `b1'
> `b' is a rigid type variable bound by
> the instance declaration at message.hs:228:20
> `b1' is a rigid type variable bound by
> the type signature for `ready' at message.hs:226:19
> Expected type: b -> c
> Inferred type: b1 -> c1
> In the expression: repeat
> In the definition of `ready': ready = repeat
>
> message.hs:229:10:
> Couldn't match expected type `c' against inferred type `c1'
> `c' is a rigid type variable bound by
> the instance declaration at message.hs:228:24
> `c1' is a rigid type variable bound by
> the type signature for `ready' at message.hs:226:21
> Expected type: b -> c
> Inferred type: b1 -> c1
> In the expression: repeat
> In the definition of `ready': ready = repeat
>
> message.hs:232:10:
> Couldn't match expected type `b1' against inferred type `b'
> `b1' is a rigid type variable bound by
> the type signature for `ready' at message.hs:226:19
> `b' is a rigid type variable bound by
> the instance declaration at message.hs:231:20
> Expected type: [b1 -> c]
> Inferred type: [b -> c1]
> In the expression: id
> In the definition of `ready': ready = id
>
> message.hs:232:10:
> Couldn't match expected type `c1' against inferred type `c'
> `c1' is a rigid type variable bound by
> the type signature for `ready' at message.hs:226:21
> `c' is a rigid type variable bound by
> the instance declaration at message.hs:231:24
> Expected type: [b -> c1]
> Inferred type: [b1 -> c]
> In the expression: id
> In the definition of `ready': ready = id
>
> Is there a way around this?
>
> Regards,
> CS
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe