Module Allegro


module Allegro: sig .. end
This is an OCaml binding for Allegro. Allegro is a cross-platform library intended for use in computer games and other types of multimedia programming.




General Functions



Allegro API documentation for this module
val allegro_init : unit -> unit
val allegro_exit : unit -> unit
val allegro_message : string -> unit
val get_allegro_error : unit -> string
val allegro_id : unit -> string
val allegro_version : unit -> int * int * int * string * int * int * int
The three first integers contain the major, middle and minor version numbers. The text string contains all version numbers and maybe some additional text (for exemple "4.2.1 (SVN)"). And the release date of Allegro (year, month, day).
val set_window_title : name:string -> unit
val cpu_vendor : unit -> string

type cpu_family =
| CPU_FAMILY_UNKNOWN
| CPU_FAMILY_I386
| CPU_FAMILY_I486
| CPU_FAMILY_I586
| CPU_FAMILY_I686
| CPU_FAMILY_ITANIUM
| CPU_FAMILY_POWERPC
| CPU_FAMILY_EXTENDED
| CPU_FAMILY_NOT_FOUND
val get_cpu_family : unit -> cpu_family
val os_version : unit -> int
val os_revision : unit -> int
val os_multitasking : unit -> bool
val desktop_color_depth : unit -> int
val get_desktop_resolution : unit -> int * int

Graphics Modes



Allegro API documentation for this module
val set_color_depth : depth:int -> unit
val get_color_depth : unit -> int
val get_screen_width : unit -> int
val get_screen_height : unit -> int
val get_virtual_width : unit -> int
val get_virtual_height : unit -> int
val request_refresh_rate : rate:int -> unit
val get_refresh_rate : unit -> int

type gfx_driver =
| GFX_AUTODETECT
| GFX_AUTODETECT_FULLSCREEN
| GFX_AUTODETECT_WINDOWED
| GFX_SAFE
| GFX_TEXT
val set_gfx_mode : gfx_driver:gfx_driver ->
width:int -> height:int -> virtual_width:int -> virtual_height:int -> unit
raises Failure "set_gfx_mode" when it fails
val get_gfx_driver_name : unit -> string
val enable_triple_buffer : unit -> bool
val vsync : unit -> unit
val scroll_screen : x:int -> y:int -> unit
val request_scroll : x:int -> y:int -> unit
val poll_scroll : unit -> bool

type gfx_capabilities =
| GFX_CAN_SCROLL
| GFX_CAN_TRIPLE_BUFFER
| GFX_HW_CURSOR
| GFX_SYSTEM_CURSOR
| GFX_HW_HLINE
| GFX_HW_HLINE_XOR
| GFX_HW_HLINE_SOLID_PATTERN
| GFX_HW_HLINE_COPY_PATTERN
| GFX_HW_FILL
| GFX_HW_FILL_XOR
| GFX_HW_FILL_SOLID_PATTERN
| GFX_HW_FILL_COPY_PATTERN
| GFX_HW_LINE
| GFX_HW_LINE_XOR
| GFX_HW_TRIANGLE
| GFX_HW_TRIANGLE_XOR
| GFX_HW_GLYPH
| GFX_HW_VRAM_BLIT
| GFX_HW_VRAM_BLIT_MASKED
| GFX_HW_MEM_BLIT
| GFX_HW_MEM_BLIT_MASKED
| GFX_HW_SYS_TO_VRAM_BLIT
| GFX_HW_SYS_TO_VRAM_BLIT_MASKED
| GFX_HW_VRAM_STRETCH_BLIT
| GFX_HW_SYS_STRETCH_BLIT
| GFX_HW_VRAM_STRETCH_BLIT_MASKED
| GFX_HW_SYS_STRETCH_BLIT_MASKED
val get_gfx_capabilities : unit -> gfx_capabilities list

type switch_mode =
| SWITCH_NONE
| SWITCH_PAUSE
| SWITCH_AMNESIA
| SWITCH_BACKGROUND
| SWITCH_BACKAMNESIA
val set_display_switch_mode : switch_mode -> unit
val get_display_switch_mode : unit -> switch_mode
val is_windowed_mode : unit -> bool
val allegro_vram_single_surface : unit -> bool
val allegro_dos : unit -> bool

Truecolor Pixel Formats



Allegro API documentation for this module
type color 
val makecol : r:int -> g:int -> b:int -> color
val makecol_depth : depth:int -> r:int -> g:int -> b:int -> color
val transparent : unit -> color
val makeacol : r:int -> g:int -> b:int -> a:int -> color
val makeacol_depth : depth:int -> r:int -> g:int -> b:int -> a:int -> color
val color_index : int -> color
val getr : color -> int
val getg : color -> int
val getb : color -> int
val geta : color -> int
val palette_color : int -> color

Display Dependent Pixel Format


val makecol8 : r:int -> g:int -> b:int -> color
val makecol15 : r:int -> g:int -> b:int -> color
val makecol16 : r:int -> g:int -> b:int -> color
val makecol24 : r:int -> g:int -> b:int -> color
val makecol32 : r:int -> g:int -> b:int -> color
val makeacol32 : r:int -> g:int -> b:int -> a:int -> color
val makecol15_dither : r:int -> g:int -> b:int -> x:int -> y:int -> color
val makecol16_dither : r:int -> g:int -> b:int -> x:int -> y:int -> color
val getr8 : color -> int
val getg8 : color -> int
val getb8 : color -> int
val getr15 : color -> int
val getg15 : color -> int
val getb15 : color -> int
val getr16 : color -> int
val getg16 : color -> int
val getb16 : color -> int
val getr24 : color -> int
val getg24 : color -> int
val getb24 : color -> int
val getr32 : color -> int
val getg32 : color -> int
val getb32 : color -> int
val geta32 : color -> int
val getr_depth : depth:int -> color -> int
val getg_depth : depth:int -> color -> int
val getb_depth : depth:int -> color -> int
val geta_depth : depth:int -> color -> int

Palette Routines



Allegro API documentation for this module
type palette 
val new_palette : unit -> palette
val free_palette : pal:palette -> unit
free palettes got from the new_palette function
val set_palette : pal:palette -> unit
val get_palette : pal:palette -> unit
val set_color : index:int -> r:int -> g:int -> b:int -> a:int -> unit
val get_desktop_palette : unit -> palette
val generate_332_palette : pal:palette -> unit
val select_palette : pal:palette -> unit
val unselect_palette : unit -> unit
val palette_set_rgb : pal:palette -> i:int -> r:int -> g:int -> b:int -> unit
val palette_set_rgba : pal:palette -> i:int -> r:int -> g:int -> b:int -> a:int -> unit
sets the index i of the palette
val palette_get_rgb : pal:palette -> i:int -> int * int * int
val palette_get_rgba : pal:palette -> i:int -> int * int * int * int
gets the index i of the palette
val palette_copy_index : src:palette -> dst:palette -> i:int -> unit
copy an entry of a palette to another

Converting Between Color Formats



Allegro API documentation for this module
val hsv_to_rgb : h:float -> s:float -> v:float -> int * int * int
val rgb_to_hsv : r:int -> g:int -> b:int -> float * float * float

Bitmap Objects



Allegro API documentation for this module
type bitmap 
val get_screen : unit -> bitmap
val create_bitmap : width:int -> height:int -> bitmap
val create_sub_bitmap : parent:bitmap ->
x:int -> y:int -> width:int -> height:int -> bitmap
val create_video_bitmap : width:int -> height:int -> bitmap
val create_system_bitmap : width:int -> height:int -> bitmap
val create_bitmap_ex : color_depth:int -> width:int -> height:int -> bitmap
val bitmap_color_depth : bmp:bitmap -> int
val destroy_bitmap : bmp:bitmap -> unit
val get_bitmap_width : bmp:bitmap -> int
val get_bitmap_height : bmp:bitmap -> int
val acquire_bitmap : bmp:bitmap -> unit
val release_bitmap : bmp:bitmap -> unit
val acquire_screen : unit -> unit
val release_screen : unit -> unit
val bitmap_mask_color : bmp:bitmap -> color
val is_same_bitmap : bmp1:bitmap -> bmp2:bitmap -> bool
val show_video_bitmap : bmp:bitmap -> unit
val request_video_bitmap : bmp:bitmap -> unit
val clear_bitmap : bmp:bitmap -> unit
val clear_to_color : bmp:bitmap -> color:color -> unit
val add_clip_rect : bmp:bitmap -> x1:int -> y1:int -> x2:int -> y2:int -> unit
val set_clip_rect : bmp:bitmap -> x1:int -> y1:int -> x2:int -> y2:int -> unit
val set_clip_state : bmp:bitmap -> bool -> unit
val get_clip_state : bmp:bitmap -> bool
val is_planar_bitmap : bmp:bitmap -> bool
val is_linear_bitmap : bmp:bitmap -> bool
val is_memory_bitmap : bmp:bitmap -> bool
val is_screen_bitmap : bmp:bitmap -> bool
val is_video_bitmap : bmp:bitmap -> bool
val is_system_bitmap : bmp:bitmap -> bool
val is_sub_bitmap : bmp:bitmap -> bool

Loading Image Files



Allegro API documentation for this module
val load_bitmap : string -> palette -> bitmap
val load_bmp : string -> palette -> bitmap
val load_lbm : string -> palette -> bitmap
val load_pcx : string -> palette -> bitmap
val load_tga : string -> palette -> bitmap
val blit : src:bitmap ->
dest:bitmap ->
src_x:int ->
src_y:int -> dest_x:int -> dest_y:int -> width:int -> height:int -> unit
val masked_blit : src:bitmap ->
dest:bitmap ->
src_x:int ->
src_y:int -> dest_x:int -> dest_y:int -> width:int -> height:int -> unit
val stretch_blit : src:bitmap ->
dest:bitmap ->
src_x:int ->
src_y:int ->
src_width:int ->
src_height:int ->
dest_x:int -> dest_y:int -> dest_width:int -> dest_height:int -> unit
val masked_stretch_blit : src:bitmap ->
dest:bitmap ->
src_x:int ->
src_y:int ->
src_width:int ->
src_height:int ->
dest_x:int -> dest_y:int -> dest_width:int -> dest_height:int -> unit

type color_conversion =
| COLORCONV_NONE
| COLORCONV_8_TO_15
| COLORCONV_8_TO_16
| COLORCONV_8_TO_24
| COLORCONV_8_TO_32
| COLORCONV_15_TO_8
| COLORCONV_15_TO_16
| COLORCONV_15_TO_24
| COLORCONV_15_TO_32
| COLORCONV_16_TO_8
| COLORCONV_16_TO_15
| COLORCONV_16_TO_24
| COLORCONV_16_TO_32
| COLORCONV_24_TO_8
| COLORCONV_24_TO_15
| COLORCONV_24_TO_16
| COLORCONV_24_TO_32
| COLORCONV_32_TO_8
| COLORCONV_32_TO_15
| COLORCONV_32_TO_16
| COLORCONV_32_TO_24
| COLORCONV_32A_TO_8
| COLORCONV_32A_TO_15
| COLORCONV_32A_TO_16
| COLORCONV_32A_TO_24
| COLORCONV_DITHER_PAL
| COLORCONV_DITHER_HI
| COLORCONV_KEEP_TRANS
| COLORCONV_EXPAND_256
| COLORCONV_REDUCE_TO_256
| COLORCONV_EXPAND_15_TO_16
| COLORCONV_REDUCE_16_TO_15
| COLORCONV_EXPAND_HI_TO_TRUE
| COLORCONV_REDUCE_TRUE_TO_HI
| COLORCONV_24_EQUALS_32
| COLORCONV_TOTAL
| COLORCONV_PARTIAL
| COLORCONV_MOST
| COLORCONV_DITHER
val set_color_conversion : color_conversion -> unit

Keyboard Routines



Allegro API documentation for this module
val install_keyboard : unit -> unit
val poll_keyboard : unit -> unit
val keypressed : unit -> bool
val readkey : unit -> char
val key_esc : unit -> bool
val key_enter : unit -> bool
val key_left : unit -> bool
val key_right : unit -> bool
val key_up : unit -> bool
val key_down : unit -> bool

type kb_flag =
| KB_SHIFT_FLAG
| KB_CTRL_FLAG
| KB_ALT_FLAG
| KB_LWIN_FLAG
| KB_RWIN_FLAG
| KB_MENU_FLAG
| KB_COMMAND_FLAG
| KB_SCROLOCK_FLAG
| KB_NUMLOCK_FLAG
| KB_CAPSLOCK_FLAG
| KB_INALTSEQ_FLAG
| KB_ACCENT1_FLAG
| KB_ACCENT2_FLAG
| KB_ACCENT3_FLAG
| KB_ACCENT4_FLAG
val get_kb_flag : kb_flag -> bool

type scancode =
| KEY_A
| KEY_B
| KEY_C
| KEY_D
| KEY_E
| KEY_F
| KEY_G
| KEY_H
| KEY_I
| KEY_J
| KEY_K
| KEY_L
| KEY_M
| KEY_N
| KEY_O
| KEY_P
| KEY_Q
| KEY_R
| KEY_S
| KEY_T
| KEY_U
| KEY_V
| KEY_W
| KEY_X
| KEY_Y
| KEY_Z
| KEY_0
| KEY_1
| KEY_2
| KEY_3
| KEY_4
| KEY_5
| KEY_6
| KEY_7
| KEY_8
| KEY_9
| KEY_0_PAD
| KEY_1_PAD
| KEY_2_PAD
| KEY_3_PAD
| KEY_4_PAD
| KEY_5_PAD
| KEY_6_PAD
| KEY_7_PAD
| KEY_8_PAD
| KEY_9_PAD
| KEY_F1
| KEY_F2
| KEY_F3
| KEY_F4
| KEY_F5
| KEY_F6
| KEY_F7
| KEY_F8
| KEY_F9
| KEY_F10
| KEY_F11
| KEY_F12
| KEY_ESC
| KEY_TILDE
| KEY_MINUS
| KEY_EQUALS
| KEY_BACKSPACE
| KEY_TAB
| KEY_OPENBRACE
| KEY_CLOSEBRACE
| KEY_ENTER
| KEY_COLON
| KEY_QUOTE
| KEY_BACKSLASH
| KEY_BACKSLASH2
| KEY_COMMA
| KEY_STOP
| KEY_SLASH
| KEY_SPACE
| KEY_INSERT
| KEY_DEL
| KEY_HOME
| KEY_END
| KEY_PGUP
| KEY_PGDN
| KEY_LEFT
| KEY_RIGHT
| KEY_UP
| KEY_DOWN
| KEY_SLASH_PAD
| KEY_ASTERISK
| KEY_MINUS_PAD
| KEY_PLUS_PAD
| KEY_DEL_PAD
| KEY_ENTER_PAD
| KEY_PRTSCR
| KEY_PAUSE
| KEY_ABNT_C1
| KEY_YEN
| KEY_KANA
| KEY_CONVERT
| KEY_NOCONVERT
| KEY_AT
| KEY_CIRCUMFLEX
| KEY_COLON2
| KEY_KANJI
| KEY_LSHIFT
| KEY_RSHIFT
| KEY_LCONTROL
| KEY_RCONTROL
| KEY_ALT
| KEY_ALTGR
| KEY_LWIN
| KEY_RWIN
| KEY_MENU
| KEY_SCRLOCK
| KEY_NUMLOCK
| KEY_CAPSLOCK
| KEY_EQUALS_PAD
| KEY_BACKQUOTE
| KEY_SEMICOLON
| KEY_COMMAND
val readkey_scancode : unit -> scancode
val clear_keybuf : unit -> unit
val set_keyboard_rate : delay:int -> repeat:int -> unit
val remove_keyboard : unit -> unit

Timer Routines



Allegro API documentation for this module
val install_timer : unit -> unit
val retrace_count : unit -> int
val rest : time:int -> unit

Mouse Routines



Allegro API documentation for this module
val install_mouse : unit -> int
val poll_mouse : unit -> unit
val mouse_driver_name : unit -> string
val enable_hardware_cursor : unit -> unit
val disable_hardware_cursor : unit -> unit

type mouse_cursor =
| MOUSE_CURSOR_NONE
| MOUSE_CURSOR_ALLEGRO
| MOUSE_CURSOR_ARROW
| MOUSE_CURSOR_BUSY
| MOUSE_CURSOR_QUESTION
| MOUSE_CURSOR_EDIT
val select_mouse_cursor : mouse_cursor -> unit
val set_mouse_cursor_bitmap : mouse_cursor -> bmp:bitmap -> unit
val show_mouse : bmp:bitmap -> unit
val hide_mouse : unit -> unit
val scare_mouse : unit -> unit
val scare_mouse_area : x:int -> y:int -> w:int -> h:int -> unit
val unscare_mouse : unit -> unit
val position_mouse : x:int -> y:int -> unit
val position_mouse_z : z:int -> unit
val set_mouse_range : x1:int -> y1:int -> x2:int -> y2:int -> unit
val set_mouse_speed : xspeed:int -> yspeed:int -> unit
val set_mouse_sprite : sprite:bitmap -> unit
val set_mouse_sprite_focus : x:int -> y:int -> unit
val get_mouse_mickeys : unit -> int * int
val get_mouse_x : unit -> int
val get_mouse_y : unit -> int
val get_mouse_z : unit -> int
val get_mouse_x_focus : unit -> int
val get_mouse_y_focus : unit -> int
val left_button_pressed : unit -> bool
val right_button_pressed : unit -> bool
val middle_button_pressed : unit -> bool
val get_mouse_b : unit -> int
val get_mouse_pos : unit -> int * int

Fixed Point Number



Allegro API documentation for this module
type fixed 
val itofix : int -> fixed
val fixtoi : fixed -> int
val ftofix : float -> fixed
val fixtof : fixed -> float
val fixadd : fixed -> fixed -> fixed
val fixsub : fixed -> fixed -> fixed
val fixdiv : fixed -> fixed -> fixed
val fixmul : fixed -> fixed -> fixed
val fixhypot : fixed -> fixed -> fixed
val fixceil : fixed -> int
val fixfloor : fixed -> int
val fixsin : fixed -> fixed
val fixcos : fixed -> fixed
val fixtan : fixed -> fixed
val fixasin : fixed -> fixed
val fixacos : fixed -> fixed
val fixatan : fixed -> fixed
val fixsqrt : fixed -> fixed
val to_rad : fixed -> fixed
val of_rad : fixed -> fixed
val fixminus : fixed -> fixed
val fixatan2 : y:fixed -> x:fixed -> fixed

Drawing Primitives



Allegro API documentation for this module
val putpixel : bmp:bitmap -> x:int -> y:int -> color:color -> unit
val rect : bmp:bitmap ->
x1:int -> y1:int -> x2:int -> y2:int -> color:color -> unit
val rectfill : bmp:bitmap ->
x1:int -> y1:int -> x2:int -> y2:int -> color:color -> unit
val arc : bmp:bitmap ->
x:int ->
y:int ->
angle1:fixed ->
angle2:fixed -> r:int -> color:color -> unit
val floodfill : bmp:bitmap -> x:int -> y:int -> color:color -> unit
val spline : bmp:bitmap ->
x1:int ->
y1:int ->
x2:int ->
y2:int -> x3:int -> y3:int -> x4:int -> y4:int -> color:color -> unit
val circle : bmp:bitmap ->
x:int -> y:int -> radius:int -> color:color -> unit
val circlefill : bmp:bitmap ->
x:int -> y:int -> radius:int -> color:color -> unit
val ellipse : bmp:bitmap ->
x:int -> y:int -> rx:int -> ry:int -> color:color -> unit
val ellipsefill : bmp:bitmap ->
x:int -> y:int -> rx:int -> ry:int -> color:color -> unit
val triangle : bmp:bitmap ->
x1:int ->
y1:int -> x2:int -> y2:int -> x3:int -> y3:int -> color:color -> unit
val line : bmp:bitmap ->
x1:int -> y1:int -> x2:int -> y2:int -> color:color -> unit
val fastline : bmp:bitmap ->
x1:int -> y1:int -> x2:int -> y2:int -> color:color -> unit
val vline : bmp:bitmap ->
x:int -> y1:int -> y2:int -> color:color -> unit
val hline : bmp:bitmap ->
x1:int -> y:int -> x2:int -> color:color -> unit
val getpixel : bmp:bitmap -> x:int -> y:int -> color
val do_circle : bmp:bitmap ->
x:int ->
y:int ->
radius:int ->
d:int -> proc:(bmp:bitmap -> x:int -> y:int -> d:int -> unit) -> unit
val do_ellipse : bmp:bitmap ->
x:int ->
y:int ->
rx:int ->
ry:int ->
d:int -> proc:(bmp:bitmap -> x:int -> y:int -> d:int -> unit) -> unit

Sprites



Allegro API documentation for this module
val draw_sprite : bmp:bitmap -> sprite:bitmap -> x:int -> y:int -> unit
val draw_sprite_v_flip : bmp:bitmap -> sprite:bitmap -> x:int -> y:int -> unit
val draw_sprite_h_flip : bmp:bitmap -> sprite:bitmap -> x:int -> y:int -> unit
val draw_sprite_vh_flip : bmp:bitmap -> sprite:bitmap -> x:int -> y:int -> unit
val rotate_sprite : bmp:bitmap ->
sprite:bitmap -> x:int -> y:int -> angle:fixed -> unit
val rotate_sprite_v_flip : bmp:bitmap ->
sprite:bitmap -> x:int -> y:int -> angle:fixed -> unit
val rotate_scaled_sprite : bmp:bitmap ->
sprite:bitmap ->
x:int -> y:int -> angle:fixed -> scale:fixed -> unit
val rotate_scaled_sprite_v_flip : bmp:bitmap ->
sprite:bitmap ->
x:int -> y:int -> angle:fixed -> scale:fixed -> unit
val pivot_sprite : bmp:bitmap ->
sprite:bitmap ->
x:int -> y:int -> cx:int -> cy:int -> angle:fixed -> unit
val pivot_sprite_v_flip : bmp:bitmap ->
sprite:bitmap ->
x:int -> y:int -> cx:int -> cy:int -> angle:fixed -> unit
val pivot_scaled_sprite : bmp:bitmap ->
sprite:bitmap ->
x:int ->
y:int ->
cx:int -> cy:int -> angle:fixed -> scale:fixed -> unit
val pivot_scaled_sprite_v_flip : bmp:bitmap ->
sprite:bitmap ->
x:int ->
y:int ->
cx:int -> cy:int -> angle:fixed -> scale:fixed -> unit
val stretch_sprite : bmp:bitmap ->
sprite:bitmap -> x:int -> y:int -> w:int -> h:int -> unit
val draw_character_ex : bmp:bitmap ->
sprite:bitmap ->
x:int -> y:int -> color:color -> bg:color -> unit
val draw_lit_sprite : bmp:bitmap ->
sprite:bitmap -> x:int -> y:int -> color:color -> unit
val draw_trans_sprite : bmp:bitmap -> sprite:bitmap -> x:int -> y:int -> unit
val draw_gouraud_sprite : bmp:bitmap ->
sprite:bitmap ->
x:int ->
y:int ->
c1:color ->
c2:color -> c3:color -> c4:color -> unit

RLE Sprites



Allegro API documentation for this module
type rle_sprite 
val get_rle_sprite : tmp:bitmap -> rle_sprite
val destroy_rle_sprite : rle_sprite -> unit
val draw_rle_sprite : bmp:bitmap -> sprite:rle_sprite -> x:int -> y:int -> unit
val draw_trans_rle_sprite : bmp:bitmap -> sprite:rle_sprite -> x:int -> y:int -> unit
val draw_lit_rle_sprite : bmp:bitmap ->
sprite:rle_sprite -> x:int -> y:int -> color:color -> unit

Compiled Sprites



Allegro API documentation for this module
type compiled_sprite 
val get_compiled_sprite : bmp:bitmap -> planar:bool -> compiled_sprite
val destroy_compiled_sprite : sprite:compiled_sprite -> unit
val draw_compiled_sprite : bmp:bitmap ->
sprite:compiled_sprite -> x:int -> y:int -> unit

Text Output



Allegro API documentation for this module
type font 
val get_font : unit -> font
val allegro_404_char : char -> unit
val text_length : f:font -> string -> int
val text_height : f:font -> int
val textout_ex : bmp:bitmap ->
f:font ->
str:string ->
x:int -> y:int -> color:color -> bg:color -> unit
val textout_centre_ex : bmp:bitmap ->
f:font ->
str:string ->
x:int -> y:int -> color:color -> bg:color -> unit
val textout_justify_ex : bmp:bitmap ->
f:font ->
str:string ->
x1:int ->
x2:int ->
y:int -> diff:int -> color:color -> bg:color -> unit
val textout_right_ex : bmp:bitmap ->
f:font ->
str:string ->
x:int -> y:int -> color:color -> bg:color -> unit
val textprintf_ex : bitmap ->
font ->
int ->
int ->
color -> color -> ('a, unit, string, unit) format4 -> 'a
val textprintf_centre_ex : bitmap ->
font ->
int ->
int ->
color -> color -> ('a, unit, string, unit) format4 -> 'a
val textprintf_justify_ex : bitmap ->
font ->
int ->
int ->
int ->
int ->
color -> color -> ('a, unit, string, unit) format4 -> 'a
val textprintf_right_ex : bitmap ->
font ->
int ->
int ->
color -> color -> ('a, unit, string, unit) format4 -> 'a

Fonts



Allegro API documentation for this module
val load_font : filename:string -> font * palette
val merge_fonts : f1:font -> f2:font -> font
val destroy_font : f:font -> unit

Transparency and Patterned Drawing



Allegro API documentation for this module

type draw_mode =
| DRAW_MODE_SOLID
| DRAW_MODE_XOR
| DRAW_MODE_COPY_PATTERN of bitmap * int * int
| DRAW_MODE_SOLID_PATTERN of bitmap * int * int
| DRAW_MODE_MASKED_PATTERN of bitmap * int * int
| DRAW_MODE_TRANS
val drawing_mode : draw_mode:draw_mode -> unit
val xor_mode : on:bool -> unit
val solid_mode : unit -> unit
val set_trans_blender : r:int -> g:int -> b:int -> a:int -> unit
val set_alpha_blender : unit -> unit
val set_write_alpha_blender : unit -> unit
val set_add_blender : r:int -> g:int -> b:int -> a:int -> unit
val set_burn_blender : r:int -> g:int -> b:int -> a:int -> unit
val set_color_blender : r:int -> g:int -> b:int -> a:int -> unit
val set_difference_blender : r:int -> g:int -> b:int -> a:int -> unit
val set_dissolve_blender : r:int -> g:int -> b:int -> a:int -> unit
val set_dodge_blender : r:int -> g:int -> b:int -> a:int -> unit
val set_hue_blender : r:int -> g:int -> b:int -> a:int -> unit
val set_invert_blender : r:int -> g:int -> b:int -> a:int -> unit
val set_luminance_blender : r:int -> g:int -> b:int -> a:int -> unit
val set_multiply_blender : r:int -> g:int -> b:int -> a:int -> unit
val set_saturation_blender : r:int -> g:int -> b:int -> a:int -> unit
val set_screen_blender : r:int -> g:int -> b:int -> a:int -> unit
val digi_driver_name : unit -> string

Sound Init Routines



Allegro API documentation for this module

type digi =
| DIGI_AUTODETECT
| DIGI_NONE

type midi =
| MIDI_AUTODETECT
| MIDI_NONE
val install_sound : digi -> midi -> unit
val remove_sound : unit -> unit
val reserve_voices : digi_voices:int -> midi_voices:int -> unit
val set_volume_per_voice : scale:int -> unit
val set_volume : digi_volume:int -> midi_volume:int -> unit
val set_hardware_volume : digi_volume:int -> midi_volume:int -> unit

Digital Sample Routines



Allegro API documentation for this module
type sample 
val load_sample : filename:string -> sample
val destroy_sample : spl:sample -> unit
val adjust_sample : spl:sample -> vol:int -> pan:int -> freq:int -> loop:bool -> unit
val play_sample : spl:sample -> vol:int -> pan:int -> freq:int -> loop:bool -> int
val stop_sample : spl:sample -> unit

File and Compression Routines



Allegro API documentation for this module
val replace_filename : path:string -> filename:string -> string

Datafile Routines



Allegro API documentation for this module
type datafile 
val load_datafile : filename:string -> datafile
val unload_datafile : dat:datafile -> unit
val fixup_datafile : dat:datafile -> unit
val palette_dat : dat:datafile -> idx:int -> palette
val bitmap_dat : dat:datafile -> idx:int -> bitmap
val font_dat : dat:datafile -> idx:int -> font
val sample_dat : dat:datafile -> idx:int -> sample
val item_dat : dat:datafile -> idx:int -> 'a

GUI Routines



Allegro API documentation for this module
val gfx_mode_select_ex : unit -> gfx_driver * int * int * int

Polygon Rendering



Allegro API documentation for this module

type polytype =
| POLYTYPE_ATEX
| POLYTYPE_ATEX_LIT
| POLYTYPE_ATEX_MASK
| POLYTYPE_ATEX_MASK_LIT
| POLYTYPE_ATEX_MASK_TRANS
| POLYTYPE_ATEX_TRANS
| POLYTYPE_FLAT
| POLYTYPE_GCOL
| POLYTYPE_GRGB
| POLYTYPE_PTEX
| POLYTYPE_PTEX_LIT
| POLYTYPE_PTEX_MASK
| POLYTYPE_PTEX_MASK_LIT
| POLYTYPE_PTEX_MASK_TRANS
| POLYTYPE_PTEX_TRANS

type 'a _v3d = {
   x : 'a;
   y : 'a;
   z : 'a; (*position*)
   u : 'a;
   v : 'a; (*texture map coordinates*)
   c : color; (*color*)
}
type v3d = fixed Allegro._v3d 
type v3d_f = float Allegro._v3d 
val triangle3d : bmp:bitmap ->
polytype:polytype ->
tex:bitmap ->
v1:v3d -> v2:v3d -> v3:v3d -> unit
val triangle3d_f : bmp:bitmap ->
polytype:polytype ->
tex:bitmap ->
v1:v3d_f -> v2:v3d_f -> v3:v3d_f -> unit
val quad3d : bmp:bitmap ->
polytype:polytype ->
tex:bitmap ->
v1:v3d -> v2:v3d -> v3:v3d -> v4:v3d -> unit
val quad3d_f : bmp:bitmap ->
polytype:polytype ->
tex:bitmap ->
v1:v3d_f ->
v2:v3d_f -> v3:v3d_f -> v4:v3d_f -> unit
val clear_scene : bmp:bitmap -> unit
val render_scene : unit -> unit
val create_scene : nedge:int -> npoly:int -> int
val destroy_scene : unit -> unit
type zbuffer 
val create_zbuffer : bmp:bitmap -> zbuffer
val create_sub_zbuffer : parent:zbuffer ->
x:int -> y:int -> width:int -> height:int -> zbuffer
val set_zbuffer : zbuffer:zbuffer -> unit
val clear_zbuffer : zbuffer:zbuffer -> z:float -> unit
val destroy_zbuffer : zbuffer:zbuffer -> unit

3D Math Routines



Allegro API documentation for this module
type matrix 
type matrix_f 
val get_identity_matrix : unit -> matrix
val get_identity_matrix_f : unit -> matrix_f
val free_matrix : matrix -> unit
val make_matrix : v:(float * float * float) * (float * float * float) * (float * float * float) ->
t:float * float * float -> matrix
val make_matrix_f : v:(float * float * float) * (float * float * float) * (float * float * float) ->
t:float * float * float -> matrix_f
use free_matrix when not used any more.
v : 3x3 scaling and rotation component
t : x/y/z translation component
val new_matrix : unit -> matrix
val new_matrix_f : unit -> matrix_f
new_matrix functions provide uninitialised matrices made to be set with the get_*_matrix functions. The choice have been made to not make the get_*_matrix functions return a fresh malloc'ed matrix, because these are mainly to be used in the display loop, so alloc the matrices with new_matrix before the loop, manipulate and use these in the loop, and finaly free it with free_matrix at the end of the display loop.
val get_translation_matrix : m:matrix ->
x:fixed -> y:fixed -> z:fixed -> unit
val get_translation_matrix_f : m:matrix -> x:float -> y:float -> z:float -> unit
val get_scaling_matrix : m:matrix ->
x:fixed -> y:fixed -> z:fixed -> unit
val get_scaling_matrix_f : m:matrix -> x:float -> y:float -> z:float -> unit
val get_x_rotate_matrix : m:matrix -> r:fixed -> unit
val get_x_rotate_matrix_f : m:matrix -> r:float -> unit
val get_y_rotate_matrix : m:matrix -> r:fixed -> unit
val get_y_rotate_matrix_f : m:matrix -> r:float -> unit
val get_z_rotate_matrix : m:matrix -> r:fixed -> unit
val get_z_rotate_matrix_f : m:matrix -> r:float -> unit
val get_rotation_matrix : m:matrix ->
x:fixed -> y:fixed -> z:fixed -> unit
val get_rotation_matrix_f : m:matrix -> x:float -> y:float -> z:float -> unit
val get_align_matrix : m:matrix ->
xfront:fixed ->
yfront:fixed ->
zfront:fixed ->
xup:fixed -> yup:fixed -> zup:fixed -> unit
val get_align_matrix_f : m:matrix_f ->
xfront:float ->
yfront:float -> zfront:float -> xup:float -> yup:float -> zup:float -> unit
val get_vector_rotation_matrix : m:matrix ->
x:fixed ->
y:fixed -> z:fixed -> a:fixed -> unit
val get_vector_rotation_matrix_f : m:matrix_f -> x:float -> y:float -> z:float -> a:float -> unit
val get_transformation_matrix : m:matrix ->
scale:fixed ->
xrot:fixed ->
yrot:fixed ->
zrot:fixed ->
x:fixed -> y:fixed -> z:fixed -> unit
val get_transformation_matrix_f : m:matrix_f ->
scale:float ->
xrot:float ->
yrot:float -> zrot:float -> x:float -> y:float -> z:float -> unit
val get_camera_matrix : m:matrix ->
x:fixed ->
y:fixed ->
z:fixed ->
xfront:fixed ->
yfront:fixed ->
zfront:fixed ->
xup:fixed ->
yup:fixed ->
zup:fixed -> fov:fixed -> aspect:fixed -> unit
val get_camera_matrix_f : m:matrix_f ->
x:float ->
y:float ->
z:float ->
xfront:float ->
yfront:float ->
zfront:float ->
xup:float -> yup:float -> zup:float -> fov:float -> aspect:float -> unit
val qtranslate_matrix : m:matrix ->
x:fixed -> y:fixed -> z:fixed -> unit
val qtranslate_matrix_f : m:matrix_f -> x:float -> y:float -> z:float -> unit
val qscale_matrix : m:matrix -> scale:fixed -> unit
val qscale_matrix_f : m:matrix_f -> scale:float -> unit
val matrix_mul : m1:matrix -> m2:matrix -> out:matrix -> unit
val matrix_mul_f : m1:matrix_f -> m2:matrix_f -> out:matrix_f -> unit
val vector_length : x:fixed -> y:fixed -> z:fixed -> fixed
val vector_length_f : x:float -> y:float -> z:float -> float
val apply_matrix : m:matrix ->
x:fixed ->
y:fixed ->
z:fixed -> fixed * fixed * fixed
val apply_matrix_f : m:matrix_f -> x:float -> y:float -> z:float -> float * float * float
val set_projection_viewport : x:int -> y:int -> w:int -> h:int -> unit
val persp_project : x:fixed ->
y:fixed -> z:fixed -> fixed * fixed
val persp_project_f : x:float -> y:float -> z:float -> float * float

Quaternion Math Routines



Allegro API documentation for this module
type quat 
val make_quat : w:float -> x:float -> y:float -> z:float -> quat
val free_quat : q:quat -> unit
val get_identity_quat : unit -> quat
use free_quat at the end as with make_quat
val get_x_rotate_quat : q:quat -> r:float -> unit
val get_y_rotate_quat : q:quat -> r:float -> unit
val get_z_rotate_quat : q:quat -> r:float -> unit
the rotation is applied on the quat parameter (thus modiling it)
val get_rotation_quat : q:quat -> x:float -> y:float -> z:float -> unit
val get_vector_rotation_quat : q:quat -> x:float -> y:float -> z:float -> a:float -> unit
val quat_to_matrix : q:quat -> matrix_f
val matrix_to_quat : m:matrix_f -> quat
val quat_mul : p:quat -> q:quat -> quat
val apply_quat : q:quat -> x:float -> y:float -> z:float -> float * float * float
val quat_interpolate : from:quat -> to_:quat -> t:float -> quat

type how_slerp =
| QUAT_SHORT
| QUAT_LONG
| QUAT_CW
| QUAT_CCW
| QUAT_USER
val quat_slerp : from:quat ->
to_:quat -> t:float -> how:how_slerp -> quat