Transducers in Haskell and the monomorphism restriction
Asked Answered
B

1

6

I implemented transducers in Haskell as follows:

{-# LANGUAGE RankNTypes #-}

import Prelude hiding (foldr)
import Data.Foldable

type Reducer b a = a -> b -> b
type Transducer a b = forall t. Reducer t b -> Reducer t a

class Foldable c => Collection c where
    insert :: a -> c a -> c a
    empty  :: c a

reduce :: Collection c => Transducer a b -> c a -> c b
reduce f = foldr (f insert) empty

mapping :: (a -> b) -> Transducer a b
mapping f g x = g (f x)

Now I want to define a generic map function. Hence I load the above code into GHCi:

Prelude> :load Transducer
[1 of 1] Compiling Main             ( Transducer.hs, interpreted )
Ok, modules loaded: Main.
*Main> let map = reduce . mapping

<interactive>:3:20:
    Couldn't match type ‘Reducer t0 b1 -> Reducer t0 a1’
                  with ‘forall t. Reducer t b -> Reducer t a’
    Expected type: (a1 -> b1) -> Transducer a b
      Actual type: (a1 -> b1) -> Reducer t0 b1 -> Reducer t0 a1
    Relevant bindings include
      map :: (a1 -> b1) -> c a -> c b (bound at <interactive>:3:5)
    In the second argument of ‘(.)’, namely ‘mapping’
    In the expression: reduce . mapping
*Main> let map f = reduce (mapping f)
*Main> :t map
map :: Collection c => (a -> b) -> c a -> c b

So I can't define map = reduce . mapping. However, I can define map f = reduce (mapping f).

I believe that this problem is caused by the monomorphism restriction. I would really like to write map = reduce . mapping instead of map f = reduce (mapping f). Hence, I have two questions:

  1. What's causing this problem? Is it indeed the monomorphism restriction?
  2. How do I fix this problem?
Barranca answered 11/1, 2015 at 14:0 Comment(9)
This is because of type inference with higher ranks. The monomorphism restriction does not matter here. No easy fix, I guess, except adding a type annotation or moving to a pointful definition.Legaspi
Type annotations don't help: let map :: Collection c => (a -> b) -> c a -> c b; map f = reduce (mapping f) still produces the same error.Barranca
The type error tells you exactly what the problem is. The type of mapping is silently changed to move the forall to the left-hand side (try :t mapping). This is a valid (semantics-preserving) transformation, but the typechecker expects the type Transducer a b proper, not Reducer t a -> Reducer t b (which could be distinct types). But when you write reduce (mapping f), the typechecker sees the application of mapping f must have type forall t. Reducer t b -> Reducer t a, which is the correct type for an argument to reduce.Alvar
let map = ((.) :: (Transducer a b -> c a -> c b) -> ((a -> b) -> Transducer a b) -> (a -> b) -> (c a -> c b)) reduce mapping works but... yuck. It's the (.) that needs the annotation.Legaspi
Try data-fix, which gives you more general case than transducers, called F-algebras. Transducers essentially are F-algebras, but only for list-shaped structures.Sworn
@chi, couldn't that be done as well by annotating the type of each operand? Still not fun, but not nearly as ugly.Aether
@Aether No, annotating the operands does not suffice. The problem is that if you write f (x :: forall a. ...) and f has a polymorphic type b -> ..., then b is not instantiated to forall a. ... since type variables can be instantiated during inference to monotypes, only. What happens is that a gets instantiated to some fresh skolem constant a0 and then f does no longer receive a fully polymorphic value. (Or at least, this is what I understood -- I'm definitely not an expert about how exactly GHC does inference)Legaspi
@Aether A much simpler explanation: if reduce is declared as having type T, using reduce :: T instead of just reduce does not tell GHC anything it does not already know. Type signatures matter when they tell GHC how to specialize a more general type: here reduce and mapping are used with their full generality, so no specialization is needed. Instead, (.) is specialized.Legaspi
I encountered the question with similar problem, and hopefully managed to explain why type doesn't work better there: https://mcmap.net/q/1779682/-rankntypes-doesn-39-t-match-return-typeKhachaturian
K
5

If you make Transducer a newtype, than the GHC will work out the types much better. Existential type variable won't escape the scope — transducer will stay polymorphic.

In other words, with below definition map = reduce . mapping works

{-# LANGUAGE RankNTypes #-}

import Prelude hiding (foldr, map, (.), id)
import Control.Category
import Data.Foldable

type Reducer b a = a -> b -> b
newtype Transducer a b = MkTrans { unTrans :: forall t. Reducer t b -> Reducer t a }

class Foldable c => Collection c where
    insert :: a -> c a -> c a
    empty  :: c a

instance Collection [] where
  insert = (:)
  empty = []

reduce :: Collection c => Transducer a b -> c a -> c b
reduce f = foldr (unTrans f insert) empty

mapping :: (a -> b) -> Transducer a b
mapping f = MkTrans $ \g x -> g (f x)

filtering :: (a -> Bool) -> Transducer a a
filtering f = MkTrans $ \g x y -> if f x then g x y else y

map :: Collection c => (a -> b) -> c a -> c b
map = reduce . mapping

filter :: Collection c => (a -> Bool) -> c a -> c a
filter = reduce . filtering

instance Category Transducer where
  id = MkTrans id
  MkTrans f . MkTrans g = MkTrans $ \x -> g (f x)

dub :: Num a => a -> a
dub x = x + x

test1 :: [Int]
test1 = reduce (filtering even . mapping dub) [1..10]
-- [2,4,6,8,10,12,14,16,18,20]

test2 :: [Int]
test2 = reduce (mapping dub . filtering even) [1..10]
-- [4,8,12,16,20]

*Main> :t reduce . mapping
reduce . mapping :: Collection c => (a -> b) -> c a -> c b

Also you could want to check http://www.reddit.com/r/haskell/comments/2cv6l4/clojures_transducers_are_perverse_lenses/ where definition is type Transducer a b =:: (a -> Constant (Endo x) a) -> (b -> Constant (Endo x) b) and various other. Also other interesting discussion.

Khachaturian answered 12/1, 2015 at 10:4 Comment(6)
Seems reasonable here to make it a newtype. Mind though, a lot of great stuff you can with lenses depends on the open-lying forall in the simple type, and wouldn't quite work with newtypes. Not sure how much that might be the case also for transducers.Franciscofranciska
Composing transducers can be done by making them a Category.Khachaturian
Edited answer a bit, add link to reddit answerKhachaturian
is it possible to implement taking transducer in similar manner to mapping or filtering? Tried to do so - but failed :( For me the most difficult part is to reuse taking in order to decrement n.Cacka
@Cacka taking should be a stateful transducer. To fit in this types above, it should be possible to write take n = foldr (taking n insert) empty, for some taking. You soon realise it's not possible. take is structurally inductive in n, not the list (like map or filter). By making newtype AutoReducer a b = a -> b -> (b, AutoReducer a b) it could be possible, but I didn't tried.Khachaturian
I see. Thank you for you response. I should try playing with AutoReducer then.Cacka

© 2022 - 2024 — McMap. All rights reserved.