[Haskell-cafe] partial type annotations

Emil Axelsson emax at chalmers.se
Fri Jan 20 07:50:29 CET 2012


In the spirit of Oleg's hack, but with nicer combinator support, you can 
use the patch combinators I just uploaded to Hackage (prompted by this 
thread):

   http://hackage.haskell.org/package/patch-combinators

Your example then becomes:

   my_code_block = do
       x <- instruction1 -:: tCon (tCon tInteger)
       y <- instruction2 (x + x)

The signature `tCon (tCon tInteger)` should be read as the type `_ (_ 
Integer)`.

Alternatively, with ViewPatterns, you can write:

   my_code_block2 = do
       (tCon tInteger -> x) <- instruction1
       y <- instruction2 (x + x)
       return y

/ Emil


2012-01-19 21:37, Nicholas Tung skrev:
> Dear all,
>
>      I wanted to voice support for a partial type annotations. Here's my
> usage scenario: I have a monad for an imperative EDSL, which has an
> associated expression data type,
>
> class (Monad m, Expression (ExprTyp m)) => MyDSLMonad m where
>      data ExprTyp m :: * -> *
>
>      and you write imperative EDSL code like so,
>
> my_code_block = do
>      x <- instruction1
>      y <- instruction2 (x + x)
>      ...
>
>      I want the user to be able to annotate "x is an Integer". However,
> to do that now, one has to now add a type signature for my_code_block
> like so, so that the $m$ variable is in scope,
>
> my_code_block :: forall m. MyDSLMonad m => m ()
> my_code_block = do
>      x :: ExprTyp m Integer <- instruction1
>      ...
>
>      If such a feature were available, one could write a nice type
> synonym "Expr" and use it like so,
>
> type Expr a = ExprTyp _ a
>
> my_code_block = do
>      x :: Expr Integer <- instruction1
>
>      Suggestions for workarounds are appreciated. I created an
> `asExprTypeOf`, similar to Prelude's `asExprTyp`, but I don't like the
> syntax as much.
>
>      Some previous discussion
> * http://www.haskell.org/pipermail/haskell/2002-April/009409.html
> * (a reply) http://www.haskell.org/pipermail/haskell/2002-April/009413.html
> * http://hackage.haskell.org/trac/haskell-prime/wiki/PartialTypeAnnotations
>
> cheers,
> Nicholas — https://ntung.com — 4432-nstung
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list