Skip to content

Commit

Permalink
Merge branch 'literals'
Browse files Browse the repository at this point in the history
  • Loading branch information
Ingo60 committed Jul 14, 2013
2 parents 272b66c + 44ec76a commit 1ca96dc
Show file tree
Hide file tree
Showing 28 changed files with 374 additions and 84 deletions.
6 changes: 4 additions & 2 deletions Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -209,7 +209,7 @@ SOURCES = $(COMPS)/Scanner.fr $(COMPS)/Classtools.fr \
$(COMPS)/Javatypes.fr $(COMPS)/Kinds.fr \
$(COMPS)/Transdef.fr $(COMPS)/Classes.fr \
$(COMPS)/Transform.fr \
$(COMPS)/tc/Methods.fr \
$(COMPS)/tc/Methods.fr $(COMPS)/tc/Patterns.fr \
$(COMPS)/Typecheck.fr \
$(COMPS)/tc/Util.fr \
$(COMPS)/gen/Util.fr $(COMPS)/gen/Const.fr \
Expand All @@ -226,7 +226,7 @@ CLASSES = $(COMPF1)/Scanner.class $(COMPF1)/Classtools.class \
$(COMPF1)/Javatypes.class $(COMPF1)/Kinds.class $(COMPF1)/Transdef.class \
$(COMPF1)/tc/Util.class \
$(COMPF1)/TAlias.class $(COMPF1)/Classes.class \
$(COMPF1)/tc/Methods.class \
$(COMPF1)/tc/Methods.class $(COMPF1)/tc/Patterns.class \
$(COMPF1)/Typecheck.class $(COMPF1)/Transform.class \
$(COMPF1)/gen/Util.class $(COMPF1)/gen/Const.class \
$(COMPF1)/gen/Bindings.class $(COMPF1)/gen/Match.class \
Expand All @@ -248,6 +248,8 @@ $(DIR1)/List.class: frege/List.fr
$(FREGEC0) $?
$(CONTROL1)/Monoid.class: frege/control/Monoid.fr
$(FREGEC0) $?
$(COMPF1)/tc/Patterns.class: frege/compiler/tc/Patterns.fr
$(FREGEC0) -make $?
$(COMPF1)/tc/Methods.class: frege/compiler/tc/Methods.fr
$(FREGEC0) -make $?
$(COMPF1)/Classtools.class: frege/compiler/Classtools.fr
Expand Down
5 changes: 3 additions & 2 deletions examples/CommandLineClock.fr
Original file line number Diff line number Diff line change
Expand Up @@ -31,13 +31,14 @@ current = do
- throws ... throws ....
-}
native sleep java.lang.Thread.sleep :: Long -> IO () throws InterruptedException
-- .... defined in frege.java.Lang
-- native sleep java.lang.Thread.sleep :: Long -> IO () throws InterruptedException


main args =
forever do
current >>= print
print "\r"
stdout.flush
sleep 999L
Thread.sleep 999L

100 changes: 100 additions & 0 deletions examples/NumericLiterals.fr
Original file line number Diff line number Diff line change
@@ -0,0 +1,100 @@
{--
The following module exemplifies the _flexibly typed numeric literal_ (FTNL) typing rules.
A numeric literal with a suffix (one of 'l', 'n', 'f', 'd', 'L', 'N', 'F', 'D' ) is
never a FTNL. The type is fixed to 'Long', 'Integer', 'Double' or 'Float'.
An integer FTNL is either @0@ or a non-null digit followed by arbitrary many digits,
without suffix letter. Octal literals (which are starting with @0@ and have at least one
further digit) and hexadecimal literals (starting with @0x@) are not FTNLs, rather,
their type is invariably 'Int'.
A floating point FTNL is a number in decimal or scientific notation, without suffix letter.
-}

module examples.NumericLiterals where

import Prelude.Floating

{--
1. If there is one and only one numeric type (that is, instance of type class 'Num')
that is valid for the integer FTNL,
then the literal denotes a value of that type.
Since @n@ is 'Integer', both literals must be 'Integer'
-}
rule1 :: Integer -> Bool
{-- Alternativly, the following types would be possible:
> rule1 :: Int -> Bool
> rule1 :: Long -> Bool
> rule1 :: Integral i => i -> Bool
-}
rule1 n = n `rem` 2 != 0

--- Since @x@ is 'Float', both literals must be 'Float' literals.
--- Alternativly, the following types would be possible:
--- > rule1d :: Double -> Double
--- > rule1d :: Real r => r -> r
rule1d :: Float -> Float
rule1d x = 0.5 * x + 1



{--
2. If only a type that is an instance of 'Real', 'PrimitiveFloating'
or some class that has 'Real' as superclass would be valid,
it denotes a value of type 'Double'.
Since
> sqrt :: Floating α => α -> α
> (**) :: Floating α => α -> α -> α
and 'Floating' is a subclass of 'Real', both literals will be 'Double'.
-}
-- rule2 :: Float -- also possible
-- rule2 :: Floating r => r -- also possible (see below)
-- rule2 :: Double -- default
rule2 = sqrt 2 ** 7

{--
3. If a type signature is present which forces the type to be polymorphic,
the literal will be replaced by an application of 'fromInt' or 'fromDouble'
to the same literal
(which then itself will get typed as 'Int' or 'Double' by the previous rules).
Because of the type signature, the literals must be polymorphic, which is achieved
through implicit application of 'fromInt' to @7@ and 'fromDouble' to @2.0@.
However, this requires that type variables
that stand for the type of the literal must have a constraint that
ensures they are numbers, i.e. instances of (a subclass of) 'Num'.
-}
rule3a :: Floating r => r
rule3a = sqrt 2.0 ** 7

rule3b :: Integral n => n -> Bool
rule3b n = n `rem` 2 != 0

-- inferred type is more constrained than expected type
-- inferred: Num a => a -> a
-- expected: a -> a
-- rule3c :: a -> a
-- rule3c n = n + 2

{--
4. If the type of an integer literal cannot be determined by the rules above,
it defaults to 'Int'.
The functions 'rem' and '!=' are polymorphic over 'Integral'/'Eq' types,
so no concrete type is enforced by the code, and rules 2 and 3 above
are not applicable. Therefore, it defaults to 'Int'.
-}
rule4 n = n `rem` 2 != 0

--- @2.0@ gets type 'Double' since the type ox @x@ is unknown.
rule4d x = x / 2.0



3 changes: 2 additions & 1 deletion frege/Prelude.fr
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,8 @@
package frege.Prelude where

import frege.prelude.PreludeBase public hiding(Ordering)
import frege.prelude.PreludeBase public (Ordering(Eq EQ, Lt LT, Gt GT))
-- provide some names Haskellers are used to
import frege.prelude.PreludeBase public (Ordering(Eq EQ, Lt LT, Gt GT), != /=)
import frege.prelude.PreludeBase public (from toEnum, ord fromEnum)
import frege.prelude.PreludeNative public
import frege.prelude.PreludeList public
Expand Down
1 change: 1 addition & 0 deletions frege/compiler/Data.fr
Original file line number Diff line number Diff line change
Expand Up @@ -245,6 +245,7 @@ pPreludeText = Pack.new "frege.prelude.PreludeText"
pPreludeList = Pack.new "frege.prelude.PreludeList"
pPreludeMonad = Pack.new "frege.prelude.PreludeMonad"
pPreludeIO = Pack.new "frege.prelude.PreludeIO"
pPreludeMath = Pack.new "frege.prelude.Math"

{-- List of Prelude packages and the namespace that needs to be assigned on import time
Expand Down
2 changes: 1 addition & 1 deletion frege/compiler/Fixdefs.fr
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@

package frege.compiler.Fixdefs where


import frege.Prelude hiding(<+>)

import frege.List(Tree)
-- import all from data
Expand Down
1 change: 1 addition & 0 deletions frege/compiler/GUtil.fr
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,7 @@

package frege.compiler.GUtil where

import frege.Prelude hiding(<+>)

import frege.List(Tree, keyvalues, keys, insertkv)
import Data.List as DL(elemBy)
Expand Down
12 changes: 6 additions & 6 deletions frege/compiler/GenJava7.fr
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,7 @@
package frege.compiler.GenJava7 where


import frege.Prelude hiding(apply)
import frege.Prelude hiding(apply, <+>)
import frege.List (Tree, values, keys, each, insert, lookup, insertkv, updatekv)
import Data.List as DL(sortBy, partitioned)

Expand Down Expand Up @@ -1231,10 +1231,10 @@ cafCode (sym@SymV {depth = 0, expr = Just x}) binds = do
code <- compiling sym (genStmts (autoboxed rtype) x binds)
case badguard of
Just (Left x) -> do
U.warn (getpos x) (msgdoc ("guard (" ++ nice x g ++ ") may evaluate to false."))
U.warn (getpos x) (msgdoc ("guard (" ++ nicer x g ++ ") may evaluate to false."))
stio (Right (code ++ jthrow))
Just (Right p) -> do
U.warn (getpos p) (msgdoc ("pattern guard (" ++ nice p g ++ ") may fail to match."))
U.warn (getpos p) (msgdoc ("pattern guard (" ++ nicer p g ++ ") may fail to match."))
stio (Right (code ++ jthrow))
Nothing -> stio (Right code)

Expand Down Expand Up @@ -1749,14 +1749,14 @@ genLambda rm (Lam {pat, ex}) ((arg@(_, _, _, s)) : args) binds = do
Just p -> do
U.warn (getpos pat) (msgdoc ("function pattern is refutable, "
++ "consider adding a case for "
++ nice p g))
++ nicer p g))
stio (code ++ jthrow)
_ -> case badguard of
Just (Left x) -> do
U.warn (getpos x) (msgdoc ("guard (" ++ nice x g ++ ") may evaluate to false."))
U.warn (getpos x) (msgdoc ("guard (" ++ nicer x g ++ ") may evaluate to false."))
stio (code ++ jthrow)
Just (Right p) -> do
U.warn (getpos p) (msgdoc ("pattern guard (" ++ nice p g ++ ") may fail to match."))
U.warn (getpos p) (msgdoc ("pattern guard (" ++ nicer p g ++ ") may fail to match."))
stio (code ++ jthrow)
Nothing -> stio code

Expand Down
5 changes: 3 additions & 2 deletions frege/compiler/GenMeta.fr
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,8 @@

package frege.compiler.GenMeta where

import frege.Prelude except(print,println,break)
import frege.Prelude except(print,println,break,<+>)

import frege.List (Tree, insertkv, keys, each, values)
import Data.List as DL(sortBy)

Expand Down Expand Up @@ -183,7 +184,7 @@ banner v = do
text "This code was generated with the frege compiler version",
text v,
text "from",
text g.options.source,
text ((´\\´.matcher g.options.source).replaceAll "/"),
text "Do not edit this file!",
text "Instead, edit the source file and recompile."]) "*/")
println ""
Expand Down
3 changes: 2 additions & 1 deletion frege/compiler/Grammar.y
Original file line number Diff line number Diff line change
Expand Up @@ -36,14 +36,15 @@
«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•»«•» */

/**
* This is the grammar for the Frege language ($Revision$).
* This is the grammar for the Frege language.
*/
package frege.compiler.Grammar where

/*
* !!! DO NOT CHANGE FILE Grammar.fr, IT HAS BEEN CREATED AUTOMATICALLY !!!
*/

import frege.Prelude hiding(<+>)

import frege.List(Tree, keyvalues, keys, insertkv)
import Data.List as DL(elemBy)
Expand Down
2 changes: 2 additions & 0 deletions frege/compiler/Kinds.fr
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,8 @@

module frege.compiler.Kinds where

import frege.Prelude hiding(<+>)

import frege.compiler.Data
import frege.compiler.Nice except (group, break)
import frege.compiler.Utilities as U()
Expand Down
2 changes: 1 addition & 1 deletion frege/compiler/Nice.fr
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@

package frege.compiler.Nice where

import frege.Prelude except(break)
import frege.Prelude except(break, <+>)
import Data.List(intersperse)
import frege.compiler.Data
import frege.lib.PP public except (line)
Expand Down
12 changes: 2 additions & 10 deletions frege/compiler/Scanner.fr
Original file line number Diff line number Diff line change
Expand Up @@ -64,18 +64,10 @@
-}


{-
* $Author$
* $Revision$
* $Date$
* $Id$
-}

package frege.compiler.Scanner where

--- This is $Revision$
public version = v "$Revision$" where
v (m ~ #(\d+)#) | Just g <- m.group 1 = g.atoi
v _ = 0
import frege.Prelude hiding(<+>)


-- import of library packages
Expand Down
1 change: 1 addition & 0 deletions frege/compiler/Transform.fr
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@

package frege.compiler.Transform where

import frege.Prelude hiding(<+>)

import frege.List (Tree, lookup, insert, insertkv, update, keys, values, each,
fromKeys, including, contains, union, isEmpty)
Expand Down
Loading

0 comments on commit 1ca96dc

Please sign in to comment.