Re: [Haskell-cafe] Can not use ST monad with polymorphic function

2012-12-03 Thread Dmitry Kulagin

 Basically, quantified types can't be given as arguments to type
 constructors (other than -, which is its own thing). I'm not entirely
 sure
 why, but it apparently makes the type system very complicated from a
 theoretical standpoint. By wrapping the quantified type in a newtype, the
 argument to IO becomes simple enough not to cause problems.


Thank you, I have read about predicative types and it seems I understand
the origin of the problem now.


  GHC has an extension -XImpredicativeTypes that lifts this restriction,
 but in my experience, it doesn't work very well.


Yes, it didn't help in my case.

Thank you,
Dmitry
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can not use ST monad with polymorphic function

2012-12-02 Thread Heinrich Apfelmus

David Menendez wrote:

On Thu, Nov 29, 2012 at 7:50 AM, Dmitry Kulagin dmitry.kula...@gmail.comwrote:


Thank you, MigMit!

If I replace your type FoldSTVoid with:
data FoldMVoid = FoldMVoid {runFold :: Monad m = (Int - m ()) - m ()}

then everything works magically with any monad!
That is exactly what I wanted, though I still do not quite understand why
wrapping the type solves the problem



Short answer: It's because GHC's type system is predicative.

Basically, quantified types can't be given as arguments to type
constructors (other than -, which is its own thing). I'm not entirely sure
why, but it apparently makes the type system very complicated from a
theoretical standpoint. By wrapping the quantified type in a newtype, the
argument to IO becomes simple enough not to cause problems.


GHC has an extension -XImpredicativeTypes that lifts this restriction, 
but in my experience, it doesn't work very well. A newtype


 data Foo = Foo { bar :: forall a . baz a }

usually works best.


Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can not use ST monad with polymorphic function

2012-12-01 Thread David Menendez
On Thu, Nov 29, 2012 at 7:50 AM, Dmitry Kulagin dmitry.kula...@gmail.comwrote:

 Thank you, MigMit!

 If I replace your type FoldSTVoid with:
 data FoldMVoid = FoldMVoid {runFold :: Monad m = (Int - m ()) - m ()}

 then everything works magically with any monad!
 That is exactly what I wanted, though I still do not quite understand why
 wrapping the type solves the problem


Short answer: It's because GHC's type system is predicative.

Basically, quantified types can't be given as arguments to type
constructors (other than -, which is its own thing). I'm not entirely sure
why, but it apparently makes the type system very complicated from a
theoretical standpoint. By wrapping the quantified type in a newtype, the
argument to IO becomes simple enough not to cause problems.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can not use ST monad with polymorphic function

2012-11-29 Thread Dmitry Kulagin
Thank you, MigMit!

If I replace your type FoldSTVoid with:
data FoldMVoid = FoldMVoid {runFold :: Monad m = (Int - m ()) - m ()}

then everything works magically with any monad!
That is exactly what I wanted, though I still do not quite understand why
wrapping the type solves the problem

Dmitry


On Thu, Nov 29, 2012 at 12:01 AM, MigMit miguelim...@yandex.ru wrote:

 Yes, monomorphism. do binding requires your fold'' to be of some
 monomorphic type, but runST requires some polymorphism.

 If you want, you can use special type like that:

 data FoldSTVoid = FoldSTVoid {runFold :: forall a. (Int - ST a ()) - ST
 a ()}

 fold :: Monad m = (Int - m ()) - m ()
 fold f = mapM_ f [0..20]

 selectFold :: String - IO FoldSTVoid -- ((Int - m ()) - m ())
 selectFold method = do
 -- in real program I'd like to choose between
 -- different fold methods, based on some IO context
 return $ FoldSTVoid fold

 useFold :: FoldSTVoid - ST a ()
 useFold fold' = runFold fold' f
 where f _ = return () -- some trivial iterator

 main = do
 fold'' - selectFold some-method-id
 print $ runST $ useFold fold''

 On Nov 28, 2012, at 9:52 PM, Dmitry Kulagin dmitry.kula...@gmail.com
 wrote:

  Hi Cafe,
 
  I try to implement some sort of monadic fold, where traversing is
 polymorphic over monad type.
  The problem is that the code below does not compile. It works with any
 monad except for ST.
  I suspect that monomorphism is at work here, but it is unclear for me
 how to change the code to make it work with ST.
 
  fold :: Monad m = (Int - m ()) - m ()
  fold f = mapM_ f [0..20]
 
  selectFold :: Monad m = String - IO ((Int - m ()) - m ())
  selectFold method = do
  -- in real program I'd like to choose between
  -- different fold methods, based on some IO context
  return fold
 
  useFold :: Monad m = ((Int - m ()) - m ()) - m ()
  useFold fold' = fold' f
  where f _ = return () -- some trivial iterator
 
  main = do
  fold'' - selectFold some-method-id
  print $ runST $ useFold fold''
 
 
  Thank you!
  Dmitry
  ___
  Haskell-Cafe mailing list
  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


[Haskell-cafe] Can not use ST monad with polymorphic function

2012-11-28 Thread Dmitry Kulagin
Hi Cafe,

I try to implement some sort of monadic fold, where traversing is
polymorphic over monad type.
The problem is that the code below does not compile. It works with any
monad except for ST.
I suspect that monomorphism is at work here, but it is unclear for me how
to change the code to make it work with ST.

fold :: Monad m = (Int - m ()) - m ()
fold f = mapM_ f [0..20]

selectFold :: Monad m = String - IO ((Int - m ()) - m ())
selectFold method = do
-- in real program I'd like to choose between
-- different fold methods, based on some IO context
return fold

useFold :: Monad m = ((Int - m ()) - m ()) - m ()
useFold fold' = fold' f
where f _ = return () -- some trivial iterator

main = do
fold'' - selectFold some-method-id
print $ runST $ useFold fold''


Thank you!
Dmitry
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can not use ST monad with polymorphic function

2012-11-28 Thread MigMit
Yes, monomorphism. do binding requires your fold'' to be of some monomorphic 
type, but runST requires some polymorphism.

If you want, you can use special type like that:

data FoldSTVoid = FoldSTVoid {runFold :: forall a. (Int - ST a ()) - ST a ()}

fold :: Monad m = (Int - m ()) - m ()
fold f = mapM_ f [0..20]

selectFold :: String - IO FoldSTVoid -- ((Int - m ()) - m ())
selectFold method = do
-- in real program I'd like to choose between 
-- different fold methods, based on some IO context
return $ FoldSTVoid fold

useFold :: FoldSTVoid - ST a ()
useFold fold' = runFold fold' f
where f _ = return () -- some trivial iterator

main = do
fold'' - selectFold some-method-id
print $ runST $ useFold fold''

On Nov 28, 2012, at 9:52 PM, Dmitry Kulagin dmitry.kula...@gmail.com wrote:

 Hi Cafe,
 
 I try to implement some sort of monadic fold, where traversing is polymorphic 
 over monad type.
 The problem is that the code below does not compile. It works with any monad 
 except for ST. 
 I suspect that monomorphism is at work here, but it is unclear for me how to 
 change the code to make it work with ST.
 
 fold :: Monad m = (Int - m ()) - m ()
 fold f = mapM_ f [0..20]
 
 selectFold :: Monad m = String - IO ((Int - m ()) - m ())
 selectFold method = do
 -- in real program I'd like to choose between 
 -- different fold methods, based on some IO context
 return fold
 
 useFold :: Monad m = ((Int - m ()) - m ()) - m ()
 useFold fold' = fold' f
 where f _ = return () -- some trivial iterator
 
 main = do
 fold'' - selectFold some-method-id
 print $ runST $ useFold fold''
 
 
 Thank you!
 Dmitry
 ___
 Haskell-Cafe mailing list
 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