~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/kernel/src/erl_ddll.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • mto: (3.3.1 squeeze)
  • mto: This revision was merged to the branch mainline in revision 17.
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
26
26
         unload_driver/1, unload/1, reload/2, reload_driver/2, 
27
27
         format_error/1,info/1,info/0, start/0, stop/0]).
28
28
 
 
29
%%----------------------------------------------------------------------------
29
30
 
30
 
%% No reason to provide contracts for the first two functions
 
31
-spec start() -> {'error', {'already_started', 'undefined'}}.
31
32
 
32
33
start() ->
33
 
    {error,{already_started,undefined}}.
 
34
    {error, {already_started,undefined}}.
 
35
 
 
36
-spec stop() -> 'ok'.
34
37
 
35
38
stop() ->
36
39
    ok.
37
40
 
38
 
-spec(load_driver/2 :: (
39
 
        Path :: string() | atom(), 
40
 
        Driver :: string() | atom()) ->
41
 
        'ok' | {'error', any()}).
 
41
-spec load_driver(Path :: string() | atom(), Driver :: string() | atom()) ->
 
42
        'ok' | {'error', any()}.
42
43
 
43
44
load_driver(Path, Driver) ->
44
45
    do_load_driver(Path, Driver, [{driver_options,[kill_ports]}]).
45
46
 
46
 
-spec(load/2 :: (
47
 
        Path :: string() | atom(), 
48
 
        Driver :: string() | atom()) ->
49
 
        'ok' | {'error', any()}).
 
47
-spec load(Path :: string() | atom(), Driver :: string() | atom()) ->
 
48
        'ok' | {'error', any()}.
50
49
 
51
50
load(Path, Driver) ->
52
51
    do_load_driver(Path, Driver, []).
95
94
            end
96
95
    end.
97
96
 
98
 
-spec(unload_driver/1 :: (Driver :: string() | atom()) ->
99
 
        'ok' | {'error', any()}).
100
 
        
 
97
-spec unload_driver(Driver :: string() | atom()) -> 'ok' | {'error', any()}.
101
98
 
102
99
unload_driver(Driver) ->
103
100
    do_unload_driver(Driver,[{monitor,pending_driver},kill_ports]).
104
101
 
105
 
-spec(unload/1 :: (Driver :: string() | atom()) ->
106
 
        'ok' | {'error', any()}).
 
102
-spec unload(Driver :: string() | atom()) -> 'ok' | {'error', any()}.
107
103
 
108
104
unload(Driver) ->
109
105
    do_unload_driver(Driver,[]).
110
106
 
111
 
-spec(reload/2 :: (
112
 
        Path :: string() | atom(),
113
 
        Driver :: string() | atom()) ->
114
 
        'ok' | {'error', any()}).
 
107
-spec reload(Path :: string() | atom(), Driver :: string() | atom()) ->
 
108
        'ok' | {'error', any()}.
115
109
 
116
110
reload(Path,Driver) ->
117
111
    do_load_driver(Path, Driver, [{reload,pending_driver}]).
118
112
 
119
 
-spec(reload_driver/2 :: (
120
 
        Path :: string() | atom(),
121
 
        Driver :: string() | atom()) ->
122
 
        'ok' | {'error', any()}).
 
113
-spec reload_driver(Path :: string() | atom(), Driver :: string() | atom()) ->
 
114
        'ok' | {'error', any()}.
123
115
 
124
116
reload_driver(Path,Driver) ->
125
117
    do_load_driver(Path, Driver, [{reload,pending_driver},
126
118
                                  {driver_options,[kill_ports]}]).                          
127
119
 
128
 
-spec(format_error/1 :: (Code :: atom()) -> string()).
 
120
-spec format_error(Code :: atom()) -> string().
129
121
 
130
122
format_error(Code) ->
131
123
    case Code of
137
129
            erl_ddll:format_error_int(Code)
138
130
    end.
139
131
 
140
 
-spec(info/1 :: (Driver :: string() | atom()) ->
141
 
        [{atom(), any()}]).
 
132
-spec info(Driver :: string() | atom()) -> [{atom(), any()}].
142
133
 
143
134
info(Driver) ->
144
135
    [{processes, erl_ddll:info(Driver,processes)},
149
140
     {awaiting_load,  erl_ddll:info(Driver,awaiting_load)},
150
141
     {awaiting_unload, erl_ddll:info(Driver,awaiting_unload)}].
151
142
 
152
 
-spec(info/0 :: () ->
153
 
        [{string(), [{atom(), any()}]}]).
 
143
-spec info() -> [{string(), [{atom(), any()}]}].
154
144
 
155
145
info() ->
156
146
    {ok,DriverList} = erl_ddll:loaded_drivers(),