[Haskell-cafe] Vague: Assembly line process
Bas van Dijk
v.dijk.bas at gmail.com
Wed Jun 16 03:36:21 EDT 2010
On Tue, Jun 15, 2010 at 9:26 PM, Bas van Dijk <v.dijk.bas at gmail.com> wrote:
> On Tue, Jun 15, 2010 at 7:23 PM, Martin Drautzburg
> <Martin.Drautzburg at web.de> wrote:
>> When I know my supplies I want to know what I can produce. When I know what I
>> want to produce I want to know what supplies I need for that. Both kinds of
>> questions should be answered by a singe Process thingy.
>
> Your Process thingy reminds me of a natural isomorphism:
>
> data Iso a b = Iso { ab :: a -> b
> , ba :: b -> a
> }
>
>> I want to be able to chain processes and the whole thing should still act like
>> a Process.
>
> These isomorphisms can be chained together using the standard Category
> method '.':
>
> import qualified Control.Category as C
>
> instance C.Category Iso where
> id = Iso id id
> Iso bc cb . Iso ab ba = Iso (bc . ab) (ba . cb)
>
I couldn't help to generalize this a bit:
-# LANGUAGE TypeOperators, UnicodeSyntax #-}
import Control.Category
import Control.Arrow
import Prelude hiding (id, (.))
data Iso (⇝) a b = Iso { ab ∷ a ⇝ b
, ba ∷ b ⇝ a
}
type IsoFunc = Iso (→)
instance Category (⇝) ⇒ Category (Iso (⇝)) where
id = Iso id id
Iso bc cb . Iso ab ba = Iso (bc . ab) (ba . cb)
An 'Iso (⇝)' also _almost_ forms an Arrow (if (⇝) forms an Arrow):
instance Arrow (⇝) ⇒ Arrow (Iso (⇝)) where
arr f = Iso (arr f) undefined
first (Iso ab ba) = Iso (first ab) (first ba)
second (Iso ab ba) = Iso (second ab) (second ba)
Iso ab ba *** Iso cd dc = Iso (ab *** cd) (ba *** dc)
Iso ab ba &&& Iso ac ca = Iso (ab &&& ac) (ba . arr fst)
-- or: (ca . arr snd)
But note the unfortunate 'undefined' in the definition of 'arr'.
This seems to suggest that all the methods besides 'arr' need to move
to a separate type class. Maybe something like:
class Category (⇝) ⇒ Arrow (⇝) where
arr ∷ (a → b) → (a ⇝ b)
class Category (⇝) ⇒ Pass (⇝) where
first ∷ (a ⇝ b) → ((a, c) ⇝ (b, c))
second ∷ (a ⇝ b) → ((c, a) ⇝ (c, b))
(***) ∷ (a ⇝ b) → (c ⇝ d) → ((a, c) ⇝ (b, d))
(&&&) ∷ (a ⇝ b) → (a ⇝ c) → (a ⇝ (b, c))
Oh well...
Bas
More information about the Haskell-Cafe
mailing list