Skip to content

Commit

Permalink
basic I/O imported by default
Browse files Browse the repository at this point in the history
  • Loading branch information
Ingo60 committed Feb 19, 2013
1 parent 2c21740 commit 5bc9f29
Show file tree
Hide file tree
Showing 8 changed files with 54 additions and 22 deletions.
15 changes: 7 additions & 8 deletions examples/Grep.fr
@@ -1,12 +1,11 @@
--- A simple grep
module examples.Grep where

import Java.IO(stdout, stderr, stdin, utf8Reader, BufferedReader)

--- exception thrown when an invalid regular expression is compiled
data PatternSyntax = native java.util.regex.PatternSyntaxException
derive Exceptional PatternSyntax

main [] = stderr.println "Usage: java example.Grep regex [files ...]"
main [] = stderr.println "Usage: java examples.Grep regex [files ...]"
main (pat:xs) = do
rgx <- return (regforce pat)
case xs of
Expand All @@ -15,23 +14,23 @@ main (pat:xs) = do
`catch` badpat where
badpat :: PatternSyntax -> IO ()
badpat pse = do
stderr.println "The given pattern is not valid."
stderr.println "The regex is not valid."
stderr.println pse.getMessage

run regex file = do
rdr <- utf8Reader file
grepit regex rdr
`catch` fnf where
fnf :: IO.FileNotFoundException -> IO ()
fnf :: FileNotFoundException -> IO ()
fnf _ = stderr.println ("Could not read " ++ file)


grepit :: Regex -> MutIO BufferedReader -> IO ()
grepit :: Regex -> BufferedReader -> IO ()
grepit pat rdr = loop `catch` eof `finally` rdr.close
where
eof ::IO.EOFException -> IO ()
eof :: EOFException -> IO ()
eof _ = return ()
loop = do
line <- rdr.getLine
when (line ~ pat) (stdout.println line)
when (line ~ pat) (println line)
loop
19 changes: 16 additions & 3 deletions frege/Prelude.fr
Expand Up @@ -22,7 +22,7 @@ import frege.prelude.PreludeIO public
import frege.prelude.Arrays public
import frege.prelude.Maybe public
import frege.java.Lang public
import frege.java.IO()
import frege.java.IO
-- derived instances for named types
derive Eq Ordering
derive Ord Ordering
Expand Down Expand Up @@ -56,6 +56,19 @@ print !d = IO.stdout.print (display d)
--- This will come out UTF8 encoded.
println !d = IO.stdout.println (display d)

--- write a character to 'stdout'
putChar :: Char -> IO ()
putChar = stdout.putChar

--- write a 'String' to standard output (Haskell compatibility)
putStr :: String -> IO()
putStr = stdout.print

--- write a 'String' and a new line to standard output (Haskell compatibility)
putStrLn :: String -> IO()
putStrLn = stdout.println


--- read a character from the standard input reader
getChar = IO.stdin.getChar

Expand All @@ -72,8 +85,8 @@ getLine = IO.stdin.getLine
Note that this imposes strictness on the traced data.
-}
trace str = IO.performUnsafe (traceStr str >> IO.return false)
trace str = IO.performUnsafe (stderr.print str >> IO.return false)
--- same as 'trace' but appends a line break
traceLn str = IO.performUnsafe (traceStrLn str >> IO.return false)
traceLn str = IO.performUnsafe (stderr.println str >> IO.return false)


5 changes: 2 additions & 3 deletions frege/compiler/Scanner.fr
Expand Up @@ -448,12 +448,11 @@ findInfixImports ts = loop start ts where
| t1.vor t2 = t1:consecutive ts
| otherwise = [t1]
consecutive rest = rest
separator t = t `is` '}' || t `is` ';' || t `is` '=' || t `is` '('
separator t = t `is` '}' || t `is` ';'
noComment t = Token.tokid t != COMMENT
infixtoken t = not (separator t) && t.tokid `elem` [SOMEOP, VARID, CONID, CHAR, INTCONST]

this ts = if isImport then consecutive (takeUntil separator tss)
else takeWhile infixtoken tss
else takeUntil separator tss
where tss = filter noComment ts

--- special symbols in tree
Expand Down
8 changes: 5 additions & 3 deletions frege/java/IO.fr
Expand Up @@ -69,6 +69,8 @@ data Writer = native java.io.Writer where
native write :: MutIO Writer -> Int -> IO () throws IOException
| MutIO Writer -> String -> IO () throws IOException
| MutIO Writer -> String -> Int -> Int -> IO () throws IOException
putChar :: MutIO Writer -> Char -> IO ()
putChar w c = write w (ord c)

data OutputStreamWriter = native java.io.OutputStreamWriter where
native new :: MutIO OutputStream -> String -> IOMut OutputStreamWriter
Expand Down Expand Up @@ -171,9 +173,9 @@ data BufferedReader = native java.io.BufferedReader where
-}
native readLine :: MutIO BufferedReader -> IO (Maybe String)
throws IOException
--- read all lines and return it as list, close reader afterwards
getlines :: MutIO BufferedReader -> IO [String]
getlines br = loop [] (repeat br.readLine) where
--- read all lines and return them as list, close reader afterwards
getLines :: MutIO BufferedReader -> IO [String]
getLines br = loop [] (repeat br.readLine) where
loop acc (a:as) = do
xms <- a
case xms of
Expand Down
9 changes: 8 additions & 1 deletion frege/prelude/PreludeBase.fr
Expand Up @@ -1838,13 +1838,20 @@ abstract data State s a = State (s -> (a, s)) where
State.State b -> b s'
)
public a >> b = a State.>>= (const b)


--- warning: use @stderr.print@ instead
--- print a 'string' to the standard error stream
native traceStr java.lang.System.err.print :: String -> IO ()

--- warning: use @stderr.println@ instead
--- print a 'string' to the standard error stream and append a new line.
native traceStrLn java.lang.System.err.println :: String -> IO ()

--- warning: use @stdout.print@ instead
--- print a 'string' to the standard output stream
native printStr java.lang.System.out.print :: String -> IO ()

--- warning: use @stdout.println@ instead
--- print a 'string' to the standard output stream and append a new line.
native printStrLn java.lang.System.out.println :: String -> IO ()

4 changes: 2 additions & 2 deletions frege/tools/YYgen.fr
Expand Up @@ -234,7 +234,7 @@ loadUrl url = do
stream <- url.openStream
isr <- InputStreamReader.new stream "UTF-8"
ifile <- BufferedReader.new isr
lines <- ifile.getlines
lines <- ifile.getLines
return (map uncr lines)
`catch` noStream
where
Expand All @@ -252,7 +252,7 @@ uncr s = (#\r#.matcher s).replaceAll "";
fileContent :: String -> IO [String];
fileContent fn = do
file <- utf8Reader fn
lines <- file.getlines
lines <- file.getLines
return (map uncr lines)
`catch` failure
where
Expand Down
5 changes: 5 additions & 0 deletions shadow/frege/prelude/Floating.fr
Expand Up @@ -34,19 +34,24 @@ instance Floating Double where
-- the following 3 can't be inherited because Double.**, Double.tan and Double.tanh
-- already exist as native functions and would be inherited from there
x ** y = exp (log x * y)
--- nowarn: already defined in @instance@ 'PrimitiveFloating' 'Double'
tan x = sin x / cos x
--- nowarn: already defined in @instance@ 'PrimitiveFloating' 'Double'
tanh x = sinh x / cosh x

instance Floating Float where
pi = Math.pi.float
-- the following 3 can't be inherited because Float.**, Float.tan and Float.tanh
-- already exist as native functions and would be inherited from there
--- nowarn: already defined in @instance@ 'PrimitiveFloating' 'Float'
x ** y = exp (log x * y)
--- nowarn: already defined in @instance@ 'PrimitiveFloating' 'Float'
tan x = sin x / cos x
--- nowarn: already defined in @instance@ 'PrimitiveFloating' 'Float'
tanh x = sinh x / cosh x
--- nowarn: already defined in @instance@ 'PrimitiveFloating' 'Float'
acos f = (Float.acos f).float
--- nowarn: already defined in @instance@ 'PrimitiveFloating' 'Float'
asin f = (Float.asin f).float
--- nowarn: already defined in @instance@ 'PrimitiveFloating' 'Float'
atan f = (Float.atan f).float
Expand Down
11 changes: 9 additions & 2 deletions shadow/frege/prelude/PreludeBase.fr
Expand Up @@ -1837,14 +1837,21 @@ abstract data State s a = State (s -> (a, s)) where
(v, !s') -> case k v of
State.State b -> b s'
)
public a >> b = State.>>= a (const b)

public a >> b = a State.>>= (const b)

--- warning: use @stderr.print@ instead
--- print a 'string' to the standard error stream
native traceStr java.lang.System.err.print :: String -> IO ()

--- warning: use @stderr.println@ instead
--- print a 'string' to the standard error stream and append a new line.
native traceStrLn java.lang.System.err.println :: String -> IO ()

--- warning: use @stdout.print@ instead
--- print a 'string' to the standard output stream
native printStr java.lang.System.out.print :: String -> IO ()

--- warning: use @stdout.println@ instead
--- print a 'string' to the standard output stream and append a new line.
native printStrLn java.lang.System.out.println :: String -> IO ()

0 comments on commit 5bc9f29

Please sign in to comment.