[GHC] #12477: Allow left sectioning and tuple sectioning of types

This gives rise to the monad `S -> (-, S)` the state monad. According to
#12477: Allow left sectioning and tuple sectioning of types -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Simple syntactic change that would be fine to have, allow writing the type `(•) r` as `(r •)`. Just getting a discussion going === Usage === Used briefly in the facts above, we should have that `Codensity (s ->)` (excuse the sectioning) is the same as state, and if we look, we see:
— [http://comonad.com/reader/2012/unnatural-transformations-and-
quantifiers/ The Comonad.Reader] on Unnatural Transformations and Quantifiers === Visible type application === Makes visible type application seem nicer: {{{#!hs fmap @_ @_ @((:-) _) :: (b :- b') -> (a :- b) -> (a :- b') fmap @_ @_ @((->) _) :: (b -> b') -> (a -> b) -> (a -> b') -- vs fmap @_ @_ @(_ :-) :: (b :- b') -> (a :- b) -> (a :- b') fmap @_ @_ @(_ ->) :: (b -> b') -> (a -> b) -> (a -> b') }}} === Examples === {{{#!hs instance Functor ((->) r) instance Functor ((,) a) instance Copointed ((,,) a b) instance Copointed ((,,) a b c) instance Magnify ((->) b) ((->) a) b a where type instance Key ((:->:) a) = a instance HasTrie e => Lookup ((:->:) e) where instance Memo a => Functor ((~>) a) where instance Functor ((&) a) where type Dom ((&) a) = (:-) type Cod ((&) a) = (:-) instance Functor ((:-) a) where type Dom ((:-) a) = (:-) type Cod ((:-) a) = (->) fmap = (.) instance Functor ((:~:) a) where type Dom ((:~:) a) = (:~:) type Cod ((:~:) a) = (->) fmap = (.) instance Adjunction ((,)a) ((->)a) (->) (->) where }}} becomes {{{#!hs instance Functor (r ->) instance Functor (a,) instance Copointed (a, b,) instance Copointed (a, b, c,) instance Magnify (b ->) (a ->) b a where type instance Key (a :->:) = a instance HasTrie e => Lookup (e :->:) where instance Memo a => Functor (a ~>) where instance Functor (a &) where type Dom (a &) = (:-) type Cod (a &) = (:-) instance Functor (a :-) where type Dom (a :-) = (:-) type Cod (a :-) = (->) fmap = (.) instance Functor (a :~:) where type Dom (a :~:) = (:~:) type Cod (a :~:) = (->) fmap = (.) instance Adjunction (a ,) (a ->) (->) (->) where }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12477 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12477: Allow left sectioning and tuple sectioning of types -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'd be ok with this if someone wants to work through the details and implement it. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12477#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12477: Allow left sectioning and tuple sectioning of types -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * owner: => Iceland_jack -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12477#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

This gives rise to the monad `S -> (-, S)` the state monad. According to
#12477: Allow left sectioning and tuple sectioning of types -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: @@ -82,0 +82,9 @@ + + **Edit**: Yoneda becomes + + {{{#!hs + type f ~> g = forall xxx. f xxx -> g xxx + + -- Yoneda f a = ((->) a) ~> f + type Yoneda f a = (a ->) ~> f + }}} New description: Simple syntactic change that would be fine to have, allow writing the type `(•) r` as `(r •)`. Just getting a discussion going === Usage === Used briefly in the facts above, we should have that `Codensity (s ->)` (excuse the sectioning) is the same as state, and if we look, we see:
— [http://comonad.com/reader/2012/unnatural-transformations-and-
quantifiers/ The Comonad.Reader] on Unnatural Transformations and Quantifiers === Visible type application === Makes visible type application seem nicer: {{{#!hs fmap @_ @_ @((:-) _) :: (b :- b') -> (a :- b) -> (a :- b') fmap @_ @_ @((->) _) :: (b -> b') -> (a -> b) -> (a -> b') -- vs fmap @_ @_ @(_ :-) :: (b :- b') -> (a :- b) -> (a :- b') fmap @_ @_ @(_ ->) :: (b -> b') -> (a -> b) -> (a -> b') }}} === Examples === {{{#!hs instance Functor ((->) r) instance Functor ((,) a) instance Copointed ((,,) a b) instance Copointed ((,,) a b c) instance Magnify ((->) b) ((->) a) b a where type instance Key ((:->:) a) = a instance HasTrie e => Lookup ((:->:) e) where instance Memo a => Functor ((~>) a) where instance Functor ((&) a) where type Dom ((&) a) = (:-) type Cod ((&) a) = (:-) instance Functor ((:-) a) where type Dom ((:-) a) = (:-) type Cod ((:-) a) = (->) fmap = (.) instance Functor ((:~:) a) where type Dom ((:~:) a) = (:~:) type Cod ((:~:) a) = (->) fmap = (.) instance Adjunction ((,)a) ((->)a) (->) (->) where }}} becomes {{{#!hs instance Functor (r ->) instance Functor (a,) instance Copointed (a, b,) instance Copointed (a, b, c,) instance Magnify (b ->) (a ->) b a where type instance Key (a :->:) = a instance HasTrie e => Lookup (e :->:) where instance Memo a => Functor (a ~>) where instance Functor (a &) where type Dom (a &) = (:-) type Cod (a &) = (:-) instance Functor (a :-) where type Dom (a :-) = (:-) type Cod (a :-) = (->) fmap = (.) instance Functor (a :~:) where type Dom (a :~:) = (:~:) type Cod (a :~:) = (->) fmap = (.) instance Adjunction (a ,) (a ->) (->) (->) where }}} **Edit**: Yoneda becomes {{{#!hs type f ~> g = forall xxx. f xxx -> g xxx -- Yoneda f a = ((->) a) ~> f type Yoneda f a = (a ->) ~> f }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12477#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

For example, if you have a stream of values, `given by Cofree (, a)`,
#12477: Allow left sectioning and tuple sectioning of types -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): In the wild [https://www.reddit.com/r/haskell/comments/4z28nk/tear_down_cofree/d6sbmwr wild]: then you can use the free monad for `(a ->)` to extract a value at some index. At each step, you can either `return` a function to extract a value from the current position in the comonad, or `liftF` a function which tells you how to handle the next value in the stream. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12477#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12477: Allow left sectioning and tuple sectioning of types -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * type: bug => feature request -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12477#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12477: Allow left sectioning and tuple sectioning of types -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): [http://stackoverflow.com/questions/12963733/writing-cojoin-or-cobind- for-n-dimensional-grid-type/13102103#13102103 (p ->)] -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12477#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC