Skip to content

Commit

Permalink
fixup! Add emacs indention testcase
Browse files Browse the repository at this point in the history
  • Loading branch information
dgud committed Jan 25, 2018
1 parent 040f2cb commit 83c3ed5
Show file tree
Hide file tree
Showing 4 changed files with 43 additions and 32 deletions.
5 changes: 4 additions & 1 deletion lib/tools/test/emacs_SUITE_data/icr
Original file line number Diff line number Diff line change
Expand Up @@ -59,8 +59,11 @@ indent_case(1, Z) ->
X = 43 div 4,
foo(X);
{Z,_,_}
when Z < 10 -> % when should be indented
when Z < 10 orelse
Z =:= foo -> % Binary op alignment here !!!
X = 43 div 4,
Bool = Z < 5 orelse % Binary op args align differently after when
Z =:= foo, % and elsewhere ???
foo(X);
{Z,_,_}
when % when should be indented
Expand Down
8 changes: 4 additions & 4 deletions lib/tools/test/emacs_SUITE_data/terms
Original file line number Diff line number Diff line change
Expand Up @@ -110,12 +110,12 @@ map(3) ->
};
map(4) ->
#{
a => <<"a">>,
a => <<"a">>
,b => 2
};
map(M) ->
M#{a :=<<"a">>
,b:=1}.
map(MapVar) ->
MapVar = #{a :=<<"a">>
,b:=1}.

deep(Rec) ->
Rec#rec{ atom = 'atom',
Expand Down
20 changes: 11 additions & 9 deletions lib/tools/test/emacs_SUITE_data/try_catch
Original file line number Diff line number Diff line change
Expand Up @@ -125,20 +125,22 @@ indent_catch() ->
catch _:_ -> baf
end,

try
sune
of
_ ->
X = 5,
(catch foo(X)),
X + 10
catch _:_ -> baf
end,
Variable = try
sune
of
_ ->
X = 5,
(catch foo(X)),
X + 10
catch _:_ -> baf
after cleanup()
end,

try
(catch sune)
of
_ ->
foo1(),
catch foo() %% BUGBUG can't handle catch inside try without parentheses
catch _:_ ->
baf
Expand Down
42 changes: 24 additions & 18 deletions lib/tools/test/emacs_SUITE_data/type_specs
Original file line number Diff line number Diff line change
Expand Up @@ -6,17 +6,19 @@


-type ann() :: Var :: integer().
-type ann2() :: Var ::
'return'
| 'return_white_spaces'
| 'return_comments'
| 'text' | ann().
-type ann2() ::
'return'
| 'return_white_spaces'
| 'return_comments'
| 'text' | ann().
-type paren() ::
(ann2()).

-type t6() :: 1 | 2 | 3 |
'foo' |
'bar'.
-type t6() ::
1 | 2 | 3 |
'foo'
| 'bar'.

-type t8() :: {any(),none(),pid(),port(),
reference(),float()}.

Expand Down Expand Up @@ -47,12 +49,15 @@
<<_:3,_:_*1472>>|<<_:19,_:_*14>>| <<_:34>>|
<<_:34>>|<<_:34>>|<<_:34>>].

-type t18() :: fun(() -> t17() | t16()).
-type t19() :: fun((t18()) -> t16()) |
fun((nonempty_maybe_improper_list('integer', any())|
1|2|3|a|b|<<_:3,_:_*14>>|integer()) ->
nonempty_maybe_improper_list('integer', any())|
1|2|3|a|b|<<_:3,_:_*14>>|integer()).
-type t18() ::
fun(() -> t17() | t16()).
-type t19() ::
fun((t18()) -> t16()) |
fun((nonempty_maybe_improper_list('integer', any())|
1|2|3|a|b|<<_:3,_:_*14>>|integer())
->
nonempty_maybe_improper_list('integer', any())| %% left to col 16?
1|2|3|a|b|<<_:3,_:_*14>>|integer()). %% left to col 16?
-type t20() :: [t19(), ...].
-type t25() :: #rec3{f123 :: [t24() |
1|2|3|4|a|b|c|d|
Expand Down Expand Up @@ -85,15 +90,16 @@
-spec handle_cast(Cast ::
{'exchange', node(), [[name(),...]]}
| {'del_member', name(), pid()},
#state{}) -> {'noreply', #state{}}.
#state{}) ->
{'noreply', #state{}}. %% left to col 10?

-spec all(fun((T) -> boolean()), List :: [T]) ->
boolean() when is_subtype(T, term()). % (*)

-spec get_closest_pid(term()) ->
Return :: pid()
| {'error', {'no_process', term()}
| {'no_such_group', term()}}.
Return :: pid() %% left to col 10?
| {'error', {'no_process', term()}} %% left to col 10?
| {'no_such_group', term()}. %% left to col 10?

-spec add( X :: integer()
, Y :: integer()
Expand Down

0 comments on commit 83c3ed5

Please sign in to comment.