module Graphics.UI.FLTK.LowLevel.Ask
  (
    flBeep,
    BeepType(..),
    flMessage,
    flAlert,
    flInput,
    flPassword
  )
where
import qualified Foreign.C.String as C2HSImp
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import C2HS hiding (cFromEnum, cToBool,cToEnum)
import Foreign.C.Types
data BeepType = BeepDefault
              | BeepMessage
              | BeepError
              | BeepQuestion
              | BeepPassword
              | BeepNotification
  deriving (Eq,Show,Ord)
instance Enum BeepType where
  succ BeepDefault = BeepMessage
  succ BeepMessage = BeepError
  succ BeepError = BeepQuestion
  succ BeepQuestion = BeepPassword
  succ BeepPassword = BeepNotification
  succ BeepNotification = error "BeepType.succ: BeepNotification has no successor"
  pred BeepMessage = BeepDefault
  pred BeepError = BeepMessage
  pred BeepQuestion = BeepError
  pred BeepPassword = BeepQuestion
  pred BeepNotification = BeepPassword
  pred BeepDefault = error "BeepType.pred: BeepDefault has no predecessor"
  enumFromTo from to = go from
    where
      end = fromEnum to
      go v = case compare (fromEnum v) end of
                 LT -> v : go (succ v)
                 EQ -> [v]
                 GT -> []
  enumFrom from = enumFromTo from BeepNotification
  fromEnum BeepDefault = 0
  fromEnum BeepMessage = 1
  fromEnum BeepError = 2
  fromEnum BeepQuestion = 3
  fromEnum BeepPassword = 4
  fromEnum BeepNotification = 5
  toEnum 0 = BeepDefault
  toEnum 1 = BeepMessage
  toEnum 2 = BeepError
  toEnum 3 = BeepQuestion
  toEnum 4 = BeepPassword
  toEnum 5 = BeepNotification
  toEnum unmatched = error ("BeepType.toEnum: Cannot match " ++ show unmatched)
flBeep' :: IO ()
flBeep' =
  flBeep''_ >>
  return ()
flBeepType' :: (CInt) -> IO ()
flBeepType' a1 =
  let {a1' = id a1} in 
  flBeepType''_ a1' >>
  return ()
flBeep :: Maybe BeepType -> IO ()
flBeep Nothing = flBeep'
flBeep (Just bt) = flBeepType' (fromIntegral (fromEnum bt))
flInput' :: (String) -> IO ()
flInput' a1 =
  C2HSImp.withCString a1 $ \a1' -> 
  flInput''_ a1' >>
  return ()
flInput :: String -> IO ()
flInput = flInput'
flPassword' :: (String) -> IO ()
flPassword' a1 =
  C2HSImp.withCString a1 $ \a1' -> 
  flPassword''_ a1' >>
  return ()
flPassword :: String -> IO ()
flPassword = flPassword'
flMessage' :: (String) -> IO ()
flMessage' a1 =
  C2HSImp.withCString a1 $ \a1' -> 
  flMessage''_ a1' >>
  return ()
flMessage :: String -> IO ()
flMessage = flMessage'
flAlert' :: (String) -> IO ()
flAlert' a1 =
  C2HSImp.withCString a1 $ \a1' -> 
  flAlert''_ a1' >>
  return ()
flAlert :: String -> IO ()
flAlert = flAlert'
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Ask.chs.h flc_beep"
  flBeep''_ :: (IO ())
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Ask.chs.h flc_beep_with_type"
  flBeepType''_ :: (C2HSImp.CInt -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Ask.chs.h flc_input"
  flInput''_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Ask.chs.h flc_password"
  flPassword''_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> (IO (C2HSImp.Ptr C2HSImp.CChar)))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Ask.chs.h flc_message"
  flMessage''_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ()))
foreign import ccall safe "Graphics/UI/FLTK/LowLevel/Ask.chs.h flc_alert"
  flAlert''_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> (IO ()))