large binaries

Jon Cast jcast@ou.edu
Tue, 23 Jul 2002 21:07:04 -0500


Malcolm Wallace <Malcolm.Wallace@cs.york.ac.uk> wrote:
> > > > Is there some reason haskell binaries have to be statically
> > > > linked?

> It would not be entirely fair to lay all the blame for large Haskell
> binaries entirely at the door of static vs. dynamic linking.

Well, considering that compiling the C binary statically linked
produces an even bigger executable:

$ gcc -static hello.c -o hello_c
$ ls -l hello_c hello_hs
-rwxrwxr-x    1 jcast    jcast      441624 Jul 23 20:56 hello_c
-rwxrwxr-x    1 jcast    jcast      157028 Jul 18 14:08 hello_hs

I think dynamic linking is fair game :)

> After all, the Haskell version is dynamically linked against exactly
> the same shared libraries as the C version, at least on my machine:

>     ldd Hello	(Hello.hs)
>    	libm.so.6 => /lib/libm.so.6 (0x40022000)
> 	libc.so.6 => /lib/libc.so.6 (0x40044000)
> 	/lib/ld-linux.so.2 => /lib/ld-linux.so.2 (0x40000000)

> Of course, it is static linking against the *Haskell* runtime
> system, Prelude and Libraries that is the cause of binary bloat.
> Quite simply, lots of extra stuff is dragged in that isn't visible
> in the apparently simple source program.  For instance, I can find
> all the following symbols in the binary for "hello world" (compiled
> with nhc98):

>     putStr, shows, showChar, showParen, showString, fromCString,
>     toCString, hGetFileName, hPutChar, hPutStr, error, flip, id, init,
>     length, not, putChar, putStrLn, seq, show, subtract, exitWith,
>     instance Bounded Int (maxBound, minBound), instance Enum Ordering
>     (succ, pred, toEnum, fromEnum, enumFrom, enumFromThen, enumFromTo,
>     enumFromThenTo), instance Enum ErrNo (succ, pred, toEnum,
>     fromEnum, enumFrom, enumFromThen, enumFromTo, enumFromThenTo),
>     instance Monad IO (>>=, >>, return, fail), instance Eq ErrNo (==,
>     /=), instance Eq Int (==, /=), instance Eq Ordering (==, /=),
>     instance Num Int (+, -, *, negate, abs, signum, fromInteger),
>     instance Ord Int (compare, <, <=, >=, >, max, min), instance Show
>     ErrNo (show, showsPrec, showList), instance Show IOError (show,
>     showsPrec, showList), instance Show Int (show, showsPrec, showList)

Well, look at the symbols I find in the statically linked C hello
world:

_Exit _GLOBAL_OFFSET_TABLE_ _IO_2_1_stderr_ _IO_2_1_stdin_
_IO_2_1_stdout_ _IO_adjust_column _IO_adjust_wcolumn _IO_cleanup
_IO_default_doallocate _IO_default_finish _IO_default_imbue
_IO_default_pbackfail _IO_default_read _IO_default_seek
_IO_default_seekoff _IO_default_seekpos _IO_default_setbuf
_IO_default_showmanyc _IO_default_stat _IO_default_sync
_IO_default_uflow _IO_default_underflow _IO_default_write
_IO_default_xsgetn _IO_default_xsputn _IO_do_write _IO_doallocbuf
_IO_fclose _IO_file_attach _IO_file_close _IO_file_close_it
_IO_file_doallocate _IO_file_finish _IO_file_fopen _IO_file_init
_IO_file_jumps _IO_file_open _IO_file_overflow _IO_file_read
_IO_file_seek _IO_file_seekoff _IO_file_setbuf _IO_file_stat
_IO_file_sync _IO_file_underflow _IO_file_write _IO_file_xsgetn
_IO_file_xsputn _IO_flockfile _IO_flush_all _IO_flush_all_linebuffered
_IO_flush_all_lockp _IO_fopen _IO_fprintf _IO_free_backup_area
_IO_free_wbackup_area _IO_ftrylockfile _IO_funlockfile _IO_fwide
_IO_getdelim _IO_getline _IO_getline_info _IO_helper_jumps
_IO_helper_overflow _IO_init _IO_init_marker _IO_init_wmarker
_IO_iter_begin _IO_iter_end _IO_iter_file _IO_iter_next
_IO_least_marker _IO_least_wmarker _IO_link_in _IO_list_all
_IO_list_all_stamp _IO_list_lock _IO_list_resetlock _IO_list_unlock
_IO_marker_delta _IO_marker_difference _IO_new_do_write _IO_new_fclose
_IO_new_file_attach _IO_new_file_close_it _IO_new_file_finish
_IO_new_file_fopen _IO_new_file_init _IO_new_file_overflow
_IO_new_file_seekoff _IO_new_file_setbuf _IO_new_file_sync
_IO_new_file_underflow _IO_new_file_write _IO_new_file_xsputn
_IO_new_fopen _IO_no_init _IO_padn _IO_printf _IO_remove_marker
_IO_seekmark _IO_seekoff _IO_seekwmark _IO_setb _IO_sgetn
_IO_sputbackc _IO_sputbackwc _IO_sscanf _IO_stderr _IO_stdfile_0_lock
_IO_stdfile_1_lock _IO_stdfile_2_lock _IO_stdin _IO_stdin_used
_IO_stdout _IO_str_count _IO_str_finish _IO_str_init_readonly
_IO_str_init_static _IO_str_jumps _IO_str_overflow _IO_str_pbackfail
_IO_str_seekoff _IO_str_underflow _IO_sungetc _IO_sungetwc
_IO_switch_to_backup_area _IO_switch_to_get_mode
_IO_switch_to_main_get_area _IO_switch_to_main_wget_area
_IO_switch_to_wbackup_area _IO_switch_to_wget_mode _IO_un_link
_IO_unsave_markers _IO_unsave_wmarkers _IO_vfprintf _IO_vfscanf
_IO_vsscanf _IO_wdefault_doallocate _IO_wdefault_finish
_IO_wdefault_pbackfail _IO_wdefault_setbuf _IO_wdefault_uflow
_IO_wdefault_xsgetn _IO_wdefault_xsputn _IO_wdo_write _IO_wdoallocbuf
_IO_wfile_doallocate _IO_wfile_jumps _IO_wfile_overflow
_IO_wfile_seekoff _IO_wfile_setbuf _IO_wfile_sync _IO_wfile_underflow
_IO_wfile_xsputn _IO_wide_data_0 _IO_wide_data_1 _IO_wide_data_2
_IO_wmarker_delta _IO_wpadn _IO_wsetb __CTOR_END__ __CTOR_LIST__
__DTOR_END__ __DTOR_LIST__ __EH_FRAME_BEGIN__ __FRAME_BEGIN__
__FRAME_BEGIN__ __FRAME_BEGIN__ __FRAME_BEGIN__ __FRAME_BEGIN__
__FRAME_BEGIN__ __FRAME_BEGIN__ __FRAME_BEGIN__ __FRAME_END__
___brk_addr ___fxstat64 ___xstat64 __access __add_to_environ
__addmntent __after_morecore_hook __argz_add_sep __argz_count
__argz_create_sep __argz_stringify __atomic_writev_replacement __brk
__bss_start __calloc __cfree __clearenv __close __clz_tab __clz_tab
__ctype32_b __ctype32_tolower __ctype32_toupper __ctype32_wctrans
__ctype32_wctype __ctype32_width __ctype_b __ctype_tolower
__ctype_toupper __curbrk __cxa_atexit __data_start __daylight
__dcgettext __dcigettext __default_morecore __deregister_frame_info
__do_global_ctors_aux __do_global_dtors_aux __dso_handle
__elf_set___libc_atexit_element__cleanup__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_free_mem__
__elf_set___libc_subfreeres_element_freeres__ __endmntent __environ
__errno_location __evoke_link_warning_llseek __exit_funcs __fcloseall
__fcntl __flockfile __fpu_control __free __free_hook __fsetlocking
__ftrylockfile __funlockfile __fxstat64 __gconv __gconv_alias_compare
__gconv_alias_db __gconv_cache __gconv_close __gconv_close_transform
__gconv_compare_alias __gconv_compare_alias_cache __gconv_find_shlib
__gconv_find_transform __gconv_get_builtin_trans __gconv_get_path
__gconv_load_cache __gconv_lookup_cache __gconv_max_path_elem_len
__gconv_modules_db __gconv_open __gconv_path_elem __gconv_path_envvar
__gconv_read_conf __gconv_release_cache __gconv_release_shlib
__gconv_release_step __gconv_transform_ascii_internal
__gconv_transform_internal_ascii __gconv_transform_internal_ucs2
__gconv_transform_internal_ucs2reverse __gconv_transform_internal_ucs4
__gconv_transform_internal_ucs4le __gconv_transform_internal_utf8
__gconv_transform_ucs2_internal __gconv_transform_ucs2reverse_internal
__gconv_transform_ucs4_internal __gconv_transform_ucs4le_internal
__gconv_transform_utf8_internal __gconv_translit_find
__gconv_transliterate __get_avphys_pages __get_nprocs
__get_nprocs_conf __get_phys_pages __getclktck __getcwd __getdelim
__getdtablesize __getegid __geteuid __getgid __getmntent_r
__getpagesize __getpid __getrlimit __gettext_extract_plural
__gettext_free_exp __gettext_germanic_plural __gettexterror
__gettextlex __gettextparse __getuid __gmon_start__ __guess_grouping
__hasmntopt __have_no_fcntl64 __have_no_new_getrlimit __have_no_stat64
__init_misc __ioctl __isatty __isinf __isinfl __isnan __isnanl __kill
__libc_argc __libc_argv __libc_calloc __libc_check_standard_fds
__libc_close __libc_dlclose __libc_dlopen __libc_dlsym
__libc_enable_secure __libc_fatal __libc_fcntl __libc_free
__libc_init_first __libc_init_secure __libc_internal_tsd_get
__libc_internal_tsd_set __libc_longjmp __libc_lseek __libc_lseek64
__libc_mallinfo __libc_malloc __libc_malloc_initialized __libc_mallopt
__libc_memalign __libc_missing_32bit_uids __libc_multiple_libcs
__libc_open __libc_open64 __libc_pagesize __libc_pvalloc __libc_read
__libc_realloc __libc_setlocale_lock __libc_sigaction
__libc_siglongjmp __libc_stack_end __libc_start_main
__libc_tsd_DL_ERROR_data __libc_tsd_MALLOC_data __libc_valloc
__libc_write __libio_codecvt __libio_translit __llseek __localtime_r
__longjmp __lseek __lseek64 __mallinfo __malloc __malloc_check_init
__malloc_get_state __malloc_hook __malloc_initialize_hook
__malloc_set_state __malloc_stats __malloc_trim __malloc_usable_size
__mallopt __mbrlen __mbrtowc __mbsnrtowcs __memalign __memalign_hook
__memchr __mempcpy __mktime_internal __mmap __mon_yday __morecore
__mpn_add_n __mpn_addmul_1 __mpn_cmp __mpn_construct_double
__mpn_construct_float __mpn_construct_long_double __mpn_divrem
__mpn_extract_double __mpn_extract_long_double __mpn_impn_mul_n
__mpn_impn_mul_n_basecase __mpn_impn_sqr_n __mpn_impn_sqr_n_basecase
__mpn_lshift __mpn_mul __mpn_mul_1 __mpn_mul_n __mpn_rshift
__mpn_sub_n __mpn_submul_1 __mprotect __mremap __munmap __new_exitfn
__new_fclose __new_fopen __new_getrlimit __new_sys_errlist
__new_sys_nerr __offtime __open __open64 __overflow __posix_memalign
__printf_arginfo_table __printf_fp __printf_fphex
__printf_function_table __profil __profile_frequency __progname
__progname_full __pthread_atfork __pthread_initialize
__pthread_initialize_minimal __pthread_mutex_destroy
__pthread_mutex_init __pthread_mutex_lock __pthread_mutex_trylock
__pthread_mutex_unlock __pthread_mutexattr_destroy
__pthread_mutexattr_init __pthread_mutexattr_settype __pthread_once
__pthread_rwlock_rdlock __pthread_rwlock_unlock __pvalloc __rawmemchr
__read __readlink __realloc __realloc_hook __register_frame_info
__register_printf_function __restore __restore_rt __sbrk __setenv
__setfpucw __setitimer __setmntent __sigaction __sigprocmask
__start___libc_atexit __start___libc_subfreeres __stop___libc_atexit
__stop___libc_subfreeres __stpcpy __strcasecmp __strcasecmp_l
__strchrnul __strdup __strerror_r __strncasecmp __strndup __strnlen
__strsep __strsep_g __strtod_internal __strtof_internal
__strtol_internal __strtold_internal __strtoll_internal
__strtoul_internal __strtoull_internal __syscall_error
__syscall_error_1 __sysconf __tcgetattr __tdelete __tdestroy __tens
__tfind __timezone __tsearch __twalk __tz_convert __tzfile_compute
__tzfile_default __tzfile_read __tzname __tzname_cur_max __tzname_max
__tzset __tzstring __ubp_memchr __udivdi3 __uflow __umoddi3 __uname
__underflow __unsetenv __use_tzfile __valloc __vfscanf __vsscanf
__wcrtomb __wcslen __wcsmbs_clone_conv __wcsmbs_gconv_fcts
__wcsmbs_last_locale __wcsmbs_load_conv __wcsmbs_named_conv __wcsnlen
__wcsrtombs __wmemcpy __wmemmove __wmempcpy __woverflow __write
__writev __wuflow __wunderflow __xstat64 _cleanup _dl_all_dirs
_dl_argv _dl_aux_init _dl_bind_not _dl_build_local_scope
_dl_cache_libcmp _dl_cache_libcmp _dl_catch_error
_dl_check_all_versions _dl_check_map_versions _dl_clktck _dl_close
_dl_correct_cache_id _dl_debug_bindings _dl_debug_fd
_dl_debug_initialize _dl_debug_mask _dl_debug_printf
_dl_debug_printf_c _dl_debug_state _dl_debug_vdprintf _dl_do_lookup
_dl_do_lookup_versioned _dl_dprintf _dl_dst_count _dl_dst_substitute
_dl_dynamic_weak _dl_get_origin _dl_global_scope
_dl_global_scope_alloc _dl_hwcap _dl_important_hwcaps
_dl_inhibit_rpath _dl_init _dl_init_all_dirs _dl_init_paths
_dl_initfirst _dl_initial_searchlist _dl_lazy _dl_load_cache_lookup
_dl_load_lock _dl_loaded _dl_lookup_symbol _dl_lookup_symbol_skip
_dl_lookup_versioned_symbol _dl_lookup_versioned_symbol_skip
_dl_main_searchlist _dl_map_object _dl_map_object_deps
_dl_map_object_from_fd _dl_mcount _dl_mcount_wrapper
_dl_mcount_wrapper_check _dl_new_object _dl_nloaded
_dl_non_dynamic_init _dl_open _dl_origin_path _dl_osversion
_dl_out_of_memory _dl_pagesize _dl_platform _dl_platformlen
_dl_profile _dl_profile_map _dl_receive_error _dl_reloc_bad_type
_dl_relocate_object _dl_rtld_map _dl_runtime_profile
_dl_runtime_resolve _dl_setup_hash _dl_signal_cerror _dl_signal_error
_dl_start _dl_start_profile _dl_starting_up _dl_sysdep_read_whole_file
_dl_unload_cache _dl_verbose _dl_x86_cap_flags _dl_x86_platforms
_edata _end _environ _errno _exit _fini _flushlbf _fp_hw
_fpioconst_pow10 _i18n_number_rewrite _init _itoa _itoa_base_table
_itoa_lower_digits _itoa_upper_digits _itowa _itowa_lower_digits
_itowa_upper_digits _libc_intl_domainname _longjmp _longjmp_unwind
_new_sys_errlist _new_sys_nerr _nl_C _nl_C_LC_ADDRESS _nl_C_LC_COLLATE
_nl_C_LC_CTYPE _nl_C_LC_CTYPE_class _nl_C_LC_CTYPE_class32
_nl_C_LC_CTYPE_class_alnum _nl_C_LC_CTYPE_class_alpha
_nl_C_LC_CTYPE_class_blank _nl_C_LC_CTYPE_class_cntrl
_nl_C_LC_CTYPE_class_digit _nl_C_LC_CTYPE_class_graph
_nl_C_LC_CTYPE_class_lower _nl_C_LC_CTYPE_class_print
_nl_C_LC_CTYPE_class_punct _nl_C_LC_CTYPE_class_space
_nl_C_LC_CTYPE_class_upper _nl_C_LC_CTYPE_class_xdigit
_nl_C_LC_CTYPE_map_tolower _nl_C_LC_CTYPE_map_toupper
_nl_C_LC_CTYPE_tolower _nl_C_LC_CTYPE_toupper _nl_C_LC_CTYPE_width
_nl_C_LC_IDENTIFICATION _nl_C_LC_MEASUREMENT _nl_C_LC_MESSAGES
_nl_C_LC_MONETARY _nl_C_LC_NAME _nl_C_LC_NUMERIC _nl_C_LC_PAPER
_nl_C_LC_TELEPHONE _nl_C_LC_TIME _nl_C_codeset _nl_C_locobj _nl_C_name
_nl_POSIX_name _nl_category_name_sizes _nl_category_names
_nl_category_num_items _nl_category_postload _nl_current
_nl_current_LC_ADDRESS _nl_current_LC_COLLATE _nl_current_LC_CTYPE
_nl_current_LC_IDENTIFICATION _nl_current_LC_MEASUREMENT
_nl_current_LC_MESSAGES _nl_current_LC_MONETARY _nl_current_LC_NAME
_nl_current_LC_NUMERIC _nl_current_LC_PAPER _nl_current_LC_TELEPHONE
_nl_current_LC_TIME _nl_current_default_domain _nl_current_names
_nl_default_default_domain _nl_default_dirname _nl_domain_bindings
_nl_expand_alias _nl_explode_name _nl_find_domain _nl_find_language
_nl_find_locale _nl_find_msg _nl_free_domain_conv _nl_get_alt_digit
_nl_get_era_entry _nl_get_walt_digit _nl_init_domain_conv
_nl_init_era_entries _nl_load_domain _nl_load_locale
_nl_loaded_domains _nl_locale_file_list _nl_make_l10nflist
_nl_msg_cat_cntr _nl_normalize_codeset _nl_parse_alt_digit
_nl_postload_ctype _nl_postload_time _nl_remove_locale
_nl_select_era_entry _nl_state_lock _nl_unload_domain
_nl_unload_locale _nl_value_type_LC_ADDRESS _nl_value_type_LC_COLLATE
_nl_value_type_LC_CTYPE _nl_value_type_LC_IDENTIFICATION
_nl_value_type_LC_MEASUREMENT _nl_value_type_LC_MESSAGES
_nl_value_type_LC_MONETARY _nl_value_type_LC_NAME
_nl_value_type_LC_NUMERIC _nl_value_type_LC_PAPER
_nl_value_type_LC_TELEPHONE _nl_value_type_LC_TIME _nl_value_types
_pthread_cleanup_pop_restore _pthread_cleanup_push_defer _quicksort
_r_debug _setjmp _start _sys_errlist _sys_nerr _tens_in_limb
_tens_in_limb _tens_in_limb _tmbuf abort access add_dependency
add_derivation add_module add_name_to_object add_to_global addmntent
alias_compare aliasfile.1 alt_digits alt_digits_initialized arena_get2
arena_key arena_mem argz_add_sep argz_count argz_create_sep
argz_stringify blanks blanks brk bsearch buf.2 buffered_vfprintf
builtin_aliases builtin_modules cache cache_malloced cache_new
cache_size cachesize call_gmon_start calloc capstr category_to_name
cfree check_action chunk_align chunk_alloc chunk_free chunk_realloc
clearenv close codeset_idx.0 collseqmb collseqwc completed.1
compute_change compute_tzname_max curwd.0 data data_start daylight
dcgettext decompose_rpath default_gconv_path default_tzdir.0
derivation_compare detect_conflict disallow_malloc_check
dl_open_worker do_always_noconv do_dlclose do_dlopen do_dlsym
do_encoding do_in do_length do_max_length do_out do_release_all
do_release_shlib do_unshift dummy_bucket.3 empty_path_elem endmntent
env_path_list environ envlock era_initialized eras errno exit
expand_dynamic_string_token expected.1 expected_note.2
extend_alias_table fclose fcloseall fcntl fgets_unlocked
find_derivation find_module find_module_idx fini_dummy fixup flockfile
flush_cleanup fopen force_to_data force_to_data fprintf frame_dummy
fread_unlocked free free_atfork free_check free_derivation free_mem
free_mem free_mem free_mem free_mem free_mem free_mem free_mem
free_mem free_mem free_mem free_mem free_mem free_mem free_mem
free_modules_db free_starter freemem.1 freemem_size.2 freeres fromidx
fromlimit froms fseek ftrylockfile funlockfile gcc2_compiled.
gcc2_compiled.  gcc2_compiled.  gcc2_compiled.  gcc2_compiled.
gconv_conf_filename gconv_module_ext gen_steps get_avphys_pages
get_nprocs get_nprocs_conf get_phys_pages get_proc_path getcwd
getdelim getdtablesize getegid getenv geteuid getgid getmntent_r
getpagesize getpid getrlimit getuid group_number group_number gsignal
guess_category_value hack_digit.0 hashfraction hasmntopt heap_trim
increment_counter index init init_dummy init_dummy initial internal
internal_trans_names.0 ioctl is_initialized.0 isatty isinf isinfl
isnan isnanl jump_table.0 kcount kcountsize kill known_compare
known_derivations known_values last_environ leaps list_all_lock
list_lock llseek loaded locale_alias_path.0 localtime localtime_offset
localtime_r lock lock lock lock lock lock lock.0 lock.1
log_hashfraction longjmp lose lowpc lseek lseek64 main main_arena
main_trim mallinfo malloc malloc_atfork malloc_check malloc_get_state
malloc_hook_ini malloc_set_state malloc_starter malloc_stats
malloc_trim malloc_usable_size mallopt map map match_symbol
max_capstrlen max_dirnamelen max_mmapped_mem max_n_mmaps
max_sbrked_mem maxmap mbrlen mbrtowc mbsnrtowcs mem2chunk_check
memalign memalign_check memalign_hook_ini memchr memcpy memmove
mempcpy memset mktime mmap mmap_threshold mmapped_mem modcounter.0
mount_proc mprotect mremap msg.9 msort_with_tmp munmap n_mmaps
n_mmaps_max narcs narcsp nbits.0 nbits.0 nbits.0 ncapstr new_do_write
new_heap nmap not_available nsamples null num_eras num_leaps
num_transitions num_types oact.0 object.2 old_tz once open open64
open_path open_verify openaux otimer.1 p.0 pagesize.1 path_proc
pc_offset pc_scale phys_pages.0 phys_pages_info plone plural_eval
plural_lookup plvar posix_memalign print_search_path printf
printf_funcs printf_unknown profil profil_counter profile_fixup
program_invocation_name program_invocation_short_name ptmalloc_init
ptmalloc_init_all ptmalloc_lock_all ptmalloc_unlock_all pvalloc qsort
raise rawmemchr read read_alias_file read_conf_file readlink realloc
realloc_check realloc_hook_ini receiver register_printf_function
release_handle result.1 rindex root rtld_search_dirs rule_dstoff
rule_stdoff run_fp running samples save_arena save_for_backup
save_for_wbackup save_free_hook save_malloc_hook sbrk sbrk_base
search_tree setenv setitimer setlocale setmntent sigaction sigfillset
siglongjmp sigprocmask sscanf stage state state state state stderr
stdin stdout step0_jumps.1 step1_jumps.2 step2_jumps.3 step3a_jumps.4
step3b_jumps.5 step4_jumps.6 step4_jumps.7 stpcpy strcasecmp strchr
strchrnul strcmp strcpy strdup strerror_r string_space
string_space_act string_space_max strncasecmp strncmp strndup strnlen
strpbrk strrchr strsep strstr strtod strtof strtol strtold strtoll
strtoq strtoul strtoull strtouq sys_errlist sys_nerr sysconf
system_dirs system_dirs_len tcgetattr tdelete tdestroy
tdestroy_recurse textsize tfind timelocal timezone to_mb to_wc
top_check top_pad tos trans_compare transcmp transitions
translit_from_idx translit_from_tbl translit_to_idx translit_to_tbl
transmem_list trecurse trim_threshold tsearch twalk type_idxs types
tz_rules tzname tzset tzset_internal tzset_lock tzstring_list uname
undefined_msg unsecure_envvars.0 unsetenv using_malloc_checking valloc
vfprintf vfscanf vsscanf walt_digits walt_digits_initialized wcrtomb
wcschr wcslen wcsnlen wcsrtombs wmemcpy wmemmove wmempcpy write writev
yycheck yydefact yydefgoto yypact yypgoto yyr1 yyr2 yytable
yytranslate zeroes zeroes zone_names

The point is, /both/ libraries have a lot of code re-use.  Dynamic
linking puts that code re-use in some random .so in $foo/lib; static
linking puts it in your executable.  That's the major difference.
(The minor difference is that most Haskell implementations use libc
more than most C implementations use the Haskell standard libraries.)

> This is not the fault of any particular implementation - the
> ghc-built binary has a similar collection - rather it is dictated by
> the nature of the language and its standard libraries.  Because
> Prelude functions are small and re-usable, they do get used all over
> the place in the implementation of other parts of the Prelude, so
> you end up with a huge dependency graph hiding underneath the
> simplest of calls.

You mean like printf("Hello, world!\n")?

> In fact, most of the extra stuff in "Hello World" is there purely to
> handle all possible error conditions in the I/O monad.

You mean as opposed to C, where most of the extra stuff is there
purely to support number formatting?

> Several years ago, Colin Runciman and I did the experiment of
> removing all the nice error-handling stuff from the prelude (and
> eliminating a few classes too I think), to see just how small we
> could squash "Hello World".  The idea was to target embedded systems
> where memory is a scarce resource, and fancy error-reporting is
> pointless (a single red LED would do).  IIRC, we managed to achieve
> a size of 25kb, compiled with nhc98, which don't forget includes a
> bytecode interpreter in the runtime system.

> Regards,
>     Malcolm

To sum up: code re-use within a library certainly happens in more
languages than just Haskell :) So don't blame code re-use for
Haskell-specific (or non-specific) problems, because code re-use is
not a Haskell-specific cause.

Jon Cast