[Haskell-cafe] Specialize a function on types of arguments?

Anthony Clayden anthony_clayden at clear.net.nz
Mon Nov 19 10:56:41 UTC 2018


On Mon, 19 Nov 2018 at 4:33 AM, ducis wrote:

>
> The top-level story is that I am trying to create a monad that somehow
> records the "intermediate steps" of computation.
>

Uh-oh. That got into deep water surprisingly quickly. We seem to be a long
way from your O.P. already. I'm not sure I can help much/here are some
general remarks.

Your examples below are using Int and String, but I take it you're really
dealing with much more complex types than that(?) -- you mention parse
trees. The usual way to stack one type on top of another in steps is with
Monad Transformers. At the point of stacking a different type, is that a
fresh computation ignoring history? Or is it a computation on type `a` that
produces a `b`?

I'm not convinced a monad is the right thing here. Perhaps any passing
Categoristas could offer an opinion. The reason using a monad feels wrong
is because of all the `return`s and especially the `(return . ( f ))`s.

I'm also wondering if using a list for "intermediate steps" is worth it: if
in general each computation step might produce a different type, just stack
on a heterogeneous list (in which some adjacent cells might by coincidence
be the same type). See the `'[]` promoted DataKind.

Yes, if GHC messages are talking about IncoherentInstances you are in
trouble. GHC seems far too eager to suggest them. "Incoherent" is just as
bad as it sounds. Almost always you can get the instances to compile but
you still can't use them/it shifts the problem to somewhere else in your
code which is even harder to diagnose. And it's always possible to rejig
the code to avoid IncoherentInstances -- that is, presuming your intended
semantics is actually coherent ;-).

I think that rather than monad bind `(>>=)` :: m a -> (a -> m b) -> m b`,
you want a polymonad bind `(>>?) :: m a -> (a -> m2 b) -> m2 b` in which
`m2` stacks a b-history on top of the a-history from `m` (which of course
includes history from previous types as well).

Now you're in trouble: polymonads currently give typechecking severe
indigestion. Contrast that for ordinary monads it's the same `m` all along
the chain, any step that fixes the monad (including the expected overall
return type) will ripple it through the lot.

But it's not as indeterminate as that: you can calculate `m2` given `m`,
`b`. And you can back-calculate `m a` given `m2` -- presuming you're using
a simple stacking structure. Sounds like a job for Type Families and (if
you want to continue using `do` notation) Rebindable syntax. But then
beware all the warnings in the Users Guide.


AntC


> e.g. something like
> Prelude> return 1
> ([],1)
> Prelude> return 1 >>= return.(+1)
> ([1],2)
> Prelude> return 1 >>= return.(+1)>>=return.(+3)
> ([2,1],5)
> (the list has the intermediate steps placed right-to-left so that new
> steps are appended to the left of the older steps)
> Of course all "intermediate steps of computation" actually form a graph,
> but we are frequently focused on, say,
> the transformation of a parse tree, where we want to take a series of
> snapshots of one "thing".
>
> Since a "lifted function" (e.g. return.(+1)) has in general the type a->m
> b, there are two ways
> to deal with input and output being not necessarily equal.
>
> The first approach I tried is to only record latest steps starting with
> the last change of type
> > newtype WithHistory b = WH ([b], b)
> and just discard the older steps when the input and output are of
> different types.
> > newtype WithHistory b = WH ([b], b) deriving
> (Show,Eq)
> > instance Monad WithHistory where
> >    return b = WH ([], b)
> >    (>>=) :: forall a b. WithHistory a -> (a -> WithHistory b) ->
> WithHistory b
> >    WH (h,a) >>= fm = WH (h1++coerceHistory (a:h),b)
> >       where
> >       WH (h1, b) = fm a
> >    class CoerceHistory a b  where
> >    coerceHistory :: [a] -> [b]
> >    instance CoerceHistory a a  where
> >    coerceHistory = id
> >    instance CoerceHistory a b  where
> >    coerceHistory _ = []
> I have got the coerceHistory function to (appear to) work in GHCi
> *Main> coerceHistory [2::Int] :: [Int]
> [2]
> *Main> coerceHistory "c" :: [Int]
> []
> But the Monad instanciation does not really work.
> GHC(7.6.3) hints for -XIncoherentInstances, which when
> enabled seems to force the (>>=) to always use the instance
> of coerceHistory returning []
>
> The second approach is to use [Dynamic] for steps, i.e.,
> > newtype WithHistory b = WH ([Dynamic], b)
> > instance Monad WithHistory where
> >    return b = WH ([], b)
> >    WH (h,a) >>= fm = WH (h1++forceDynList a++h, b)
> >       where WH (h1, b) = fm a
> and presumably
> > class ForceDynList a                                   where
> forceDynList :: a -> [Dynamic]
> > instance (Typeable a) => ForceDynList a    where forceDynList x = [toDyn
> x]
> > instance ForceDynList a                              where forceDynList
> x = []
> which is far from correct with error "Duplicate instance declarations"
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20181119/48b0e8ed/attachment-0001.html>


More information about the Haskell-Cafe mailing list