-- GENERATED by C->Haskell Compiler, version 0.28.6 Switcheroo, 25 November 2017 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}
{-# LANGUAGE CPP, UndecidableInstances, ExistentialQuantification, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts, ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Graphics.UI.FLTK.LowLevel.TreePrefs
       (
         treePrefsNew
         -- * Hierarchy
         --
         -- $hierarchy

         -- * Functions
         --
         -- $functions
       )
where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp





import C2HS hiding (cFromEnum, cFromBool, cToBool,cToEnum)

import Graphics.UI.FLTK.LowLevel.Fl_Enumerations
import Graphics.UI.FLTK.LowLevel.Fl_Types
import Graphics.UI.FLTK.LowLevel.Utils
import Graphics.UI.FLTK.LowLevel.Dispatch
import Graphics.UI.FLTK.LowLevel.Hierarchy

treePrefsNew' :: IO ((Ptr ()))
treePrefsNew' =
  treePrefsNew''_ >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 26 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

treePrefsNew :: IO (Ref TreePrefs)
treePrefsNew = treePrefsNew' >>= toRef
itemLabelfont' :: (Ptr ()) -> IO ((Font))
itemLabelfont' a1 =
  let {a1' = id a1} in
  itemLabelfont''_ a1' >>= \res ->
  let {res' = cToFont res} in
  return (res')

{-# LINE 29 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Font))) => Op (GetItemLabelfont ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> itemLabelfont' tree_prefsPtr
setItemLabelfont' :: (Ptr ()) -> (Font) -> IO ()
setItemLabelfont' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromFont a2} in
  setItemLabelfont''_ a1' a2' >>
  return ()

{-# LINE 32 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Font ->  IO ())) => Op (SetItemLabelfont ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setItemLabelfont' tree_prefsPtr val
itemLabelsize' :: (Ptr ()) -> IO ((CInt))
itemLabelsize' a1 =
  let {a1' = id a1} in
  itemLabelsize''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 35 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (FontSize))) => Op (GetItemLabelsize ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> itemLabelsize' tree_prefsPtr >>= return . FontSize
setItemLabelsize' :: (Ptr ()) -> (CInt) -> IO ()
setItemLabelsize' a1 a2 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  setItemLabelsize''_ a1' a2' >>
  return ()

{-# LINE 38 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (FontSize ->  IO ())) => Op (SetItemLabelsize ()) TreePrefs orig impl where
  runOp _ _ tree_prefs (FontSize val) = withRef tree_prefs $ \tree_prefsPtr -> setItemLabelsize' tree_prefsPtr val
setItemLabelfgcolor' :: (Ptr ()) -> (Color) -> IO ()
setItemLabelfgcolor' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromColor a2} in
  setItemLabelfgcolor''_ a1' a2' >>
  return ()

{-# LINE 41 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Color ->  IO ())) => Op (SetItemLabelfgcolor ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setItemLabelfgcolor' tree_prefsPtr val
itemLabelbgcolor' :: (Ptr ()) -> IO ((Color))
itemLabelbgcolor' a1 =
  let {a1' = id a1} in
  itemLabelbgcolor''_ a1' >>= \res ->
  let {res' = cToColor res} in
  return (res')

{-# LINE 44 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Color))) => Op (GetItemLabelbgcolor ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> itemLabelbgcolor' tree_prefsPtr
setItemLabelbgcolor' :: (Ptr ()) -> (Color) -> IO ()
setItemLabelbgcolor' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromColor a2} in
  setItemLabelbgcolor''_ a1' a2' >>
  return ()

{-# LINE 47 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Color ->  IO ())) => Op (SetItemLabelbgcolor ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setItemLabelbgcolor' tree_prefsPtr val
labelfont' :: (Ptr ()) -> IO ((Font))
labelfont' a1 =
  let {a1' = id a1} in
  labelfont''_ a1' >>= \res ->
  let {res' = cToFont res} in
  return (res')

{-# LINE 50 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Font))) => Op (GetLabelfont ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> labelfont' tree_prefsPtr
setLabelfont' :: (Ptr ()) -> (Font) -> IO ()
setLabelfont' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromFont a2} in
  setLabelfont''_ a1' a2' >>
  return ()

{-# LINE 53 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Font ->  IO ())) => Op (SetLabelfont ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setLabelfont' tree_prefsPtr val
labelsize' :: (Ptr ()) -> IO ((CInt))
labelsize' a1 =
  let {a1' = id a1} in
  labelsize''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 56 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (FontSize))) => Op (GetLabelsize ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> labelsize' tree_prefsPtr >>= return . FontSize
setLabelsize' :: (Ptr ()) -> (CInt) -> IO ()
setLabelsize' a1 a2 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  setLabelsize''_ a1' a2' >>
  return ()

{-# LINE 59 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (FontSize ->  IO ())) => Op (SetLabelsize ()) TreePrefs orig impl where
  runOp _ _ tree_prefs (FontSize val) = withRef tree_prefs $ \tree_prefsPtr -> setLabelsize' tree_prefsPtr val
labelfgcolor' :: (Ptr ()) -> IO ((Color))
labelfgcolor' a1 =
  let {a1' = id a1} in
  labelfgcolor''_ a1' >>= \res ->
  let {res' = cToColor res} in
  return (res')

{-# LINE 62 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Color))) => Op (GetLabelfgcolor ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> labelfgcolor' tree_prefsPtr
setLabelfgcolor' :: (Ptr ()) -> (Color) -> IO ()
setLabelfgcolor' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromColor a2} in
  setLabelfgcolor''_ a1' a2' >>
  return ()

{-# LINE 65 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Color ->  IO ())) => Op (SetLabelfgcolor ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setLabelfgcolor' tree_prefsPtr val
labelbgcolor' :: (Ptr ()) -> IO ((Color))
labelbgcolor' a1 =
  let {a1' = id a1} in
  labelbgcolor''_ a1' >>= \res ->
  let {res' = cToColor res} in
  return (res')

{-# LINE 68 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Color))) => Op (GetLabelbgcolor ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> labelbgcolor' tree_prefsPtr
setLabelbgcolor' :: (Ptr ()) -> (Color) -> IO ()
setLabelbgcolor' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromColor a2} in
  setLabelbgcolor''_ a1' a2' >>
  return ()

{-# LINE 71 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Color ->  IO ())) => Op (SetLabelbgcolor ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setLabelbgcolor' tree_prefsPtr val
marginleft' :: (Ptr ()) -> IO ((Int))
marginleft' a1 =
  let {a1' = id a1} in
  marginleft''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 74 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Int))) => Op (GetMarginleft ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> marginleft' tree_prefsPtr
setMarginleft' :: (Ptr ()) -> (Int) -> IO ()
setMarginleft' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setMarginleft''_ a1' a2' >>
  return ()

{-# LINE 77 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Int ->  IO ())) => Op (SetMarginleft ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setMarginleft' tree_prefsPtr val
margintop' :: (Ptr ()) -> IO ((Int))
margintop' a1 =
  let {a1' = id a1} in
  margintop''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 80 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Int))) => Op (GetMargintop ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> margintop' tree_prefsPtr
setMargintop' :: (Ptr ()) -> (Int) -> IO ()
setMargintop' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setMargintop''_ a1' a2' >>
  return ()

{-# LINE 83 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Int ->  IO ())) => Op (SetMargintop ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setMargintop' tree_prefsPtr val
openchildMarginbottom' :: (Ptr ()) -> IO ((Int))
openchildMarginbottom' a1 =
  let {a1' = id a1} in
  openchildMarginbottom''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 86 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Int))) => Op (GetOpenchildMarginbottom ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> openchildMarginbottom' tree_prefsPtr
setOpenchildMarginbottom' :: (Ptr ()) -> (Int) -> IO ()
setOpenchildMarginbottom' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setOpenchildMarginbottom''_ a1' a2' >>
  return ()

{-# LINE 89 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Int ->  IO ())) => Op (SetOpenchildMarginbottom ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setOpenchildMarginbottom' tree_prefsPtr val
usericonmarginleft' :: (Ptr ()) -> IO ((Int))
usericonmarginleft' a1 =
  let {a1' = id a1} in
  usericonmarginleft''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 92 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Int))) => Op (GetUsericonmarginleft ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> usericonmarginleft' tree_prefsPtr
setUsericonmarginleft' :: (Ptr ()) -> (Int) -> IO ()
setUsericonmarginleft' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setUsericonmarginleft''_ a1' a2' >>
  return ()

{-# LINE 95 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Int ->  IO ())) => Op (SetUsericonmarginleft ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setUsericonmarginleft' tree_prefsPtr val
labelmarginleft' :: (Ptr ()) -> IO ((Int))
labelmarginleft' a1 =
  let {a1' = id a1} in
  labelmarginleft''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 98 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Int))) => Op (GetLabelmarginleft ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> labelmarginleft' tree_prefsPtr
setLabelmarginleft' :: (Ptr ()) -> (Int) -> IO ()
setLabelmarginleft' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setLabelmarginleft''_ a1' a2' >>
  return ()

{-# LINE 101 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Int ->  IO ())) => Op (SetLabelmarginleft ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setLabelmarginleft' tree_prefsPtr val
linespacing' :: (Ptr ()) -> IO ((Int))
linespacing' a1 =
  let {a1' = id a1} in
  linespacing''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 104 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Int))) => Op (GetLinespacing ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> linespacing' tree_prefsPtr
setLinespacing' :: (Ptr ()) -> (Int) -> IO ()
setLinespacing' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setLinespacing''_ a1' a2' >>
  return ()

{-# LINE 107 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Int ->  IO ())) => Op (SetLinespacing ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setLinespacing' tree_prefsPtr val
connectorcolor' :: (Ptr ()) -> IO ((Color))
connectorcolor' a1 =
  let {a1' = id a1} in
  connectorcolor''_ a1' >>= \res ->
  let {res' = cToColor res} in
  return (res')

{-# LINE 110 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Color))) => Op (GetConnectorcolor ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> connectorcolor' tree_prefsPtr
setConnectorcolor' :: (Ptr ()) -> (Color) -> IO ()
setConnectorcolor' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromColor a2} in
  setConnectorcolor''_ a1' a2' >>
  return ()

{-# LINE 113 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Color ->  IO ())) => Op (SetConnectorcolor ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setConnectorcolor' tree_prefsPtr val
connectorstyle' :: (Ptr ()) -> IO ((TreeConnector))
connectorstyle' a1 =
  let {a1' = id a1} in
  connectorstyle''_ a1' >>= \res ->
  let {res' = cToEnum res} in
  return (res')

{-# LINE 116 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (TreeConnector))) => Op (GetConnectorstyle ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> connectorstyle' tree_prefsPtr
setConnectorstyle' :: (Ptr ()) -> (TreeConnector) -> IO ()
setConnectorstyle' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromEnum a2} in
  setConnectorstyle''_ a1' a2' >>
  return ()

{-# LINE 119 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (TreeConnector -> IO ())) => Op (SetConnectorstyle ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setConnectorstyle' tree_prefsPtr val
connectorwidth' :: (Ptr ()) -> IO ((Int))
connectorwidth' a1 =
  let {a1' = id a1} in
  connectorwidth''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 122 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Int))) => Op (GetConnectorwidth ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> connectorwidth' tree_prefsPtr
setConnectorwidth' :: (Ptr ()) -> (Int) -> IO ()
setConnectorwidth' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setConnectorwidth''_ a1' a2' >>
  return ()

{-# LINE 125 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Int ->  IO ())) => Op (SetConnectorwidth ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setConnectorwidth' tree_prefsPtr val
openicon' :: (Ptr ()) -> IO ((Ptr ()))
openicon' a1 =
  let {a1' = id a1} in
  openicon''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 128 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Maybe (Ref Image)))) => Op (GetOpenicon ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> openicon' tree_prefsPtr >>= toMaybeRef
setOpenicon' :: (Ptr ()) -> (Ptr ()) -> IO ()
setOpenicon' a1 a2 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  setOpenicon''_ a1' a2' >>
  return ()

{-# LINE 131 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (Parent a Image, impl ~ (Maybe ( Ref a )  ->  IO ())) => Op (SetOpenicon ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> withMaybeRef val $ \valPtr -> setOpenicon' tree_prefsPtr valPtr
closeicon' :: (Ptr ()) -> IO ((Ptr ()))
closeicon' a1 =
  let {a1' = id a1} in
  closeicon''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 134 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Maybe (Ref Image)))) => Op (GetCloseicon ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> closeicon' tree_prefsPtr >>= toMaybeRef
setCloseicon' :: (Ptr ()) -> (Ptr ()) -> IO ()
setCloseicon' a1 a2 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  setCloseicon''_ a1' a2' >>
  return ()

{-# LINE 137 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (Parent a Image, impl ~ (Maybe ( Ref a )  ->  IO ())) => Op (SetCloseicon ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> withMaybeRef val $ \valPtr -> setCloseicon' tree_prefsPtr valPtr
usericon' :: (Ptr ()) -> IO ((Ptr ()))
usericon' a1 =
  let {a1' = id a1} in
  usericon''_ a1' >>= \res ->
  let {res' = id res} in
  return (res')

{-# LINE 140 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Maybe (Ref Image)))) => Op (GetUsericon ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> usericon' tree_prefsPtr >>= toMaybeRef
setUsericon' :: (Ptr ()) -> (Ptr ()) -> IO ()
setUsericon' a1 a2 =
  let {a1' = id a1} in
  let {a2' = id a2} in
  setUsericon''_ a1' a2' >>
  return ()

{-# LINE 143 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (Parent a Image, impl ~ (Maybe ( Ref a )  ->  IO ())) => Op (SetUsericon ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> withMaybeRef val $ \valPtr -> setUsericon' tree_prefsPtr valPtr
showcollapse' :: (Ptr ()) -> IO ((Bool))
showcollapse' a1 =
  let {a1' = id a1} in
  showcollapse''_ a1' >>= \res ->
  let {res' = cToBool res} in
  return (res')

{-# LINE 146 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Bool))) => Op (GetShowcollapse ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> showcollapse' tree_prefsPtr
setShowcollapse' :: (Ptr ()) -> (Bool) -> IO ()
setShowcollapse' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromBool a2} in
  setShowcollapse''_ a1' a2' >>
  return ()

{-# LINE 149 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Bool ->  IO ())) => Op (SetShowcollapse ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setShowcollapse' tree_prefsPtr val
sortorder' :: (Ptr ()) -> IO ((TreeSort))
sortorder' a1 =
  let {a1' = id a1} in
  sortorder''_ a1' >>= \res ->
  let {res' = cToEnum res} in
  return (res')

{-# LINE 152 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (TreeSort))) => Op (GetSortorder ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> sortorder' tree_prefsPtr
setSortorder' :: (Ptr ()) -> (TreeSort) -> IO ()
setSortorder' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromEnum a2} in
  setSortorder''_ a1' a2' >>
  return ()

{-# LINE 155 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (TreeSort ->  IO ())) => Op (SetSortorder ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setSortorder' tree_prefsPtr val
selectbox' :: (Ptr ()) -> IO ((Boxtype))
selectbox' a1 =
  let {a1' = id a1} in
  selectbox''_ a1' >>= \res ->
  let {res' = cToEnum res} in
  return (res')

{-# LINE 158 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Boxtype))) => Op (GetSelectbox ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> selectbox' tree_prefsPtr
setSelectbox' :: (Ptr ()) -> (Boxtype) -> IO ()
setSelectbox' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromEnum a2} in
  setSelectbox''_ a1' a2' >>
  return ()

{-# LINE 161 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Boxtype ->  IO ())) => Op (SetSelectbox ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setSelectbox' tree_prefsPtr val
showroot' :: (Ptr ()) -> IO ((Bool))
showroot' a1 =
  let {a1' = id a1} in
  showroot''_ a1' >>= \res ->
  let {res' = cToBool res} in
  return (res')

{-# LINE 164 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (Bool))) => Op (GetShowroot ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> showroot' tree_prefsPtr
setShowroot' :: (Ptr ()) -> (Bool) -> IO ()
setShowroot' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromBool a2} in
  setShowroot''_ a1' a2' >>
  return ()

{-# LINE 167 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Bool ->  IO ())) => Op (SetShowroot ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setShowroot' tree_prefsPtr val
selectmode' :: (Ptr ()) -> IO ((TreeSelect))
selectmode' a1 =
  let {a1' = id a1} in
  selectmode''_ a1' >>= \res ->
  let {res' = cToEnum res} in
  return (res')

{-# LINE 170 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (IO (TreeSelect))) => Op (GetSelectmode ()) TreePrefs orig impl where
  runOp _ _ tree_prefs = withRef tree_prefs $ \tree_prefsPtr -> selectmode' tree_prefsPtr
setSelectmode' :: (Ptr ()) -> (TreeSelect) -> IO ()
setSelectmode' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromEnum a2} in
  setSelectmode''_ a1' a2' >>
  return ()

{-# LINE 173 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (TreeSelect ->  IO ())) => Op (SetSelectmode ()) TreePrefs orig impl where
  runOp _ _ tree_prefs val = withRef tree_prefs $ \tree_prefsPtr -> setSelectmode' tree_prefsPtr val
marginbottom' :: (Ptr ()) -> IO ((Int))
marginbottom' a1 =
  let {a1' = id a1} in
  marginbottom''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 176 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ ( IO (Int)) ) => Op (GetMarginbottom ()) TreePrefs orig impl where
  runOp _ _ tree = withRef tree $ \treePtr -> marginbottom' treePtr
setMarginbottom' :: (Ptr ()) -> (Int) -> IO ()
setMarginbottom' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setMarginbottom''_ a1' a2' >>
  return ()

{-# LINE 179 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Int ->  IO ()) ) => Op (SetMarginbottom ()) TreePrefs orig impl where
  runOp _ _ tree val = withRef tree $ \treePtr -> setMarginbottom' treePtr val
widgetmarginleft' :: (Ptr ()) -> IO ((Int))
widgetmarginleft' a1 =
  let {a1' = id a1} in
  widgetmarginleft''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 182 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ ( IO (Int)) ) => Op (GetWidgetmarginleft ()) TreePrefs orig impl where
  runOp _ _ tree = withRef tree $ \treePtr -> widgetmarginleft' treePtr
setWidgetmarginleft' :: (Ptr ()) -> (Int) -> IO ()
setWidgetmarginleft' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setWidgetmarginleft''_ a1' a2' >>
  return ()

{-# LINE 185 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (Int ->  IO ()) ) => Op (SetWidgetmarginleft ()) TreePrefs orig impl where
  runOp _ _ tree val = withRef tree $ \treePtr -> setWidgetmarginleft' treePtr val
item_reselect_mode' :: (Ptr ()) -> IO ((TreeItemReselectMode))
item_reselect_mode' a1 =
  let {a1' = id a1} in
  item_reselect_mode''_ a1' >>= \res ->
  let {res' = cToEnum res} in
  return (res')

{-# LINE 188 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ ( IO (TreeItemReselectMode)) ) => Op (GetItemReselectMode ()) TreePrefs orig impl where
  runOp _ _ tree = withRef tree $ \treePtr -> item_reselect_mode' treePtr
setItem_Reselect_Mode' :: (Ptr ()) -> (TreeItemReselectMode) -> IO ()
setItem_Reselect_Mode' a1 a2 =
  let {a1' = id a1} in
  let {a2' = cFromEnum a2} in
  setItem_Reselect_Mode''_ a1' a2' >>
  return ()

{-# LINE 191 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ (TreeItemReselectMode ->  IO ()) ) => Op (SetItemReselectMode ()) TreePrefs orig impl where
  runOp _ _ tree val = withRef tree $ \treePtr -> setItem_Reselect_Mode' treePtr val
item_draw_mode' :: (Ptr ()) -> IO ((CInt))
item_draw_mode' a1 =
  let {a1' = id a1} in
  item_draw_mode''_ a1' >>= \res ->
  let {res' = fromIntegral res} in
  return (res')

{-# LINE 194 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ ( IO ([TreeItemDrawMode])) ) => Op (GetItemDrawMode ()) TreePrefs orig impl where
  runOp _ _ tree = withRef tree $ \treePtr -> item_draw_mode' treePtr >>= return . extract allTreeItemDrawModes
setItem_Draw_Mode' :: (Ptr ()) -> (CInt) -> IO ()
setItem_Draw_Mode' a1 a2 =
  let {a1' = id a1} in
  let {a2' = fromIntegral a2} in
  setItem_Draw_Mode''_ a1' a2' >>
  return ()

{-# LINE 197 "src/Graphics/UI/FLTK/LowLevel/TreePrefs.chs" #-}

instance (impl ~ ([TreeItemDrawMode] ->  IO ()) ) => Op (SetItemDrawMode ()) TreePrefs orig impl where
  runOp _ _ tree val = withRef tree $ \treePtr -> setItem_Draw_Mode' treePtr (fromIntegral (combine val))

-- $functions
-- @
-- getCloseicon :: 'Ref' 'TreePrefs' -> 'IO' ('Maybe' ('Ref' 'Image'))
--
-- getConnectorcolor :: 'Ref' 'TreePrefs' -> 'IO' ('Color')
--
-- getConnectorstyle :: 'Ref' 'TreePrefs' -> 'IO' ('TreeConnector')
--
-- getConnectorwidth :: 'Ref' 'TreePrefs' -> 'IO' ('Int')
--
-- getItemDrawMode :: 'Ref' 'TreePrefs' -> 'IO' (['TreeItemDrawMode')]
--
-- getItemLabelbgcolor :: 'Ref' 'TreePrefs' -> 'IO' ('Color')
--
-- getItemLabelfont :: 'Ref' 'TreePrefs' -> 'IO' ('Font')
--
-- getItemLabelsize :: 'Ref' 'TreePrefs' -> 'IO' ('FontSize')
--
-- getItemReselectMode :: 'Ref' 'TreePrefs' -> 'IO' ('TreeItemReselectMode')
--
-- getLabelbgcolor :: 'Ref' 'TreePrefs' -> 'IO' ('Color')
--
-- getLabelfgcolor :: 'Ref' 'TreePrefs' -> 'IO' ('Color')
--
-- getLabelfont :: 'Ref' 'TreePrefs' -> 'IO' ('Font')
--
-- getLabelmarginleft :: 'Ref' 'TreePrefs' -> 'IO' ('Int')
--
-- getLabelsize :: 'Ref' 'TreePrefs' -> 'IO' ('FontSize')
--
-- getLinespacing :: 'Ref' 'TreePrefs' -> 'IO' ('Int')
--
-- getMarginbottom :: 'Ref' 'TreePrefs' -> 'IO' ('Int')
--
-- getMarginleft :: 'Ref' 'TreePrefs' -> 'IO' ('Int')
--
-- getMargintop :: 'Ref' 'TreePrefs' -> 'IO' ('Int')
--
-- getOpenchildMarginbottom :: 'Ref' 'TreePrefs' -> 'IO' ('Int')
--
-- getOpenicon :: 'Ref' 'TreePrefs' -> 'IO' ('Maybe' ('Ref' 'Image'))
--
-- getSelectbox :: 'Ref' 'TreePrefs' -> 'IO' ('Boxtype')
--
-- getSelectmode :: 'Ref' 'TreePrefs' -> 'IO' ('TreeSelect')
--
-- getShowcollapse :: 'Ref' 'TreePrefs' -> 'IO' ('Bool')
--
-- getShowroot :: 'Ref' 'TreePrefs' -> 'IO' ('Bool')
--
-- getSortorder :: 'Ref' 'TreePrefs' -> 'IO' ('TreeSort')
--
-- getUsericon :: 'Ref' 'TreePrefs' -> 'IO' ('Maybe' ('Ref' 'Image'))
--
-- getUsericonmarginleft :: 'Ref' 'TreePrefs' -> 'IO' ('Int')
--
-- getWidgetmarginleft :: 'Ref' 'TreePrefs' -> 'IO' ('Int')
--
-- setCloseicon:: ('Parent' a 'Image') => 'Ref' 'TreePrefs' -> 'Maybe' ( 'Ref' a ) -> 'IO' ()
--
-- setConnectorcolor :: 'Ref' 'TreePrefs' -> 'Color' -> 'IO' ()
--
-- setConnectorstyle :: 'Ref' 'TreePrefs' -> 'TreeConnector' -> 'IO' ()
--
-- setConnectorwidth :: 'Ref' 'TreePrefs' -> 'Int' -> 'IO' ()
--
-- setItemDrawMode :: 'Ref' 'TreePrefs' -> ['TreeItemDrawMode'] -> 'IO' ()
--
-- setItemLabelbgcolor :: 'Ref' 'TreePrefs' -> 'Color' -> 'IO' ()
--
-- setItemLabelfgcolor :: 'Ref' 'TreePrefs' -> 'Color' -> 'IO' ()
--
-- setItemLabelfont :: 'Ref' 'TreePrefs' -> 'Font' -> 'IO' ()
--
-- setItemLabelsize :: 'Ref' 'TreePrefs' -> 'FontSize' -> 'IO' ()
--
-- setItemReselectMode :: 'Ref' 'TreePrefs' -> 'TreeItemReselectMode' -> 'IO' ()
--
-- setLabelbgcolor :: 'Ref' 'TreePrefs' -> 'Color' -> 'IO' ()
--
-- setLabelfgcolor :: 'Ref' 'TreePrefs' -> 'Color' -> 'IO' ()
--
-- setLabelfont :: 'Ref' 'TreePrefs' -> 'Font' -> 'IO' ()
--
-- setLabelmarginleft :: 'Ref' 'TreePrefs' -> 'Int' -> 'IO' ()
--
-- setLabelsize :: 'Ref' 'TreePrefs' -> 'FontSize' -> 'IO' ()
--
-- setLinespacing :: 'Ref' 'TreePrefs' -> 'Int' -> 'IO' ()
--
-- setMarginbottom :: 'Ref' 'TreePrefs' -> 'Int' -> 'IO' ()
--
-- setMarginleft :: 'Ref' 'TreePrefs' -> 'Int' -> 'IO' ()
--
-- setMargintop :: 'Ref' 'TreePrefs' -> 'Int' -> 'IO' ()
--
-- setOpenchildMarginbottom :: 'Ref' 'TreePrefs' -> 'Int' -> 'IO' ()
--
-- setOpenicon:: ('Parent' a 'Image') => 'Ref' 'TreePrefs' -> 'Maybe' ( 'Ref' a ) -> 'IO' ()
--
-- setSelectbox :: 'Ref' 'TreePrefs' -> 'Boxtype' -> 'IO' ()
--
-- setSelectmode :: 'Ref' 'TreePrefs' -> 'TreeSelect' -> 'IO' ()
--
-- setShowcollapse :: 'Ref' 'TreePrefs' -> 'Bool' -> 'IO' ()
--
-- setShowroot :: 'Ref' 'TreePrefs' -> 'Bool' -> 'IO' ()
--
-- setSortorder :: 'Ref' 'TreePrefs' -> 'TreeSort' -> 'IO' ()
--
-- setUsericon:: ('Parent' a 'Image') => 'Ref' 'TreePrefs' -> 'Maybe' ( 'Ref' a ) -> 'IO' ()
--
-- setUsericonmarginleft :: 'Ref' 'TreePrefs' -> 'Int' -> 'IO' ()
--
-- setWidgetmarginleft :: 'Ref' 'TreePrefs' -> 'Int' -> 'IO' ()
-- @

-- $hierarchy
-- @
-- "Graphics.UI.FLTK.LowLevel.TreePrefs"
-- @

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_New"
  treePrefsNew''_ :: (IO (C2HSImp.Ptr ()))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_item_labelfont"
  itemLabelfont''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_item_labelfont"
  setItemLabelfont''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_item_labelsize"
  itemLabelsize''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_item_labelsize"
  setItemLabelsize''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_item_labelfgcolor"
  setItemLabelfgcolor''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_item_labelbgcolor"
  itemLabelbgcolor''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_item_labelbgcolor"
  setItemLabelbgcolor''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_labelfont"
  labelfont''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_labelfont"
  setLabelfont''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_labelsize"
  labelsize''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_labelsize"
  setLabelsize''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_labelfgcolor"
  labelfgcolor''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_labelfgcolor"
  setLabelfgcolor''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_labelbgcolor"
  labelbgcolor''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_labelbgcolor"
  setLabelbgcolor''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_marginleft"
  marginleft''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_marginleft"
  setMarginleft''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_margintop"
  margintop''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_margintop"
  setMargintop''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_openchild_marginbottom"
  openchildMarginbottom''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_openchild_marginbottom"
  setOpenchildMarginbottom''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_usericonmarginleft"
  usericonmarginleft''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_usericonmarginleft"
  setUsericonmarginleft''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_labelmarginleft"
  labelmarginleft''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_labelmarginleft"
  setLabelmarginleft''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_linespacing"
  linespacing''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_linespacing"
  setLinespacing''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_connectorcolor"
  connectorcolor''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CUInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_connectorcolor"
  setConnectorcolor''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CUInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_connectorstyle"
  connectorstyle''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_connectorstyle_with_tree_connector"
  setConnectorstyle''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_connectorwidth"
  connectorwidth''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_connectorwidth"
  setConnectorwidth''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_openicon"
  openicon''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_openicon"
  setOpenicon''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_closeicon"
  closeicon''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_closeicon"
  setCloseicon''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_usericon"
  usericon''_ :: ((C2HSImp.Ptr ()) -> (IO (C2HSImp.Ptr ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_usericon"
  setUsericon''_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr ()) -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_showcollapse"
  showcollapse''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CChar))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_showcollapse"
  setShowcollapse''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_sortorder"
  sortorder''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_sortorder"
  setSortorder''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_selectbox"
  selectbox''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_selectbox"
  setSelectbox''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_showroot"
  showroot''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_showroot"
  setShowroot''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_selectmode"
  selectmode''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_selectmode"
  setSelectmode''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_marginbottom"
  marginbottom''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_marginbottom"
  setMarginbottom''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_widgetmarginleft"
  widgetmarginleft''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_widgetmarginleft"
  setWidgetmarginleft''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_item_reselect_mode"
  item_reselect_mode''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_item_reselect_mode"
  setItem_Reselect_Mode''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_item_draw_mode"
  item_draw_mode''_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Graphics/UI/FLTK/LowLevel/TreePrefs.chs.h Fl_Tree_Prefs_set_item_draw_mode"
  setItem_Draw_Mode''_ :: ((C2HSImp.Ptr ()) -> (C2HSImp.CInt -> (IO ())))