Re: [Haskell-cafe] What extension do I need to write "type Job = Map k a"?

(resending to café, turns out I wasn't subbed from this address.) Hi Magicloud, This is correct; because you've hidden the type-variables away by universally quantifying them, there's no more level of specificity you can get back *out* of them than just "some kind of Map" (Job = M.Map k b, where k ≠ k0, b ≠ b0). If you have a Job type which can store *any* kind of Map (forall k a. Job (Map k a)), then that means you could have a Job with a Map Int Bool, and a Job with a Map String (Float -> Float), and they'd both have the same type "Job". You can't do anything with the values within, because you're being too permissive about what a Job is. You may want "data Job k a = Job (Map k a)", *or* if you do actually use one kind of Map only, then why not "data Job = Job (Map Int String)" (substituting your real types for Int and String). In this case, you could also consider using newtype ("newtype Job = Job { getJob :: Map Int String }") to provide the guarantee that you're getting a Job (and not any Map Int String) without performance loss. Let me know if I've been more confusing than helpful; Arlen On Thursday, 14 June 2012 at 1:16 PM, Magicloud Magiclouds wrote:
Hi there, Thanks for the reply. To be clear, all I want is to "avoid having to type type variables all over the place". What should I do? My original code with RankNTypes and ImpredicativeTypes does not work....
The "type Job = forall k a. M.Map k a" works now. But function uses it does not. Compiler complains about "Couldn't match expected type `Job' with actual type `M.Map k0 b0'".
On Wed, Jun 13, 2012 at 9:15 PM, Daniel Peebles
wrote: That doesn't require existential quantification, but it'll need Rank-2 typesif you ever do anything with Job. Unfortunately, a universally quantifiedJob like what you wrote (or what Magicloud seems to want) is only inhabitedby the empty Map. An existentially quantified Job, as you might get with
data Job = forall k a. Job (Map k a)
does let you wrap up any Map containing anything in it, but unfortunatelythe only thing you can do with that map afterwards is ask for "structural"properties about it, like whether it's empty or how many elements it has init. You could ask to enumerate the elements in it, but you wouldn't be ableto touch any of them because you wouldn't know what their types were.
So I'm not really sure how to interpret the question. Was the goal to have aheterogeneous Map, maybe? Or just to avoid having to type type variables allover the place? Both of those are possible but require a bit moresophistication with types.
-Dan
On Wed, Jun 13, 2012 at 7:32 AM, Ismael Figueroa Palet
wrote: Do you want to hide the specific types of the job? Presumably to thendefine a type JobList = [Job] ?You can do that with the ExistentialQuantification extension.
type Job = forall k a. Map k atype JobList = [Job]
??Note you can't unpack the types k a once you have hidden them. But thetypechecker can use it to ensure some static property.Also you could use unsafeCoerce to do some casts, but *only if you are*sure* that things will go OK*.
2012/6/13 Magicloud Magiclouds
Hi,I've forgotten this.This is OK:type Job k a = Map k aAnd this is OK:{-# LANGUAGE RankNTypes #-} -- or LiberalTypeSynonyms?type Job = forall a. forall k. Map k a
Then how to write it like this?type Job = Map k a--竹密岂妨流水过山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
_______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org)
--Ismael
_______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org)
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) http://www.haskell.org/mailman/listinfo/haskell-cafe

OK. I think I understand a little.
I use Job here just wants to simplify the code. And since I provide
the function as library, I cannot decide what exact type k is. What
should I do?
On Thu, Jun 14, 2012 at 11:23 AM, Arlen Cuss
(resending to café, turns out I wasn't subbed from this address.)
Hi Magicloud, This is correct; because you've hidden the type-variables away by universally quantifying them, there's no more level of specificity you can get back *out* of them than just "some kind of Map" (Job = M.Map k b, where k ≠ k0, b ≠ b0).
If you have a Job type which can store *any* kind of Map (forall k a. Job (Map k a)), then that means you could have a Job with a Map Int Bool, and a Job with a Map String (Float -> Float), and they'd both have the same type "Job". You can't do anything with the values within, because you're being too permissive about what a Job is.
You may want "data Job k a = Job (Map k a)", *or* if you do actually use one kind of Map only, then why not "data Job = Job (Map Int String)" (substituting your real types for Int and String). In this case, you could also consider using newtype ("newtype Job = Job { getJob :: Map Int String }") to provide the guarantee that you're getting a Job (and not any Map Int String) without performance loss.
Let me know if I've been more confusing than helpful;
Arlen
On Thursday, 14 June 2012 at 1:16 PM, Magicloud Magiclouds wrote:
Hi there, Thanks for the reply. To be clear, all I want is to "avoid having to type type variables all over the place". What should I do? My original code with RankNTypes and ImpredicativeTypes does not work....
The "type Job = forall k a. M.Map k a" works now. But function uses it does not. Compiler complains about "Couldn't match expected type `Job' with actual type `M.Map k0 b0'".
On Wed, Jun 13, 2012 at 9:15 PM, Daniel Peebles
wrote: That doesn't require existential quantification, but it'll need Rank-2 typesif you ever do anything with Job. Unfortunately, a universally quantifiedJob like what you wrote (or what Magicloud seems to want) is only inhabitedby the empty Map. An existentially quantified Job, as you might get with
data Job = forall k a. Job (Map k a)
does let you wrap up any Map containing anything in it, but unfortunatelythe only thing you can do with that map afterwards is ask for "structural"properties about it, like whether it's empty or how many elements it has init. You could ask to enumerate the elements in it, but you wouldn't be ableto touch any of them because you wouldn't know what their types were.
So I'm not really sure how to interpret the question. Was the goal to have aheterogeneous Map, maybe? Or just to avoid having to type type variables allover the place? Both of those are possible but require a bit moresophistication with types.
-Dan
On Wed, Jun 13, 2012 at 7:32 AM, Ismael Figueroa Palet
wrote: Do you want to hide the specific types of the job? Presumably to thendefine a type JobList = [Job] ?You can do that with the ExistentialQuantification extension.
type Job = forall k a. Map k atype JobList = [Job]
??Note you can't unpack the types k a once you have hidden them. But thetypechecker can use it to ensure some static property.Also you could use unsafeCoerce to do some casts, but *only if you are*sure* that things will go OK*.
2012/6/13 Magicloud Magiclouds
Hi,I've forgotten this.This is OK:type Job k a = Map k aAnd this is OK:{-# LANGUAGE RankNTypes #-} -- or LiberalTypeSynonyms?type Job = forall a. forall k. Map k a
Then how to write it like this?type Job = Map k a--竹密岂妨流水过山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
_______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org)
--Ismael
_______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org)
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org (mailto: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
-- 竹密岂妨流水过 山高哪阻野云飞 And for G+, please use magiclouds#gmail.com.

On 14 June 2012 14:20, Magicloud Magiclouds
OK. I think I understand a little. I use Job here just wants to simplify the code. And since I provide the function as library, I cannot decide what exact type k is. What should I do?
Do you know what the type of `a'? If so: type Job k = Map k String Otherwise... do you even need a type alias?
On Thu, Jun 14, 2012 at 11:23 AM, Arlen Cuss
wrote: (resending to café, turns out I wasn't subbed from this address.)
Hi Magicloud, This is correct; because you've hidden the type-variables away by universally quantifying them, there's no more level of specificity you can get back *out* of them than just "some kind of Map" (Job = M.Map k b, where k ≠ k0, b ≠ b0).
If you have a Job type which can store *any* kind of Map (forall k a. Job (Map k a)), then that means you could have a Job with a Map Int Bool, and a Job with a Map String (Float -> Float), and they'd both have the same type "Job". You can't do anything with the values within, because you're being too permissive about what a Job is.
You may want "data Job k a = Job (Map k a)", *or* if you do actually use one kind of Map only, then why not "data Job = Job (Map Int String)" (substituting your real types for Int and String). In this case, you could also consider using newtype ("newtype Job = Job { getJob :: Map Int String }") to provide the guarantee that you're getting a Job (and not any Map Int String) without performance loss.
Let me know if I've been more confusing than helpful;
Arlen
On Thursday, 14 June 2012 at 1:16 PM, Magicloud Magiclouds wrote:
Hi there, Thanks for the reply. To be clear, all I want is to "avoid having to type type variables all over the place". What should I do? My original code with RankNTypes and ImpredicativeTypes does not work....
The "type Job = forall k a. M.Map k a" works now. But function uses it does not. Compiler complains about "Couldn't match expected type `Job' with actual type `M.Map k0 b0'".
On Wed, Jun 13, 2012 at 9:15 PM, Daniel Peebles
wrote: That doesn't require existential quantification, but it'll need Rank-2 typesif you ever do anything with Job. Unfortunately, a universally quantifiedJob like what you wrote (or what Magicloud seems to want) is only inhabitedby the empty Map. An existentially quantified Job, as you might get with
data Job = forall k a. Job (Map k a)
does let you wrap up any Map containing anything in it, but unfortunatelythe only thing you can do with that map afterwards is ask for "structural"properties about it, like whether it's empty or how many elements it has init. You could ask to enumerate the elements in it, but you wouldn't be ableto touch any of them because you wouldn't know what their types were.
So I'm not really sure how to interpret the question. Was the goal to have aheterogeneous Map, maybe? Or just to avoid having to type type variables allover the place? Both of those are possible but require a bit moresophistication with types.
-Dan
On Wed, Jun 13, 2012 at 7:32 AM, Ismael Figueroa Palet
wrote: Do you want to hide the specific types of the job? Presumably to thendefine a type JobList = [Job] ?You can do that with the ExistentialQuantification extension.
type Job = forall k a. Map k atype JobList = [Job]
??Note you can't unpack the types k a once you have hidden them. But thetypechecker can use it to ensure some static property.Also you could use unsafeCoerce to do some casts, but *only if you are*sure* that things will go OK*.
2012/6/13 Magicloud Magiclouds
Hi,I've forgotten this.This is OK:type Job k a = Map k aAnd this is OK:{-# LANGUAGE RankNTypes #-} -- or LiberalTypeSynonyms?type Job = forall a. forall k. Map k a
Then how to write it like this?type Job = Map k a--竹密岂妨流水过山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
_______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org)
--Ismael
_______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org)
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org (mailto: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
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

I think I need to think this through....
On Thu, Jun 14, 2012 at 12:28 PM, Ivan Lazar Miljenovic
On 14 June 2012 14:20, Magicloud Magiclouds
wrote: OK. I think I understand a little. I use Job here just wants to simplify the code. And since I provide the function as library, I cannot decide what exact type k is. What should I do?
Do you know what the type of `a'? If so:
type Job k = Map k String
Otherwise... do you even need a type alias?
On Thu, Jun 14, 2012 at 11:23 AM, Arlen Cuss
wrote: (resending to café, turns out I wasn't subbed from this address.)
Hi Magicloud, This is correct; because you've hidden the type-variables away by universally quantifying them, there's no more level of specificity you can get back *out* of them than just "some kind of Map" (Job = M.Map k b, where k ≠ k0, b ≠ b0).
If you have a Job type which can store *any* kind of Map (forall k a. Job (Map k a)), then that means you could have a Job with a Map Int Bool, and a Job with a Map String (Float -> Float), and they'd both have the same type "Job". You can't do anything with the values within, because you're being too permissive about what a Job is.
You may want "data Job k a = Job (Map k a)", *or* if you do actually use one kind of Map only, then why not "data Job = Job (Map Int String)" (substituting your real types for Int and String). In this case, you could also consider using newtype ("newtype Job = Job { getJob :: Map Int String }") to provide the guarantee that you're getting a Job (and not any Map Int String) without performance loss.
Let me know if I've been more confusing than helpful;
Arlen
On Thursday, 14 June 2012 at 1:16 PM, Magicloud Magiclouds wrote:
Hi there, Thanks for the reply. To be clear, all I want is to "avoid having to type type variables all over the place". What should I do? My original code with RankNTypes and ImpredicativeTypes does not work....
The "type Job = forall k a. M.Map k a" works now. But function uses it does not. Compiler complains about "Couldn't match expected type `Job' with actual type `M.Map k0 b0'".
On Wed, Jun 13, 2012 at 9:15 PM, Daniel Peebles
wrote: That doesn't require existential quantification, but it'll need Rank-2 typesif you ever do anything with Job. Unfortunately, a universally quantifiedJob like what you wrote (or what Magicloud seems to want) is only inhabitedby the empty Map. An existentially quantified Job, as you might get with
data Job = forall k a. Job (Map k a)
does let you wrap up any Map containing anything in it, but unfortunatelythe only thing you can do with that map afterwards is ask for "structural"properties about it, like whether it's empty or how many elements it has init. You could ask to enumerate the elements in it, but you wouldn't be ableto touch any of them because you wouldn't know what their types were.
So I'm not really sure how to interpret the question. Was the goal to have aheterogeneous Map, maybe? Or just to avoid having to type type variables allover the place? Both of those are possible but require a bit moresophistication with types.
-Dan
On Wed, Jun 13, 2012 at 7:32 AM, Ismael Figueroa Palet
wrote: Do you want to hide the specific types of the job? Presumably to thendefine a type JobList = [Job] ?You can do that with the ExistentialQuantification extension.
type Job = forall k a. Map k atype JobList = [Job]
??Note you can't unpack the types k a once you have hidden them. But thetypechecker can use it to ensure some static property.Also you could use unsafeCoerce to do some casts, but *only if you are*sure* that things will go OK*.
2012/6/13 Magicloud Magiclouds
> Hi,I've forgotten this.This is OK:type Job k a = Map k aAnd this is OK:{-# LANGUAGE RankNTypes #-} -- or LiberalTypeSynonyms?type Job = forall a. forall k. Map k a > Then how to write it like this?type Job = Map k a--竹密岂妨流水过山高哪阻野云飞 > And for G+, please use magiclouds#gmail.com (http://gmail.com). > _______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > http://www.haskell.org/mailman/listinfo/haskell-cafe
--Ismael
_______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org)
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org (mailto: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
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com
-- 竹密岂妨流水过 山高哪阻野云飞 And for G+, please use magiclouds#gmail.com.

OK. I am totally confused here. Why "Couldn't match expected type
`Jobs k e a' with actual type `M.Map k0 b0'"....
9|data JobInfo a e = (Exception e) =>
10| JobInfo { jobId :: ThreadId
11| , result :: MVar (Either e a) }
12|
13|type Jobs k e a = (Ord k, Exception e) =>
14| M.Map k (JobInfo e a)
15|
16|type JobArgs k a = (Ord k) =>
17| M.Map k a
21|
22|start :: (Ord k, Exception e) => JobArgs k a -> (a -> IO b) -> IO
(Jobs k e a)
23|start args worker = do
24| arg <- newEmptyMVar
25| Map.mapM (\a -> do
26| putMVar arg a
27| result <- newEmptyMVar
28| tId <- forkIO $ do
29| arg_ <- takeMVar arg
30| result_ <- try $ worker arg_
31| putMVar result result_
32| return $ JobInfo tId result
33| ) args
On Thu, Jun 14, 2012 at 1:24 PM, Magicloud Magiclouds
I think I need to think this through....
On Thu, Jun 14, 2012 at 12:28 PM, Ivan Lazar Miljenovic
wrote: On 14 June 2012 14:20, Magicloud Magiclouds
wrote: OK. I think I understand a little. I use Job here just wants to simplify the code. And since I provide the function as library, I cannot decide what exact type k is. What should I do?
Do you know what the type of `a'? If so:
type Job k = Map k String
Otherwise... do you even need a type alias?
On Thu, Jun 14, 2012 at 11:23 AM, Arlen Cuss
wrote: (resending to café, turns out I wasn't subbed from this address.)
Hi Magicloud, This is correct; because you've hidden the type-variables away by universally quantifying them, there's no more level of specificity you can get back *out* of them than just "some kind of Map" (Job = M.Map k b, where k ≠ k0, b ≠ b0).
If you have a Job type which can store *any* kind of Map (forall k a. Job (Map k a)), then that means you could have a Job with a Map Int Bool, and a Job with a Map String (Float -> Float), and they'd both have the same type "Job". You can't do anything with the values within, because you're being too permissive about what a Job is.
You may want "data Job k a = Job (Map k a)", *or* if you do actually use one kind of Map only, then why not "data Job = Job (Map Int String)" (substituting your real types for Int and String). In this case, you could also consider using newtype ("newtype Job = Job { getJob :: Map Int String }") to provide the guarantee that you're getting a Job (and not any Map Int String) without performance loss.
Let me know if I've been more confusing than helpful;
Arlen
On Thursday, 14 June 2012 at 1:16 PM, Magicloud Magiclouds wrote:
Hi there, Thanks for the reply. To be clear, all I want is to "avoid having to type type variables all over the place". What should I do? My original code with RankNTypes and ImpredicativeTypes does not work....
The "type Job = forall k a. M.Map k a" works now. But function uses it does not. Compiler complains about "Couldn't match expected type `Job' with actual type `M.Map k0 b0'".
On Wed, Jun 13, 2012 at 9:15 PM, Daniel Peebles
wrote: That doesn't require existential quantification, but it'll need Rank-2 typesif you ever do anything with Job. Unfortunately, a universally quantifiedJob like what you wrote (or what Magicloud seems to want) is only inhabitedby the empty Map. An existentially quantified Job, as you might get with
data Job = forall k a. Job (Map k a)
does let you wrap up any Map containing anything in it, but unfortunatelythe only thing you can do with that map afterwards is ask for "structural"properties about it, like whether it's empty or how many elements it has init. You could ask to enumerate the elements in it, but you wouldn't be ableto touch any of them because you wouldn't know what their types were.
So I'm not really sure how to interpret the question. Was the goal to have aheterogeneous Map, maybe? Or just to avoid having to type type variables allover the place? Both of those are possible but require a bit moresophistication with types.
-Dan
On Wed, Jun 13, 2012 at 7:32 AM, Ismael Figueroa Palet
wrote: > Do you want to hide the specific types of the job? Presumably to thendefine a type JobList = [Job] ?You can do that with the ExistentialQuantification extension. > type Job = forall k a. Map k atype JobList = [Job] > ??Note you can't unpack the types k a once you have hidden them. But thetypechecker can use it to ensure some static property.Also you could use unsafeCoerce to do some casts, but *only if you are*sure* that things will go OK*. > > 2012/6/13 Magicloud Magiclouds
> > Hi,I've forgotten this.This is OK:type Job k a = Map k aAnd this is OK:{-# LANGUAGE RankNTypes #-} -- or LiberalTypeSynonyms?type Job = forall a. forall k. Map k a > > Then how to write it like this?type Job = Map k a--竹密岂妨流水过山高哪阻野云飞 > > And for G+, please use magiclouds#gmail.com (http://gmail.com). > > _______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > --Ismael > > _______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > http://www.haskell.org/mailman/listinfo/haskell-cafe -- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org (mailto: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
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com.
-- 竹密岂妨流水过 山高哪阻野云飞 And for G+, please use magiclouds#gmail.com.

Sorry, the last 'a' of line 22 is 'b'.
On Thu, Jun 14, 2012 at 3:19 PM, Magicloud Magiclouds
OK. I am totally confused here. Why "Couldn't match expected type `Jobs k e a' with actual type `M.Map k0 b0'"....
9|data JobInfo a e = (Exception e) => 10| JobInfo { jobId :: ThreadId 11| , result :: MVar (Either e a) } 12| 13|type Jobs k e a = (Ord k, Exception e) => 14| M.Map k (JobInfo e a) 15| 16|type JobArgs k a = (Ord k) => 17| M.Map k a 21| 22|start :: (Ord k, Exception e) => JobArgs k a -> (a -> IO b) -> IO (Jobs k e a) 23|start args worker = do 24| arg <- newEmptyMVar 25| Map.mapM (\a -> do 26| putMVar arg a 27| result <- newEmptyMVar 28| tId <- forkIO $ do 29| arg_ <- takeMVar arg 30| result_ <- try $ worker arg_ 31| putMVar result result_ 32| return $ JobInfo tId result 33| ) args
On Thu, Jun 14, 2012 at 1:24 PM, Magicloud Magiclouds
wrote: I think I need to think this through....
On Thu, Jun 14, 2012 at 12:28 PM, Ivan Lazar Miljenovic
wrote: On 14 June 2012 14:20, Magicloud Magiclouds
wrote: OK. I think I understand a little. I use Job here just wants to simplify the code. And since I provide the function as library, I cannot decide what exact type k is. What should I do?
Do you know what the type of `a'? If so:
type Job k = Map k String
Otherwise... do you even need a type alias?
On Thu, Jun 14, 2012 at 11:23 AM, Arlen Cuss
wrote: (resending to café, turns out I wasn't subbed from this address.)
Hi Magicloud, This is correct; because you've hidden the type-variables away by universally quantifying them, there's no more level of specificity you can get back *out* of them than just "some kind of Map" (Job = M.Map k b, where k ≠ k0, b ≠ b0).
If you have a Job type which can store *any* kind of Map (forall k a. Job (Map k a)), then that means you could have a Job with a Map Int Bool, and a Job with a Map String (Float -> Float), and they'd both have the same type "Job". You can't do anything with the values within, because you're being too permissive about what a Job is.
You may want "data Job k a = Job (Map k a)", *or* if you do actually use one kind of Map only, then why not "data Job = Job (Map Int String)" (substituting your real types for Int and String). In this case, you could also consider using newtype ("newtype Job = Job { getJob :: Map Int String }") to provide the guarantee that you're getting a Job (and not any Map Int String) without performance loss.
Let me know if I've been more confusing than helpful;
Arlen
On Thursday, 14 June 2012 at 1:16 PM, Magicloud Magiclouds wrote:
Hi there, Thanks for the reply. To be clear, all I want is to "avoid having to type type variables all over the place". What should I do? My original code with RankNTypes and ImpredicativeTypes does not work....
The "type Job = forall k a. M.Map k a" works now. But function uses it does not. Compiler complains about "Couldn't match expected type `Job' with actual type `M.Map k0 b0'".
On Wed, Jun 13, 2012 at 9:15 PM, Daniel Peebles
wrote: That doesn't require existential quantification, but it'll need Rank-2 typesif you ever do anything with Job. Unfortunately, a universally quantifiedJob like what you wrote (or what Magicloud seems to want) is only inhabitedby the empty Map. > An existentially quantified Job, as you might get with > data Job = forall k a. Job (Map k a) > does let you wrap up any Map containing anything in it, but unfortunatelythe only thing you can do with that map afterwards is ask for "structural"properties about it, like whether it's empty or how many elements it has init. You could ask to enumerate the elements in it, but you wouldn't be ableto touch any of them because you wouldn't know what their types were. > So I'm not really sure how to interpret the question. Was the goal to have aheterogeneous Map, maybe? Or just to avoid having to type type variables allover the place? Both of those are possible but require a bit moresophistication with types. > -Dan > > On Wed, Jun 13, 2012 at 7:32 AM, Ismael Figueroa Palet wrote: > > Do you want to hide the specific types of the job? Presumably to thendefine a type JobList = [Job] ?You can do that with the ExistentialQuantification extension. > > type Job = forall k a. Map k atype JobList = [Job] > > ??Note you can't unpack the types k a once you have hidden them. But thetypechecker can use it to ensure some static property.Also you could use unsafeCoerce to do some casts, but *only if you are*sure* that things will go OK*. > > > > 2012/6/13 Magicloud Magiclouds > > > Hi,I've forgotten this.This is OK:type Job k a = Map k aAnd this is OK:{-# LANGUAGE RankNTypes #-} -- or LiberalTypeSynonyms?type Job = forall a. forall k. Map k a > > > Then how to write it like this?type Job = Map k a--竹密岂妨流水过山高哪阻野云飞 > > > And for G+, please use magiclouds#gmail.com (http://gmail.com). > > > _______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > > > > > > > > --Ismael > > > > _______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org (mailto: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
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com.
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com.
-- 竹密岂妨流水过 山高哪阻野云飞 And for G+, please use magiclouds#gmail.com.

And line 14, should be JobInfo a e.
I must be too sleepy....
On Thu, Jun 14, 2012 at 3:30 PM, Magicloud Magiclouds
Sorry, the last 'a' of line 22 is 'b'.
On Thu, Jun 14, 2012 at 3:19 PM, Magicloud Magiclouds
wrote: OK. I am totally confused here. Why "Couldn't match expected type `Jobs k e a' with actual type `M.Map k0 b0'"....
9|data JobInfo a e = (Exception e) => 10| JobInfo { jobId :: ThreadId 11| , result :: MVar (Either e a) } 12| 13|type Jobs k e a = (Ord k, Exception e) => 14| M.Map k (JobInfo e a) 15| 16|type JobArgs k a = (Ord k) => 17| M.Map k a 21| 22|start :: (Ord k, Exception e) => JobArgs k a -> (a -> IO b) -> IO (Jobs k e a) 23|start args worker = do 24| arg <- newEmptyMVar 25| Map.mapM (\a -> do 26| putMVar arg a 27| result <- newEmptyMVar 28| tId <- forkIO $ do 29| arg_ <- takeMVar arg 30| result_ <- try $ worker arg_ 31| putMVar result result_ 32| return $ JobInfo tId result 33| ) args
On Thu, Jun 14, 2012 at 1:24 PM, Magicloud Magiclouds
wrote: I think I need to think this through....
On Thu, Jun 14, 2012 at 12:28 PM, Ivan Lazar Miljenovic
wrote: On 14 June 2012 14:20, Magicloud Magiclouds
wrote: OK. I think I understand a little. I use Job here just wants to simplify the code. And since I provide the function as library, I cannot decide what exact type k is. What should I do?
Do you know what the type of `a'? If so:
type Job k = Map k String
Otherwise... do you even need a type alias?
On Thu, Jun 14, 2012 at 11:23 AM, Arlen Cuss
wrote: (resending to café, turns out I wasn't subbed from this address.)
Hi Magicloud, This is correct; because you've hidden the type-variables away by universally quantifying them, there's no more level of specificity you can get back *out* of them than just "some kind of Map" (Job = M.Map k b, where k ≠ k0, b ≠ b0).
If you have a Job type which can store *any* kind of Map (forall k a. Job (Map k a)), then that means you could have a Job with a Map Int Bool, and a Job with a Map String (Float -> Float), and they'd both have the same type "Job". You can't do anything with the values within, because you're being too permissive about what a Job is.
You may want "data Job k a = Job (Map k a)", *or* if you do actually use one kind of Map only, then why not "data Job = Job (Map Int String)" (substituting your real types for Int and String). In this case, you could also consider using newtype ("newtype Job = Job { getJob :: Map Int String }") to provide the guarantee that you're getting a Job (and not any Map Int String) without performance loss.
Let me know if I've been more confusing than helpful;
Arlen
On Thursday, 14 June 2012 at 1:16 PM, Magicloud Magiclouds wrote:
> Hi there, > Thanks for the reply. To be clear, all I want is to "avoid having to > type type variables all over the place". What should I do? My original > code with RankNTypes and ImpredicativeTypes does not work.... > > The "type Job = forall k a. M.Map k a" works now. But function uses > it does not. Compiler complains about "Couldn't match expected type > `Job' with actual type `M.Map k0 b0'". > > On Wed, Jun 13, 2012 at 9:15 PM, Daniel Peebles
wrote: > That doesn't require existential quantification, but it'll need Rank-2 typesif you ever do anything with Job. Unfortunately, a universally quantifiedJob like what you wrote (or what Magicloud seems to want) is only inhabitedby the empty Map. > > > An existentially quantified Job, as you might get with > > > data Job = forall k a. Job (Map k a) > > > does let you wrap up any Map containing anything in it, but unfortunatelythe only thing you can do with that map afterwards is ask for "structural"properties about it, like whether it's empty or how many elements it has init. You could ask to enumerate the elements in it, but you wouldn't be ableto touch any of them because you wouldn't know what their types were. > > > So I'm not really sure how to interpret the question. Was the goal to have aheterogeneous Map, maybe? Or just to avoid having to type type variables allover the place? Both of those are possible but require a bit moresophistication with types. > > > -Dan > > > > > On Wed, Jun 13, 2012 at 7:32 AM, Ismael Figueroa Palet wrote: > > > > Do you want to hide the specific types of the job? Presumably to thendefine a type JobList = [Job] ?You can do that with the ExistentialQuantification extension. > > > > type Job = forall k a. Map k atype JobList = [Job] > > > > ??Note you can't unpack the types k a once you have hidden them. But thetypechecker can use it to ensure some static property.Also you could use unsafeCoerce to do some casts, but *only if you are*sure* that things will go OK*. > > > > > > > 2012/6/13 Magicloud Magiclouds > > > > > Hi,I've forgotten this.This is OK:type Job k a = Map k aAnd this is OK:{-# LANGUAGE RankNTypes #-} -- or LiberalTypeSynonyms?type Job = forall a. forall k. Map k a > > > > > Then how to write it like this?type Job = Map k a--竹密岂妨流水过山高哪阻野云飞 > > > > > And for G+, please use magiclouds#gmail.com (http://gmail.com). > > > > > _______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > > > > > > > > > > > > > > > > > --Ismael > > > > > > > _______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > > -- > 竹密岂妨流水过 > 山高哪阻野云飞 > > And for G+, please use magiclouds#gmail.com (http://gmail.com). > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org (mailto: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
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com.
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com.
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com.
-- 竹密岂妨流水过 山高哪阻野云飞 And for G+, please use magiclouds#gmail.com.

Hi Magicloud, The indentation has been lost in the mail. Could you post your code (preferably without line numbers) on hpaste.org or similar? —A On Thursday, 14 June 2012 at 5:33 PM, Magicloud Magiclouds wrote:
And line 14, should be JobInfo a e. I must be too sleepy....
On Thu, Jun 14, 2012 at 3:30 PM, Magicloud Magiclouds
wrote: Sorry, the last 'a' of line 22 is 'b'.
On Thu, Jun 14, 2012 at 3:19 PM, Magicloud Magiclouds
wrote: OK. I am totally confused here. Why "Couldn't match expected type `Jobs k e a' with actual type `M.Map k0 b0'"....
9|data JobInfo a e = (Exception e) => 10| JobInfo { jobId :: ThreadId 11| , result :: MVar (Either e a) } 12| 13|type Jobs k e a = (Ord k, Exception e) => 14| M.Map k (JobInfo e a) 15| 16|type JobArgs k a = (Ord k) => 17| M.Map k a 21| 22|start :: (Ord k, Exception e) => JobArgs k a -> (a -> IO b) -> IO (Jobs k e a) 23|start args worker = do 24| arg <- newEmptyMVar 25| Map.mapM (\a -> do 26| putMVar arg a 27| result <- newEmptyMVar 28| tId <- forkIO $ do 29| arg_ <- takeMVar arg 30| result_ <- try $ worker arg_ 31| putMVar result result_ 32| return $ JobInfo tId result 33| ) args
On Thu, Jun 14, 2012 at 1:24 PM, Magicloud Magiclouds
wrote: I think I need to think this through....
On Thu, Jun 14, 2012 at 12:28 PM, Ivan Lazar Miljenovic
wrote: On 14 June 2012 14:20, Magicloud Magiclouds
wrote: OK. I think I understand a little. I use Job here just wants to simplify the code. And since I provide the function as library, I cannot decide what exact type k is. What should I do?
Do you know what the type of `a'? If so:
type Job k = Map k String
Otherwise... do you even need a type alias?
On Thu, Jun 14, 2012 at 11:23 AM, Arlen Cuss
wrote: > (resending to café, turns out I wasn't subbed from this address.) > > Hi Magicloud, > This is correct; because you've hidden the type-variables away by universally quantifying them, there's no more level of specificity you can get back *out* of them than just "some kind of Map" (Job = M.Map k b, where k ≠ k0, b ≠ b0). > > If you have a Job type which can store *any* kind of Map (forall k a. Job (Map k a)), then that means you could have a Job with a Map Int Bool, and a Job with a Map String (Float -> Float), and they'd both have the same type "Job". You can't do anything with the values within, because you're being too permissive about what a Job is. > > You may want "data Job k a = Job (Map k a)", *or* if you do actually use one kind of Map only, then why not "data Job = Job (Map Int String)" (substituting your real types for Int and String). In this case, you could also consider using newtype ("newtype Job = Job { getJob :: Map Int String }") to provide the guarantee that you're getting a Job (and not any Map Int String) without performance loss. > > Let me know if I've been more confusing than helpful; > > Arlen > > > On Thursday, 14 June 2012 at 1:16 PM, Magicloud Magiclouds wrote: > > > Hi there, > > Thanks for the reply. To be clear, all I want is to "avoid having to > > type type variables all over the place". What should I do? My original > > code with RankNTypes and ImpredicativeTypes does not work.... > > > > The "type Job = forall k a. M.Map k a" works now. But function uses > > it does not. Compiler complains about "Couldn't match expected type > > `Job' with actual type `M.Map k0 b0'". > > > > On Wed, Jun 13, 2012 at 9:15 PM, Daniel Peebles wrote: > > That doesn't require existential quantification, but it'll need Rank-2 typesif you ever do anything with Job. Unfortunately, a universally quantifiedJob like what you wrote (or what Magicloud seems to want) is only inhabitedby the empty Map. > > > > > > An existentially quantified Job, as you might get with > > > > > > data Job = forall k a. Job (Map k a) > > > > > > does let you wrap up any Map containing anything in it, but unfortunatelythe only thing you can do with that map afterwards is ask for "structural"properties about it, like whether it's empty or how many elements it has init. You could ask to enumerate the elements in it, but you wouldn't be ableto touch any of them because you wouldn't know what their types were. > > > > > > So I'm not really sure how to interpret the question. Was the goal to have aheterogeneous Map, maybe? Or just to avoid having to type type variables allover the place? Both of those are possible but require a bit moresophistication with types. > > > > > > -Dan > > > > > > On Wed, Jun 13, 2012 at 7:32 AM, Ismael Figueroa Palet wrote: > > > > > > > > > Do you want to hide the specific types of the job? Presumably to thendefine a type JobList = [Job] ?You can do that with the ExistentialQuantification extension. > > > > > > > > > type Job = forall k a. Map k atype JobList = [Job] > > > > > > > > > ??Note you can't unpack the types k a once you have hidden them. But thetypechecker can use it to ensure some static property.Also you could use unsafeCoerce to do some casts, but *only if you are*sure* that things will go OK*. > > > > > > > > > 2012/6/13 Magicloud Magiclouds > > > > > > > > > > > > > Hi,I've forgotten this.This is OK:type Job k a = Map k aAnd this is OK:{-# LANGUAGE RankNTypes #-} -- or LiberalTypeSynonyms?type Job = forall a. forall k. Map k a > > > > > > > > > > > > > Then how to write it like this?type Job = Map k a--竹密岂妨流水过山高哪阻野云飞 > > > > > > > > > > > > > And for G+, please use magiclouds#gmail.com (http://gmail.com). > > > > > > > > > > > > > _______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > > > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > > > > > --Ismael > > > > > > > > > _______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > > > > > > > > > > > > > > > -- > > 竹密岂妨流水过 > > 山高哪阻野云飞 > > > > And for G+, please use magiclouds#gmail.com (http://gmail.com). > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > http://www.haskell.org/mailman/listinfo/haskell-cafe -- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com (mailto:Ivan.Miljenovic@gmail.com) http://IvanMiljenovic.wordpress.com
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).

Sorry, the full code is here:
http://hpaste.org/69972
On Fri, Jun 15, 2012 at 7:09 AM, Arlen Cuss
Hi Magicloud,
The indentation has been lost in the mail. Could you post your code (preferably without line numbers) on hpaste.org or similar?
—A
On Thursday, 14 June 2012 at 5:33 PM, Magicloud Magiclouds wrote:
And line 14, should be JobInfo a e. I must be too sleepy....
On Thu, Jun 14, 2012 at 3:30 PM, Magicloud Magiclouds
wrote: Sorry, the last 'a' of line 22 is 'b'.
On Thu, Jun 14, 2012 at 3:19 PM, Magicloud Magiclouds
wrote: OK. I am totally confused here. Why "Couldn't match expected type `Jobs k e a' with actual type `M.Map k0 b0'"....
9|data JobInfo a e = (Exception e) => 10| JobInfo { jobId :: ThreadId 11| , result :: MVar (Either e a) } 12| 13|type Jobs k e a = (Ord k, Exception e) => 14| M.Map k (JobInfo e a) 15| 16|type JobArgs k a = (Ord k) => 17| M.Map k a 21| 22|start :: (Ord k, Exception e) => JobArgs k a -> (a -> IO b) -> IO (Jobs k e a) 23|start args worker = do 24| arg <- newEmptyMVar 25| Map.mapM (\a -> do 26| putMVar arg a 27| result <- newEmptyMVar 28| tId <- forkIO $ do 29| arg_ <- takeMVar arg 30| result_ <- try $ worker arg_ 31| putMVar result result_ 32| return $ JobInfo tId result 33| ) args
On Thu, Jun 14, 2012 at 1:24 PM, Magicloud Magiclouds
wrote: I think I need to think this through....
On Thu, Jun 14, 2012 at 12:28 PM, Ivan Lazar Miljenovic
wrote: On 14 June 2012 14:20, Magicloud Magiclouds
wrote: > OK. I think I understand a little. > I use Job here just wants to simplify the code. And since I provide > the function as library, I cannot decide what exact type k is. What > should I do? Do you know what the type of `a'? If so:
type Job k = Map k String
Otherwise... do you even need a type alias?
> > On Thu, Jun 14, 2012 at 11:23 AM, Arlen Cuss
wrote: > > (resending to café, turns out I wasn't subbed from this address.) > > > > Hi Magicloud, > > This is correct; because you've hidden the type-variables away by universally quantifying them, there's no more level of specificity you can get back *out* of them than just "some kind of Map" (Job = M.Map k b, where k ≠ k0, b ≠ b0). > > > > If you have a Job type which can store *any* kind of Map (forall k a. Job (Map k a)), then that means you could have a Job with a Map Int Bool, and a Job with a Map String (Float -> Float), and they'd both have the same type "Job". You can't do anything with the values within, because you're being too permissive about what a Job is. > > > > You may want "data Job k a = Job (Map k a)", *or* if you do actually use one kind of Map only, then why not "data Job = Job (Map Int String)" (substituting your real types for Int and String). In this case, you could also consider using newtype ("newtype Job = Job { getJob :: Map Int String }") to provide the guarantee that you're getting a Job (and not any Map Int String) without performance loss. > > > > Let me know if I've been more confusing than helpful; > > > > Arlen > > > > > > On Thursday, 14 June 2012 at 1:16 PM, Magicloud Magiclouds wrote: > > > > > Hi there, > > > Thanks for the reply. To be clear, all I want is to "avoid having to > > > type type variables all over the place". What should I do? My original > > > code with RankNTypes and ImpredicativeTypes does not work.... > > > > > > The "type Job = forall k a. M.Map k a" works now. But function uses > > > it does not. Compiler complains about "Couldn't match expected type > > > `Job' with actual type `M.Map k0 b0'". > > > > > > On Wed, Jun 13, 2012 at 9:15 PM, Daniel Peebles wrote: > > > That doesn't require existential quantification, but it'll need Rank-2 typesif you ever do anything with Job. Unfortunately, a universally quantifiedJob like what you wrote (or what Magicloud seems to want) is only inhabitedby the empty Map. > > > > > > > > > An existentially quantified Job, as you might get with > > > > > > > > > data Job = forall k a. Job (Map k a) > > > > > > > > > does let you wrap up any Map containing anything in it, but unfortunatelythe only thing you can do with that map afterwards is ask for "structural"properties about it, like whether it's empty or how many elements it has init. You could ask to enumerate the elements in it, but you wouldn't be ableto touch any of them because you wouldn't know what their types were. > > > > > > > > > So I'm not really sure how to interpret the question. Was the goal to have aheterogeneous Map, maybe? Or just to avoid having to type type variables allover the place? Both of those are possible but require a bit moresophistication with types. > > > > > > > > > -Dan > > > > > > > > > On Wed, Jun 13, 2012 at 7:32 AM, Ismael Figueroa Palet wrote: > > > > > > > > > > > > > Do you want to hide the specific types of the job? Presumably to thendefine a type JobList = [Job] ?You can do that with the ExistentialQuantification extension. > > > > > > > > > > > > > type Job = forall k a. Map k atype JobList = [Job] > > > > > > > > > > > > > ??Note you can't unpack the types k a once you have hidden them. But thetypechecker can use it to ensure some static property.Also you could use unsafeCoerce to do some casts, but *only if you are*sure* that things will go OK*. > > > > > > > > > > > > > 2012/6/13 Magicloud Magiclouds > > > > > > > > > > > > > > > > > > Hi,I've forgotten this.This is OK:type Job k a = Map k aAnd this is OK:{-# LANGUAGE RankNTypes #-} -- or LiberalTypeSynonyms?type Job = forall a. forall k. Map k a > > > > > > > > > > > > > > > > > > Then how to write it like this?type Job = Map k a--竹密岂妨流水过山高哪阻野云飞 > > > > > > > > > > > > > > > > > > And for G+, please use magiclouds#gmail.com (http://gmail.com). > > > > > > > > > > > > > > > > > > _______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > > > > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > > > > > > > > > > --Ismael > > > > > > > > > > > > > _______________________________________________Haskell-Cafe mailing listHaskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > > > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > > > > > > > > > > > > > > > > > > > > > > > > > > -- > > > 竹密岂妨流水过 > > > 山高哪阻野云飞 > > > > > > And for G+, please use magiclouds#gmail.com (http://gmail.com). > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > Haskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > -- > 竹密岂妨流水过 > 山高哪阻野云飞 > > And for G+, please use magiclouds#gmail.com (http://gmail.com). > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org (mailto:Haskell-Cafe@haskell.org) > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com (mailto:Ivan.Miljenovic@gmail.com) http://IvanMiljenovic.wordpress.com
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
-- 竹密岂妨流水过 山高哪阻野云飞
And for G+, please use magiclouds#gmail.com (http://gmail.com).
-- 竹密岂妨流水过 山高哪阻野云飞 And for G+, please use magiclouds#gmail.com.
participants (3)
-
Arlen Cuss
-
Ivan Lazar Miljenovic
-
Magicloud Magiclouds