Perhaps this is not what you had in mind, but we could write a signature like

    {-# LANGUAGE KindSignatures #-}
    signature Mystery where
    import Data.Kind
    import Control.Monad
    data MysteryMonad :: Type -> Type
    instance Functor MysteryMonad
    instance Applicative MysteryMonad
    instance Monad MysteryMonad
    instance PrimMonad MysteryMonad

that reused the existing PrimMonad class. Code could depend on that signature without being tied to a concrete monad (this would make the package that has the code "indefinite"). Once we compiled the indefinite code against an actual implementation, it would be optimized as if we had used concrete types from the beginning.

One problem with this solution is that it leaves out ST. If we wanted to make it work with ST, one possible hack would be to define the signature like this

    data MysteryMonad :: Type -> Type -> Type
    instance Functor (MysteryMonad s)
    instance Applicative (MysteryMonad s)
    instance Monad (MysteryMonad s)
    instance PrimMonad (MysteryMonad s)

And then use some kind of newtype adapter with a phantom type for non-ST monads:

module Mystery where  
type MysteryMonad = W IO
newtype W m a b = W (m b) deriving newtype (Functor, Applicative, Monad)

But perhaps it would complicate things too much.
 
On Sat, Sep 11, 2021 at 2:08 PM <haskell-cafe-request@haskell.org> wrote:
Send Haskell-Cafe mailing list submissions to
        haskell-cafe@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
or, via email, send a message with subject or body 'help' to
        haskell-cafe-request@haskell.org

You can reach the person managing the list at
        haskell-cafe-owner@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Haskell-Cafe digest..."


Today's Topics:

   1. Backpack: polymorphic instantation? (Jaro Reinders)


----------------------------------------------------------------------

Message: 1
Date: Sat, 11 Sep 2021 11:58:26 +0200
From: Jaro Reinders <jaro.reinders@gmail.com>
To: Haskell Cafe <haskell-cafe@haskell.org>
Subject: [Haskell-cafe] Backpack: polymorphic instantation?
Message-ID: <3fb19986-f998-61c7-8c56-482b1647e2eb@gmail.com>
Content-Type: text/plain; charset=utf-8; format=flowed

I'm playing around with backpack, trying to rewrite existing libraries. My end
goal is to see if Backpack could improve the primitive library. Right now, the
primitive library (in my opinion) relies too heavily on specialization of its
type classes, so I think Backpack could help. However, I seem to be running
into a limitation. I am wondering if it is a fundamental limitation, if perhaps
there is a workaround, or if Backpack could be improved to support this use-case.

Instead of primitive, I will take the simpler example: semigroup, which also
shows this limitation. Let's convert the Semigroup class to a backpack signature:

     unit indef where
       signature Semigroup where
         import Prelude hiding ((<>))
         data T
         (<>) :: T -> T -> T

The problem is how to implement this signature with the type of polymorphic
lists. It is easy to implement it for concrete lists like strings:

     unit string where
      module Semigroup where
       import Prelude hiding ((<>))
       type T = String
       (<>) :: T -> T -> T
       (<>) = (++)

It is also possible to implement it in terms of another signature:

     unit list where
       signature Elem where
         data A

       module Semigroup where
         import Prelude hiding ((<>))
         import Elem
         type T = [A]
         (<>) :: T -> T -> T
         (<>) = (++)

This is still problematic, because it is annoying that this new type A needs to
be instantiated each time you want to use it. However, even more importantly,
if I want to translate the 'PrimMonad' class to a Backpack signature then the
'ST s' instance needs a polymorphic type variable 's', which cannot be made
concrete.

And do note that I want the monad to be concrete for performance reasons, but
the 's' parameter doesn't have to be concrete, because it is a phantom
parameter anyway. And for lists making the 'a' parameter concrete also would
not improve performance as far as I know.

One possible way to fix this is to add a type variable in the 'Semigroup'
signature, but then I think it becomes impossible to write the 'String'
instance and sometimes you need more than one new type variable such as with
the 'ReaderT r (ST s)' instance of 'PrimMonad'.

In OCaml you can still kind of work around this problem by creating local
instances inside functions. That trick still allows you to write a polymorphic
concatenation function using a monoid signature (taken from [1]):

     let concat (type a) xs =
       let module MU = MonoidUtils (ListMonoid(struct type t = a end)) in
       MU.concat xs;;

So, I'm wondering if it would be possible to "generalise" over indefinite
Backpack types such as 'A' in the 'Elem' signature above or if we can at least
implement something which enables the same trick that you can use in OCaml.

Thanks,

Jaro

[1] https://blog.shaynefletcher.org/2017/05/more-type-classes-in-ocaml.html


------------------------------

Subject: Digest Footer

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe


------------------------------

End of Haskell-Cafe Digest, Vol 217, Issue 10
*********************************************