Difference between revisions of "User:Zzo38/Proposal for more-notation"

From HaskellWiki
Jump to navigation Jump to search
 
(6 intermediate revisions by the same user not shown)
Line 96: Line 96:
 
* Duplicate fields that do not match are errors.
 
* Duplicate fields that do not match are errors.
 
* A more-declaration can specify both the type and the value. Types are only used in data type declarations and values only in the other places.
 
* A more-declaration can specify both the type and the value. Types are only used in data type declarations and values only in the other places.
  +
  +
In addition, parameters of a more-notation used in a field more-notation of a datatype declaration can be named <tt>_</tt> in which case that parameter can only be used to compute the value of the field, not the type of the field. It is also permitted in a field more-notation of a value construction or update syntax, which case that parameter is not used for value construction and can only be used to compute the type. If there is a parameter that is named <tt>_</tt> neither in the value or datatype declaration, then it has to be a type but you can use that type both in the type of the field and in types used for computing values of that field.
   
 
Example:
 
Example:
Line 126: Line 128:
   
 
===Uses in quotations===
 
===Uses in quotations===
  +
A more-notation can go with quotations in both ways, and with splices in both ways. For example, you can have <tt>$(doThis 0 [more MoreDoThis])</tt> with declarations having to do with <tt>MoreDoThis</tt> outside of the splice.
   
 
===Manipulation in splices===
 
===Manipulation in splices===
Line 175: Line 178:
   
 
As it might see, they are all written in many places, and the other ones are just written all in one way.
 
As it might see, they are all written in many places, and the other ones are just written all in one way.
  +
<haskell>
 
 
data PExp l = more PExpConstructors l;
 
data PExp l = more PExpConstructors l;
 
instance Annotated PExp where {
 
instance Annotated PExp where {
 
ann e = case e of more PExpAnnCases;
 
ann e = case e of more PExpAnnCases;
amap f e = case e of more PExpAmapCases;
+
amap f e = case e of more PExpAmapCases f;
 
};
 
};
 
let {
 
let {
Line 190: Line 193:
 
return $ fmap convAnn m;
 
return $ fmap convAnn m;
 
};
 
};
  +
</haskell>
   
 
===Magic Set Editor===
 
===Magic Set Editor===
  +
In MSE, there are game templates, style templates, and export templates. Let's say you could somehow write them as a value in Haskell (MSE has some impure functions, but it is possible to make pure versions of those functions).
  +
  +
You could have a card datatype like this (if the <tt>cardStyle</tt> is <tt>Nothing</tt> then it uses the default style for the set):
  +
data Card = Card { more CardFields, cardStyle :: Maybe Style };
  +
  +
Now you can have styles.
  +
data Style = more Styles;
  +
renderStyle :: Style -> Render ();
  +
renderStyle s = case s of more StyleRenderers;
  +
  +
The <tt>Render</tt> monad can allow you to retrieve card field values, as well as use do-notation with more-notation. You could then use the orders of the more-declarations to represent z-orders of fields.
   
 
===Extensibility===
 
===Extensibility===
   
 
===Literate programming===
 
===Literate programming===
  +
You might want a datatype or something else representing features of the program, and you might want to organize them into chapters. Therefore, you can define things in the chapter they belong.
  +
  +
===Inform 7===
  +
  +
==See also==
  +
* [[Extensible datatypes]]
  +
* [[Relative infix operator precedences]]
   
 
[[Category:Proposals]]
 
[[Category:Proposals]]

Latest revision as of 19:55, 16 September 2011

This document is proposal for more-notation in Haskell.

Syntax

Anywhere that a more-notation is allowed (see Uses), you can use the syntax:

  • more [(name_of_enumeration)] more_name {parameters}
  • name_of_enumeration: A name of any type which is an enumeration. It can be another one using more-notation, but it must be able to fully determine it before this more-notation can be fully determined.
  • more_name: A capitalized name. It uses the same namespace as constructors, so you are not allowed to have a constructor of the same name (although it is OK to have types of the that name).
  • parameters: Optional lowercased names. These names are in local scope, and may already exist in this scope, although they do not have to.

A more-declaration is a module-level declaration of this syntax:

  • [ numeric_literal | (enumeration_constructor) ] more_name {parameters} = contents { | contents } ;
  • numeric_literal: It should be a natural number. Omitted is the same as zero. This number is called the "order" of the declaration.
  • enumeration_constructor: A constructor of the enumeration that was specified in the more-notation. If an enumeration is specified, the enumeration constructor is required here. This number is called the "order" of the declaration.
  • parameters: Lowercased names which will be scoped locally to this declaration. The number of parameters must match the number of parameters specified in the more-notation. An unused parameter can be replaced by an underscore.
  • contents: The contents depends on where the more-notation is.

Semantics

In the place where the more-notation is, all contents of more-declarations of that name will be reordered and corrected before being placed in place of the more-notation.

Automatic reordering is overridden by the enumeration constructors or numeric literals in front of more-declarations.

Uses

Do-blocks

A statement in a do-block may be replaced by a more-notation. Semantics of more-declarations becomes as follows:

  • Multiple statements in a single more-declaration stay in that order and consecutive.

Example:

x = (2 *);
main = do {
  x <- return 21;
  more Doing x;
  print x;
};
Doing a = a <- return $ x a;

becomes

x = (2 *);
main = do {
  x <- return 21;
  x <- return $ Main.x x;
  print x; -- results in 42 (the answer to life, the universe, and everything)
};

Case alternatives

An alternative for a case block may be replaced by a more-notation. Semantics of more-declarations becomes as follows:

  • Cases within an order are reordered so that the most specific ones come first.

Example:

X = (_, False, True) -> 1;
X = (True, True, True) -> 2;
X = _ -> 3;
X = (False, True, True) -> 4;
y x = case x of {
  more X;
};

becomes:

y x = case x of {
  (True, True, True) -> 2;
  (False, True, True) -> 4;
  (_, False, True) -> 1;
  _ -> 3;
};

Case guards

Cases can have guards and case alternatives in more-declarations can also have guards that use more-notation. There is no guarantee to the order except:

  • Guards listed in a single more-declaration keep that order.
  • Duplicate guards are removed.
  • Duplicate guard conditions that to not have matching result expressions are errors.
  • You can list guard conditions without the result values; these cause the order to be forced if such guard conditions exist, but does not create them if they do not exist.

Example:

y x = case x of {
  more Cases;
};
Cases = (a, b) | more X a b;
X a b = a > 5 -> b;
X a b = a < 5 -> a;
X a b = a == 5 -> 0;

Datatype declarations

A constructor definition in a data declaration is allowed to be replaced by a more-notation. Semantics of more-declarations becomes as follows:

  • Duplicate constructors are removed.
  • Duplicate constructors that do not match are errors.
  • Multiple constructors in a single more-declaration are guaranteed to keep the order given.

Example:

data T = Zero | more T deriving (Eq);
T = Two | Three | Four;
T = One | Two;

becomes

data T = Zero | One | Two | Three | Four deriving (Eq);

Fields in record syntax

A field in either a data type declaration or in a value construction or update syntax can be replaced by more-notation. Semantics of more-declarations becomes as follows:

  • Duplicate fields are removed.
  • Duplicate fields that do not match are errors.
  • A more-declaration can specify both the type and the value. Types are only used in data type declarations and values only in the other places.

In addition, parameters of a more-notation used in a field more-notation of a datatype declaration can be named _ in which case that parameter can only be used to compute the value of the field, not the type of the field. It is also permitted in a field more-notation of a value construction or update syntax, which case that parameter is not used for value construction and can only be used to compute the type. If there is a parameter that is named _ neither in the value or datatype declaration, then it has to be a type but you can use that type both in the type of the field and in types used for computing values of that field.

Example:

data Abc = Abc { name_of :: String, more AbcField };
makeAbc :: Abc;
makeAbc = Abc { name_of = "", more AbcField };
AbcField = age_of :: Int = 0;
AbcField = existing :: Bool = True;

becomes

data Abc = Abc { name_of :: String, age_of :: Int, existing :: Bool };
makeAbc :: Abc;
makeAbc = Abc { name_of = "", age_of = 0, existing = True }; 

Lists

A list item can be replaced by a more-notation. Semantics of more-declarations becomes as follows:

  • Multiple items in a single more-declaration stay in that order and consecutive.

Example:

k :: [String];
k = [more K];
1 K = "One";
5 K = "Five";
3 K = "Three";
K = "Zero";

becomes:

k :: [String];
k = ["Zero", "One", "Three", "Five"];

Combining with Template Haskell

Uses in quotations

A more-notation can go with quotations in both ways, and with splices in both ways. For example, you can have $(doThis 0 [more MoreDoThis]) with declarations having to do with MoreDoThis outside of the splice.

Manipulation in splices

Types and constructors

* Dec
** MoreCaseD Name MoreOrder [Name] [Match]
** MoreDataD Name MoreOrder [Name] [Con]
** MoreDoD Name MoreOrder [Name] [Stmt]
** MoreListD Name MoreOrder [Name] [Exp]
** MoreRecD Name MoreOrder [Name] [MoreField]
* Info
** MoreI Int MoreMode Name [Dec]
* MoreField = (Name, Maybe StrictType, Maybe Exp)
* MoreMode
** MoreCase
** MoreData
** MoreDo
** MoreList
** MoreRec Bool Bool
* MoreOrder
** NoOrder
** NamedOrder Name
** NumericOrder Int

Purpose to use more-notation

haskell-src-exts

In the ParseSyntax.hs file, everything has to be defined multiple times in different places, and in a common way. Using more-notation with Template Haskell could fix that. You could even put different extensions in different files and then combine them into one file.

data PExp l
    = Var l (QName l)                       -- ^ variable
    | IPVar l (IPName l)                    -- ^ implicit parameter variable
    | Con l (QName l)                       -- ^ data constructor
    | Lit l (Literal l)                     -- ^ literal constant
{- ... -}
instance Annotated PExp where
    ann e = case e of
        Var l qn        -> l
        IPVar l ipn     -> l
        Con l qn        -> l
        Lit l lit       -> l
{- ... -}
   amap f e = case e of
       Var l qn                -> Var   (f l) qn
       IPVar l ipn             -> IPVar (f l) ipn
       Con l qn                -> Con   (f l) qn
       Lit l lit               -> Lit   (f l) lit

As it might see, they are all written in many places, and the other ones are just written all in one way.

 data PExp l = more PExpConstructors l;
 instance Annotated PExp where {
   ann e = case e of more PExpAnnCases;
   amap f e = case e of more PExpAmapCases f;
 };
 let {
   convAnn :: Dec -> Dec;
   convAnn (MoreDataD _ _ _ c) = MoreCaseD ''PExpAnnCases NoOrder 'l $ fmap convAnn1 c;
   convAnn1 :: Con -> Match;
   convAnn1 (NormalC n t) = Match (ConP n $ (VarP 'l) : fmap (const WildP) (tail t)) (VarE 'l) [];
 } in do {
   MoreI _ _ _ m <- reify ''PExpConstructors;
   return $ fmap convAnn m;
 };

Magic Set Editor

In MSE, there are game templates, style templates, and export templates. Let's say you could somehow write them as a value in Haskell (MSE has some impure functions, but it is possible to make pure versions of those functions).

You could have a card datatype like this (if the cardStyle is Nothing then it uses the default style for the set):

data Card = Card { more CardFields, cardStyle :: Maybe Style };

Now you can have styles.

data Style = more Styles;
renderStyle :: Style -> Render ();
renderStyle s = case s of more StyleRenderers;

The Render monad can allow you to retrieve card field values, as well as use do-notation with more-notation. You could then use the orders of the more-declarations to represent z-orders of fields.

Extensibility

Literate programming

You might want a datatype or something else representing features of the program, and you might want to organize them into chapters. Therefore, you can define things in the chapter they belong.

Inform 7

See also