[Haskell-cafe] gathering position information lazily using traverse

2010-09-10 Thread Jan Christiansen

Dear Applicative experts,

I am seeking advice on Applicative instances and their use in  
traverse. Consider the following Applicative instance.


  newtype Proj a = Proj { unProj :: [Bool] - a }

  instance Functor Proj where
fmap g (Proj f) = Proj (g . f)

  instance Applicative Proj where
pure = Proj . const
Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))

In fact, this is not an Applicative instance as it does not satisfy  
the laws. On basis of this instance I have defined the following  
function.


  gshape :: Traversable t = t a - t [Bool]
  gshape x = unProj (traverse (const (Proj reverse)) x) []

The idea is simply to replace every polymorphic component by an  
identifier that identifies the position of the component in the data  
structure. That is, provided with the identifier I want to be able to  
project to the corresponding component. In this case this identifier  
is a path in the idiomatic term from the root to the component.


I can define a correct Applicative instance if I add an additional  
constructor, which represents pure. I did not prove that it satisfies  
all laws but I think it does.


  data Proj a = Pure a | Proj ([Bool] - a)

  instance Functor Proj where
fmap g (Pure x) = Pure (g x)
fmap g (Proj f) = Proj (g . f)

  instance Applicative Proj where
pure x = Pure x
Pure f * Pure x = Pure (f x)
Pure f * Proj x = Proj (\p - f (x p))
Proj f * Pure x = Proj (\p - f p x)
Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))

My problem is that this correct instance is too strict for my purpose.  
It is important that gshape operates correctly on partial data, that  
is, even if its argument is partial all the components should be  
replaced correctly. For example, we have


  gshape (Node _|_ 0 (Leaf 1))) = Node _|_ [False,True] (Leaf [True])


If the applicative instance performs pattern matching, like the latter  
instance, then gshape is too strict. Therefore I suspect that there is  
no correct Applicative instance that satisfies my needs but I am not  
at all certain.


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


Re: [Haskell-cafe] gathering position information lazily using traverse

2010-09-10 Thread Felipe Lessa
H...

On Fri, Sep 10, 2010 at 6:47 PM, Jan Christiansen
j...@informatik.uni-kiel.de wrote:
  instance Applicative Proj where
    pure = Proj . const
    Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))

  (pure f) * Proj x
   === Proj (const f) * Proj x
   === Proj (\p - (const f) (False:p) (x (True:p)))
   === Proj (\p - f (x (True:p)))

  Proj f * (pure x)
   === Proj f * Proj (const x)
   === Proj (\p - f (False:p) ((const x) (True:p)))
   === Proj (\p - f (False:p) x))

  instance Applicative Proj where
    pure x = Pure x
    Pure f * Pure x = Pure (f x)
    Pure f * Proj x = Proj (\p - f (x p))
    Proj f * Pure x = Proj (\p - f p x)
    Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))

  (pure f) * Proj x
   === Pure f * Proj x
   === Proj (\p - f (x p))

  (Proj f) * (pure x)
   === Proj f * Pure x
   === Proj (\p - f p x)

Was this difference intended?

Cheers! =)

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


Re: [Haskell-cafe] gathering position information lazily using traverse

2010-09-10 Thread Jan Christiansen


On 10.09.2010, at 23:58, Felipe Lessa wrote:


H...

On Fri, Sep 10, 2010 at 6:47 PM, Jan Christiansen
j...@informatik.uni-kiel.de wrote:

 instance Applicative Proj where
   pure = Proj . const
   Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))


 (pure f) * Proj x
  === Proj (const f) * Proj x
  === Proj (\p - (const f) (False:p) (x (True:p)))
  === Proj (\p - f (x (True:p)))

 Proj f * (pure x)
  === Proj f * Proj (const x)
  === Proj (\p - f (False:p) ((const x) (True:p)))
  === Proj (\p - f (False:p) x))


 instance Applicative Proj where
   pure x = Pure x
   Pure f * Pure x = Pure (f x)
   Pure f * Proj x = Proj (\p - f (x p))
   Proj f * Pure x = Proj (\p - f p x)
   Proj f * Proj x = Proj (\p - f (False:p) (x (True:p)))


 (pure f) * Proj x
  === Pure f * Proj x
  === Proj (\p - f (x p))

 (Proj f) * (pure x)
  === Proj f * Pure x
  === Proj (\p - f p x)

Was this difference intended?


Yes, this is intended. This difference is the reason why the former  
instance does not satisfy the Applicative laws while the latter does.


The first instance provides every subterm of an idiomatic term with a  
position. Even a pure term is provided with a position although it  
does not use it. The latter instance does not provide a pure term  
with a position as it does not need one. Therefore, the second  
instance simply passes position p to a subterm if the other subterm is  
pure. In the example for the first instance we can observe that we  
unnecessarily extend the position with True and False respectively.

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