MonadicIO0

-- | This module provides type info for use by the Programatica front-end.
-- The functions are defined in the OH run-time system.
module MonadicIO0 where
foreign import ohc "(B->C->C->E)" primPutChar :: Char -> IO ()
foreign import ohc "(E->C->C->E)" primPutStr  :: String -> IO ()
foreign import ohc "(C->C->E)"    primGetChar :: IO Char
foreign import ohc "ECC" primGetContents      :: IO String
foreign import ohc "EECC" primReadFile        :: FilePath -> IO String
foreign import ohc "EECCC" primWriteFile      :: FilePath -> String -> IO ()
foreign import ohc "EECCC" primAppendFile     :: FilePath -> String -> IO ()
foreign import ohc "EE" primUnsafePerformIO   :: IO a -> a

foreign import ohc "EEECC" primRenameFile       :: FilePath -> FilePath -> IO ()
foreign import ohc "EECC"  primRemoveFile       :: FilePath -> IO ()
foreign import ohc "EECC"  primCreateDirectory  :: FilePath -> IO ()
foreign import ohc "EECC"  primRemoveDirectory  :: FilePath -> IO ()

foreign import ohc "EECC" primGetFileMode           :: FilePath -> IO Int
foreign import ohc "EEECC" primSetFileMode          :: FilePath -> Int -> IO ()
foreign import ohc "EECC" primGetModificationTime   :: FilePath -> IO (Int,Int)
foreign import ohc "EECC " primGetDirectoryContents :: FilePath -> IO [FilePath]

type Addr = Int
--type PrimHandle = Handle
newtype Handle = Handle Addr deriving (Eq,Show)

data Main

foreign import ohc "B" prim_stdin       :: Handle
foreign import ohc "B" prim_stdout      :: Handle
foreign import ohc "B" prim_stderr      :: Handle


foreign import ohc "EBBCC" primHPutChar    :: Handle -> Char   -> IO ()
foreign import ohc "EEECC" primHPutStr     :: Handle -> String -> IO ()
foreign import ohc "EECC" primHGetChar     :: Handle -> IO Char
foreign import ohc "EECC" primHGetContents :: Handle -> IO String

foreign import ohc "EECC" primHFlush    :: Handle -> IO ()

foreign import ohc "EEECC" primHSetBinaryMode :: Handle -> Bool -> IO ()

type PrimIOMode = Int
type PrimBufferMode = Int
foreign import ohc "EEECC" primOpenFile :: FilePath -> PrimIOMode -> IO Handle
foreign import ohc "EECC" primHClose    :: Handle -> IO ()
foreign import ohc "EEECC" primHSetBuffering:: Handle -> PrimBufferMode -> IO ()

foreign import ohc "(C->C->E)" primGetCurrentDirectory :: IO FilePath

type PrimExitCode = Int
foreign import ohc "(E->E->C->C->E)" primRawSystem :: FilePath -> [String] -> IO PrimExitCode

foreign import ohc "(E->C->E)" primGetEnvironment :: IO [String]
foreign import ohc "EECC" primGetEnv :: String -> IO String
foreign import ohc "(B->C->C->E)" primExit   :: PrimExitCode -> IO a

foreign import ohc "(B->C->C->E)" prim_usleep :: Int -> IO ()

foreign import ohc "ECC" primGetClockTime :: IO (Int,Int)
foreign import ohc "EECC"
 primToCalendarTime :: Int->IO (Int,Int,Int,Int,Int,Int,Int,Int,String,Int,Bool)
foreign import ohc "EE"
        primToUTCTime :: Int->(Int,Int,Int,Int,Int,Int,Int,Int,String,Int,Bool)

foreign import ohc "EEC" primClock :: IO Int
foreign import ohc "E" primClocksPerSec :: Int

type PrimPort = Int
type PrimSocket = Socket
newtype Socket = MkSocket Int deriving (Eq,Show)

foreign import ohc "EECC" primListenOnPort :: String -> IO PrimSocket
foreign import ohc "EECC" primAccept :: PrimSocket -> IO (Handle,String,PrimPort)
foreign import ohc "EEECC" primConnectTo :: String -> String -> IO Handle

--type PrimFd = Fd
newtype Fd = Fd Int deriving (Eq,Ord,Bounded,Enum,Show,Read)

foreign import ohc "(E->B->B->C->C->E)"
        primOpenFd :: String -> Int -> Int -> IO Fd
foreign import ohc "(B->C->C->E)" primCloseFd :: Fd -> IO ()

foreign import ohc "B" o_creat :: Int

foreign import ohc "(E->E->B->C->C->E)"
  primSelect :: [Fd] -> [Fd] -> Int -> IO ([Fd],[Fd])
  -- Note Fd, not Handle!!

foreign import ohc "(B->E->C->E)" primFileNo :: Handle -> IO Fd

foreign import ohc "(B->C->C->E)" primFileSizeFd :: Fd -> IO Int