Difference between revisions of "Partibles for composing monads"

From HaskellWiki
Jump to navigation Jump to search
m (Minor formatting change)
m
 
(9 intermediate revisions by the same user not shown)
Line 1: Line 1:
  +
<div style="border-left:1px solid lightgray; padding: 1em" alt="blockquote">
<i>
 
 
Having praised monads to the hilt, let me level one criticism. Monads tend to be an all-or-nothing proposition. If you discover that you need interaction deep within your program, you must rewrite that segment to use a monad. If you discover that you need two sorts of interaction, you tend to make a single monad support both sorts. It seems to me that instead we should be able to move smoothly from no monads (no interactions) to one monad (a single form of interaction) to many monads (several independent forms of interactions). How to achieve this remains a challenge for the future.
 
Having praised monads to the hilt, let me level one criticism. Monads tend to be an all-or-nothing proposition. If you discover that you need interaction deep within your program, you must rewrite that segment to use a monad. If you discover that you need two sorts of interaction, you tend to make a single monad support both sorts. It seems to me that instead we should be able to move smoothly from no monads (no interactions) to one monad (a single form of interaction) to many monads (several independent forms of interactions). How to achieve this remains a challenge for the future.
  +
</i>
 
* <tt>[https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.91.3579&rep=rep1&type=pdf How to Declare an Imperative], Philip Wadler.</tt>
+
<small>[https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.91.3579&rep=rep1&type=pdf How to Declare an Imperative], Philip Wadler.</small>
 
</div>
   
 
<sub> </sub>
 
<sub> </sub>
Assuming the partible types being used are appropriately defined, then:
+
Assuming the [[Partible|partible]] types being used are appropriately defined, then:
   
 
<haskell>
 
<haskell>
instance Partible a => Monad ((->) a) where
+
type M p a = p -> a
return x = \ u -> case part u of !_ -> x
 
   
m >>= k = \ u -> case part u of
+
unit :: Partible p => a -> M p a
(u1, u2) -> case m u1 of !x -> k x u2
+
unit x = \ u -> let !_ = part u in x
   
m >> w = \ u -> case part u of
+
bind :: Partible p => M p a -> (a -> M p b) -> M p b
(u1, u2) -> case m u1 of !_ -> w u2
+
m `bind` k = \ u -> let !(u1, u2) = part u in
  +
let !x = m u1 in
  +
let !y = k x u2 in
  +
y
   
fail s = \ u -> case part u of !_ -> error s
+
next :: Partible p => M p a -> M p b -> M p b
  +
m `next` w = \ u -> let !(u1, u2) = part u in
  +
let !x = m u1 in
  +
let !y = w u2 in
  +
y
  +
  +
fail :: Partible p => String -> M p a
 
fail s = \ u -> let !_ = part u in error s
 
</haskell>
 
</haskell>
   
Line 23: Line 33:
   
 
<haskell>
 
<haskell>
instance (Partible a, Monad ((->) a)) => MonadFix ((->) a) where
+
mfix :: Partible p => (a -> M p a) -> M p a
mfix m = \ u -> yet (\ x -> m x u)
+
mfix m = \ u -> yet (\ x -> m x u)
   
instance (Partible a, Monad ((->) a), Partible b, Monad ((->) b)) => MonadCommute ((->) a) ((->) b) where
+
mcommute :: (Partible p1, Partible p2) => M p1 (M p2 a) -> M p2 (M p1 a)
mcommute g = \ v u -> g u v
+
mcommute g = \ v u -> g u v
   
instance (Monad m, Partible b, Monad ((->) b)) => MonadCommute m ((->) b) where
+
mcommute' :: (Monad m, Partible p) => m (M p a) -> M p (m a)
mcommute m = \ v -> liftM ($ v) m
+
mcommute' m = \ v -> liftM ($ v) m
 
</haskell>
 
</haskell>
   
Line 39: Line 49:
 
yet :: (a -> a) -> a
 
yet :: (a -> a) -> a
 
yet f = f (yet f)
 
yet f = f (yet f)
 
class Monad m => MonadFix m where
 
mfix :: (a -> m a) -> m a
 
 
class (Monad m1, Monad m2) => MonadCommute m1 m2 where
 
mcommute :: m1 (m2 a) -> m2 (m1 a)
 
 
</haskell>
 
</haskell>
 
|}
 
|}
Line 50: Line 54:
 
Using partible types to define monadic ones can enable an intermediate approach to the use of effects, in contrast to the ''all-or-nothing proposition'' of only using the monadic interface. In addition, if the definitions for such monadic types are ''visible'' (e.g. as type synonyms), this may also allow the manipulation of control in ways beyond what the monadic interface provides.
 
Using partible types to define monadic ones can enable an intermediate approach to the use of effects, in contrast to the ''all-or-nothing proposition'' of only using the monadic interface. In addition, if the definitions for such monadic types are ''visible'' (e.g. as type synonyms), this may also allow the manipulation of control in ways beyond what the monadic interface provides.
   
  +
=== Composing arrows ===
  +
  +
Partible types can also be used to define [[Arrow|arrow]] types:
  +
  +
<haskell>
 
type A p b c = (p -> b) -> (p -> c)
  +
  +
arr :: Partible p => (b -> c) -> A p b c
  +
arr f = \ c' u -> f $! c' u
  +
  +
  +
both :: Partible p => A p b c -> A p b' c' -> A p (b, b') (c, c')
  +
f' `both` g' = \ c' u -> let !(u1:u2:u3:_) = parts u in
  +
let !(x, x') = c' u1 in
  +
let !y = f' (unit x) u2 in
  +
let !y' = g' (unit x') u3 in
  +
(y, y')
  +
where
  +
unit x u = let !_ = part u in x
  +
</haskell>
  +
  +
(...though most will probably opt for the convenience of the associated [https://hackage.haskell.org/package/base-4.15.0.0/docs/src/Control-Arrow.html#Kleisli <code>Kleisli</code>] type).
  +
  +
=== Composing comonads ===
  +
  +
[[Comonad|Comonadic]] types can be defined using partible types as well:
  +
  +
<haskell>
  +
type C p a = (a, p)
  +
  +
extract :: Partible p => C p a -> a
  +
extract (x, u) = let !_ = part u in x
  +
  +
duplicate :: Partible p => C p a -> C p (C p a)
  +
duplicate (x, u) = let !(u1, u2) = part u in
  +
((x, u1), u2)
  +
  +
extend :: Partible p => (C p a -> b) -> C p a -> C p b
  +
extend h (x, u) = let !(u1, u2) = part u in
  +
let !y = h (x, u1) in
  +
(y, u2)
  +
</haskell>
 
----
 
----
 
See also:
 
See also:
Line 59: Line 105:
 
* [[Prelude extensions]]
 
* [[Prelude extensions]]
 
* [https://downloads.haskell.org/~ghc/7.8.4/docs/html/users_guide/bang-patterns.html Bang patterns]
 
* [https://downloads.haskell.org/~ghc/7.8.4/docs/html/users_guide/bang-patterns.html Bang patterns]
  +
* [https://gitlab.haskell.org/ghc/ghc/-/issues/19809 GHC ticket 19809: Overhaul ST using ''pseudodatata'']
 
   
   
 
[[User:Atravers|Atravers]] 04:31, 10 April 2018 (UTC)
 
[[User:Atravers|Atravers]] 04:31, 10 April 2018 (UTC)
   
  +
[[Category:Arrow]]
 
[[Category:Monad]]
 
[[Category:Monad]]
 
[[Category:Proposals]]
 
[[Category:Proposals]]

Latest revision as of 08:14, 12 June 2023

Having praised monads to the hilt, let me level one criticism. Monads tend to be an all-or-nothing proposition. If you discover that you need interaction deep within your program, you must rewrite that segment to use a monad. If you discover that you need two sorts of interaction, you tend to make a single monad support both sorts. It seems to me that instead we should be able to move smoothly from no monads (no interactions) to one monad (a single form of interaction) to many monads (several independent forms of interactions). How to achieve this remains a challenge for the future.

How to Declare an Imperative, Philip Wadler.

Assuming the partible types being used are appropriately defined, then:

type M p a  =  p -> a

unit        :: Partible p =>     a -> M p a
unit x      =  \ u -> let !_ = part u in x

bind        :: Partible p =>     M p a -> (a -> M p b) -> M p b
m `bind` k  =  \ u -> let !(u1, u2) = part u in
                      let !x = m u1 in
                      let !y = k x u2 in
                      y 

next        :: Partible p =>     M p a -> M p b -> M p b
m `next` w  =  \ u -> let !(u1, u2) = part u in
                      let !x = m u1 in
                      let !y = w u2 in
                      y

fail        :: Partible p =>     String -> M p a
fail s      =  \ u -> let !_ = part u in error s

Furthermore:

mfix        :: Partible p =>     (a -> M p a) -> M p a
mfix m      =  \ u -> yet (\ x -> m x u)

mcommute    :: (Partible p1, Partible p2) => M p1 (M p2 a) -> M p2 (M p1 a)
mcommute g  =  \ v u -> g u v

mcommute'   :: (Monad m, Partible p) => m (M p a) -> M p (m a)
mcommute' m =  \ v -> liftM ($ v) m

where:

yet   :: (a -> a) -> a
yet f =  f (yet f)

Using partible types to define monadic ones can enable an intermediate approach to the use of effects, in contrast to the all-or-nothing proposition of only using the monadic interface. In addition, if the definitions for such monadic types are visible (e.g. as type synonyms), this may also allow the manipulation of control in ways beyond what the monadic interface provides.

Composing arrows

Partible types can also be used to define arrow types:

type A p b c =  (p -> b) -> (p -> c)

arr          :: Partible p      => (b -> c) -> A p b c
arr f        =  \ c' u -> f $! c' u


both         :: Partible p      => A p b c -> A p b' c' -> A p (b, b') (c, c')
f' `both` g' =  \ c' u -> let !(u1:u2:u3:_) = parts u in
                          let !(x, x')      = c' u1 in
                          let !y            = f' (unit x) u2 in
                          let !y'           = g' (unit x') u3 in
                          (y, y')                           
                where
                  unit x u = let !_ = part u in x

(...though most will probably opt for the convenience of the associated Kleisli type).

Composing comonads

Comonadic types can be defined using partible types as well:

type C p a       =  (a, p)

extract          :: Partible p =>    C p a -> a
extract (x, u)   =  let !_ = part u in x

duplicate        :: Partible p =>    C p a -> C p (C p a)
duplicate (x, u) =  let !(u1, u2) = part u in
                    ((x, u1), u2)

extend           :: Partible p =>    (C p a -> b) -> C p a -> C p b
extend h (x, u)  =  let !(u1, u2) = part u in
                    let !y        = h (x, u1) in
                    (y, u2)

See also:


Atravers 04:31, 10 April 2018 (UTC)