module Prelude.OldIO ( -- * IO Requests and responses IORequest(..), IOResponse(..), run, -- * Other convenient operators (.), trace, ) where import qualified Prelude as P import qualified Data.Char import Prelude (fmap, map, (>>), (>>=), return, putStrLn, getLine, readFile, ($), print, (.), mapM, (||), (&&), not, Bool(..)) import Debug.Trace (trace) import System.IO.Unsafe (unsafePerformIO) import Control.DeepSeq (deepseq, NFData) import System.Exit (exitSuccess) import Data.List ((++), head, last, tail, init, null, length, map, reverse, intersperse, intercalate, foldl, foldl1, foldr, foldr1, concat, concatMap, and, or, any, all, iterate, repeat, replicate, cycle, take, drop, splitAt, takeWhile, dropWhile) -- IO requests and responses data IORequest = Print String | PrintChar Char | GetLine | ReadFile P.FilePath | WriteToFile P.FilePath String | Exit instance NFData IOResponse data IOResponse = Success | FileContents String | ConsoleLine String run :: ([IOResponse] -> [IORequest]) -> IO () run main = deepseq responses $ return () where requests = main responses responses = map (unsafePerformIO . processRequest) requests processRequest Exit = exitSuccess >> return Success processRequest (Print str) = putStrLn str >> return Success processRequest GetLine = fmap ConsoleLine getLine processRequest (ReadFile filename) = P.fmap FileContents (readFile filename) -- Week 0 prelude type Int = P.Int type Double = P.Double type IO = P.IO type Char = P.Char type String = [P.Char] -- Integer arithmetic (+) :: Int -> Int -> Int (+) = (P.+) (-) :: Int -> Int -> Int (-) = (P.-) (*) :: Int -> Int -> Int (*) = (P.*) mod :: Int -> Int -> Int mod = P.mod -- Floating point arithmetic (+.) :: Double -> Double -> Double (+.) = (P.+) (-.) :: Double -> Double -> Double (-.) = (P.-) (*.) :: Double -> Double -> Double (*.) = (P.*) (/.) :: Double -> Double -> Double (/.) = (P./) -- String operations (<>) :: String -> String -> String (<>) = (P.++) -- Conversion functions doubleToString :: Double -> String doubleToString = P.show intToString :: Int -> String intToString = P.show charToString :: Char -> String charToString = P.show intToDouble :: Int -> Double intToDouble = P.fromIntegral intToChar :: Int -> Char intToChar = Data.Char.chr charToInt :: Char -> Int charToInt = Data.Char.ord -- Comparison (==) :: Int -> Int -> Bool (==) = (P.==) (==.) :: Double -> Double -> Bool (==.) = (P.==) (<=) :: Int -> Int -> Bool (<=) = (P.<=) (<=.) :: Double -> Double -> Bool (<=.) = (P.<=) (>=) :: Int -> Int -> Bool (>=) = (P.>=) (>=.) :: Double -> Double -> Bool (>=.) = (P.>=) (<) :: Int -> Int -> Bool (<) = (P.<) (<.) :: Double -> Double -> Bool (<.) = (P.<) (>) :: Int -> Int -> Bool (>) = (P.>) (>.) :: Double -> Double -> Bool (>.) = (P.>) (/=) :: Int -> Int -> Bool (/=) = (P./=) (/=.) :: Double -> Double -> Bool (/=.) = (P./=)