Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Haskell: how to write a monadic variadic function, with parameters using the monadic context

I'm trying to make a variadic function with a monadic return type, whose parameters also require the monadic context. (I'm not sure how to describe that second point: e.g. printf can return IO () but it's different in that its parameters are treated the same whether it ends up being IO () or String.)

Basically, I've got a data constructor that takes, say, two Char parameters. I want to provide two pointer style ID Char arguments instead, which can be automagically decoded from an enclosing State monad via a type class instance. So, instead of doing get >>= \s -> foo1adic (Constructor (idGet s id1) (idGet s id2)), I want to do fooVariadic Constructor id1 id2.

What follows is what I've got so far, Literate Haskell style in case somebody wants to copy it and mess with it.

First, the basic environment:

> {-# LANGUAGE FlexibleContexts #-}
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE MultiParamTypeClasses #-}

> import Control.Monad.Trans.State

> data Foo = Foo0
>          | Foo1 Char
>          | Foo2 Bool Char
>          | Foo3 Char Bool Char
>    deriving Show

> type Env = (String,[Bool])
> newtype ID a = ID {unID :: Int}
>    deriving Show

> class InEnv a where envGet :: Env -> ID a -> a
> instance InEnv Char where envGet (s,_) i = s !! unID i
> instance InEnv Bool where envGet (_,b) i = b !! unID i

Some test data for convenience:

> cid :: ID Char
> cid = ID 1
> bid :: ID Bool
> bid = ID 2
> env :: Env
> env = ("xy", map (==1) [0,0,1])

I've got this non-monadic version, which simply takes the environment as the first parameter. This works fine but it's not quite what I'm after. Examples:

$ mkFoo env Foo0 :: Foo
Foo0
$ mkFoo env Foo3 cid bid cid :: Foo
Foo3 'y' True 'y'

(I could use functional dependencies or type families to get rid of the need for the :: Foo type annotations. For now I'm not fussed about it, since this isn't what I'm interested in anyway.)

> mkFoo :: VarC a b => Env -> a -> b
> mkFoo = variadic
>
> class VarC r1 r2 where
>    variadic :: Env -> r1 -> r2
>
> -- Take the partially applied constructor, turn it into one that takes an ID
> -- by using the given state.
> instance (InEnv a, VarC r1 r2) => VarC (a -> r1) (ID a -> r2) where
>    variadic e f = \aid -> variadic e (f (envGet e aid))
>
> instance VarC Foo Foo where
>    variadic _ = id

Now, I want a variadic function that runs in the following monad.

> type MyState = State Env

And basically, I have no idea how I should proceed. I've tried expressing the type class in different ways (variadicM :: r1 -> r2 and variadicM :: r1 -> MyState r2) but I haven't succeeded in writing the instances. I've also tried adapting the non-monadic solution above so that I somehow "end up" with an Env -> Foo which I could then easily turn into a MyState Foo, but no luck there either.

What follows is my best attempt thus far.

> mkFooM :: VarMC r1 r2 => r1 -> r2
> mkFooM = variadicM
>
> class VarMC r1 r2 where
>    variadicM :: r1 -> r2
>
> -- I don't like this instance because it requires doing a "get" at each
> -- stage. I'd like to do it only once, at the start of the whole computation
> -- chain (ideally in mkFooM), but I don't know how to tie it all together.
> instance (InEnv a, VarMC r1 r2) => VarMC (a -> r1) (ID a -> MyState r2) where
>    variadicM f = \aid -> get >>= \e -> return$ variadicM (f (envGet e aid))
>
> instance VarMC Foo Foo where
>    variadicM = id
>
> instance VarMC Foo (MyState Foo) where
>    variadicM = return

It works for Foo0 and Foo1, but not beyond that:

$ flip evalState env (variadicM Foo1 cid :: MyState Foo)
Foo1 'y'
$ flip evalState env (variadicM Foo2 cid bid :: MyState Foo)

No instance for (VarMC (Bool -> Char -> Foo)
                       (ID Bool -> ID Char -> MyState Foo))

(Here I would like to get rid of the need for the annotation, but the fact that this formulation needs two instances for Foo makes that problematic.)

I understand the complaint: I only have an instance that goes from Bool -> Char -> Foo to ID Bool -> MyState (ID Char -> Foo). But I can't make the instance it wants because I need MyState in there somewhere so that I can turn the ID Bool into a Bool.

I don't know if I'm completely off track or what. I know that I could solve my basic issue (I don't want to pollute my code with the idGet s equivalents all over the place) in different ways, such as creating liftA/liftM-style functions for different numbers of ID parameters, with types like (a -> b -> ... -> z -> ret) -> ID a -> ID b -> ... -> ID z -> MyState ret, but I've spent too much time thinking about this. :-) I want to know what this variadic solution should look like.

like image 551
Deewiant Avatar asked Aug 29 '12 10:08

Deewiant


1 Answers

WARNING

Preferably don't use variadic functions for this type of work. You only have a finite number of constructors, so smart constructors don't seem to be a big deal. The ~10-20 lines you would need are a lot simpler and more maintainable than a variadic solution. Also an applicative solution is much less work.

WARNING

The monad/applicative in combination with variadic functions is the problem. The 'problem' is the argument addition step used for the variadic class. The basic class would look like

class Variadic f where 
    func :: f 
    -- possibly with extra stuff

where you make it variadic by having instances of the form

instance Variadic BaseType where ...
instance Variadic f =>  Variadic (arg -> f) where ...

Which would break when you would start to use monads. Adding the monad in the class definition would prevent argument expansion (you would get :: M (arg -> f), for some monad M). Adding it to the base case would prevent using the monad in the expansion, as it's not possible (as far as I know) to add the monadic constraint to the expansion instance. For a hint to a complex solution see the P.S..

The solution direction of using a function which results in (Env -> Foo) is more promising. The following code still requires a :: Foo type constraint and uses a simplified version of the Env/ID for brevity.

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}

module Test where

data Env = Env
data ID a = ID
data Foo
    = Foo0
    | Foo1 Char
    | Foo2 Char Bool
    | Foo3 Char Bool Char
    deriving (Eq, Ord, Show)

class InEnv a where
    resolve :: Env -> ID a -> a
instance InEnv Char where
    resolve _ _ = 'a'
instance InEnv Bool where
    resolve _ _ = True

The Type families extension is used to make the matching stricter/better. Now the variadic function class.

class MApp f r where
    app :: Env -> f -> r

instance MApp Foo Foo where
    app _ = id
instance (MApp r' r, InEnv a, a ~ b) => MApp (a -> r') (ID b -> r) where
    app env f i = app env . f $ resolve env i
    -- using a ~ b makes this instance to match more easily and
    -- then forces a and b to be the same. This prevents ambiguous
    -- ID instances when not specifying there type. When using type
    -- signatures on all the ID's you can use
    -- (MApp r' r, InEnv a) => MApp (a -> r') (ID a -> r)
    -- as constraint.

The environment Env is explicitly passed, in essence the Reader monad is unpacked preventing the problems between monads and variadic functions (for the State monad the resolve function should return a new environment). Testing with app Env Foo1 ID :: Foo results in the expected Foo1 'a'.

P.S. You can get monadic variadic functions to work (to some extent) but it requires bending your functions (and mind) in some very strange ways. The way I've got such things to work is to 'fold' all the variadic arguments into a heterogeneous list. The unwrapping can then be done monadic-ally. Though I've done some things like that, I strongly discourage you from using such things in actual (used) code as it quickly gets incomprehensible and unmaintainable (not to speak of the type errors you would get).

like image 76
Laar Avatar answered Nov 15 '22 06:11

Laar