Skip to content

Commit bde6939

Browse files
author
Matthew Mirman
committed
fixed what appears to be a bug in how unicode imports worked, and updated the bounds
1 parent 66f965e commit bde6939

File tree

6 files changed

+27
-15
lines changed

6 files changed

+27
-15
lines changed

Diff for: caledon.cabal

+2-2
Original file line numberDiff line numberDiff line change
@@ -45,10 +45,10 @@ executable caledon
4545
containers >= 0.4 && < 1.0,
4646
transformers >= 0.3 && < 1.0,
4747
cpphs >= 1.0 && < 2.0,
48-
lens >= 3.0 && < 4.0,
48+
lens >= 3.0,
4949
deepseq >= 1 && < 2,
5050
spoon >= 0 && < 1,
51-
fgl >= 5.4 && < 5.5
51+
fgl >= 5.4
5252

5353
Extensions: FlexibleContexts,
5454
FlexibleInstances,

Diff for: sources/HOU.hs

+15-7
Original file line numberDiff line numberDiff line change
@@ -4,15 +4,18 @@
44
UnicodeSyntax,
55
BangPatterns,
66
TupleSections,
7-
ViewPatterns
7+
ViewPatterns,
8+
FlexibleContexts
89
#-}
910
module HOU where
1011

12+
1113
import Src.Tracing
1214
import Names
1315
import Choice
1416
import AST
1517
import Substitution
18+
1619
import Context
1720
import TopoSortAxioms
1821
import Control.Monad.State.Strict (StateT, forM_,runStateT, modify, get,put, State, runState)
@@ -34,6 +37,11 @@ import System.IO.Unsafe
3437

3538
import Control.Lens hiding (Choice(..))
3639

40+
-- No idea why I would need to redefine these here
41+
(.∀) :: Name -> Type -> Constraint -> Constraint
42+
(.∀) = Bind Forall
43+
44+
3745
throwTrace !i s = vtrace i s $ throwError s
3846

3947
-----------------------------------------------
@@ -689,7 +697,7 @@ checkType b sp ty = case sp of
689697
t'' <- regenAbsVars t
690698
v' <- checkType b v'' t
691699
r <- getNewWith "@r"
692-
Spine _ l' <- addToEnv (∀) r t'' $ checkType b (Spine r l) ty
700+
Spine _ l' <- addToEnv (.∀) r t'' $ checkType b (Spine r l) ty
693701
if b
694702
then return $ rebuildSpine (rebuildFromMem mem v') l'
695703
else return $ rebuildSpine (ascribe (rebuildFromMem mem v') t) l'
@@ -706,20 +714,20 @@ checkType b sp ty = case sp of
706714

707715
Spine "#imp_forall#" [_, Abs x tyA tyB] -> do
708716
tyA <- checkType b tyA tipe
709-
tyB <- addToEnv (∀) x tyA $ checkType b tyB ty
717+
tyB <- addToEnv (.∀) x tyA $ checkType b tyB ty
710718
return $ imp_forall x tyA tyB
711719

712720
Spine "#forall#" [_, Abs x tyA tyB] -> do
713721
tyA <- checkType b tyA tipe
714-
forall x tyA <$> (addToEnv (∀) x tyA $
722+
forall x tyA <$> (addToEnv (.∀) x tyA $
715723
checkType b tyB ty )
716724

717725
-- below are the only cases where bidirectional type checking is useful
718726
Spine "#imp_abs#" [_, Abs x tyA sp] -> case ty of
719727
Spine "#imp_forall#" [_, Abs x' tyA' tyF'] | x == x' || "" == x' -> do
720728
tyA <- checkType b tyA tipe
721729
tyA tyA'
722-
addToEnv (∀) x tyA $ do
730+
addToEnv (.∀) x tyA $ do
723731
imp_abs x tyA <$> checkType b sp tyF'
724732
_ -> do
725733
-- here this acts like "infers" since we can always initialize a ?\ like an infers!
@@ -733,14 +741,14 @@ checkType b sp ty = case sp of
733741
Spine "#forall#" [_, Abs x' tyA' tyF'] -> do
734742
tyA <- checkType b tyA tipe
735743
tyA tyA'
736-
addToEnv (∀) x tyA $ do
744+
addToEnv (.∀) x tyA $ do
737745
Abs x tyA <$> checkType b sp (subst (x' |-> var x) tyF')
738746
_ -> do
739747
e <- getNewWith "@e"
740748
tyA <- checkType b tyA tipe
741749
addToEnv (∃) e (forall "" tyA tipe) $ do
742750
forall x tyA (Spine e [var x]) ty
743-
Abs x tyA <$> addToEnv (∀) x tyA (checkType b sp $ Spine e [var x])
751+
Abs x tyA <$> addToEnv (.∀) x tyA (checkType b sp $ Spine e [var x])
744752
Spine nm [] | isChar nm -> do
745753
ty Spine "char" []
746754
return sp

Diff for: sources/Main.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -3,10 +3,10 @@ module Main where
33

44
import Options
55
import AST
6+
import HOU
67
import Substitution
78
import Src.Tracing
89
import Choice
9-
import HOU
1010
import qualified Src.Pipeline as Src
1111
import Parser
1212
import System.Environment
@@ -101,4 +101,4 @@ main = do
101101
processFile $ options & case files of
102102
[] -> id
103103
[fname] -> optFile .~ fname
104-
_ -> error $ "Too many file arguments."++header
104+
_ -> error $ "Too many file arguments."++header

Diff for: sources/Parser.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ import qualified Data.Set as S
2929
import Debug.Trace
3030
import qualified Data.Foldable as F
3131

32-
import Control.Lens
32+
import Control.Lens hiding (noneOf)
3333

3434
-----------------------------------------------------------------------
3535
-------------------------- PARSER -------------------------------------

Diff for: sources/Src/Elaborate.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE
2-
ViewPatterns
2+
ViewPatterns,
3+
FlexibleContexts
34
#-}
45
module Src.Elaborate (typeConstraints) where
56

@@ -155,4 +156,4 @@ getType (a :+: v) = do
155156
Just ~(ty,t') -> do
156157
return $ fromType $ appN' (Abs ty $ Pat t') v
157158

158-
159+

Diff for: sources/Substitution.hs

+4-1
Original file line numberDiff line numberDiff line change
@@ -233,7 +233,10 @@ instance Subst Constraint where
233233

234234
subq s f e c1 c2 = e (substFree s f c1) (substFree s f c2)
235235

236+
(∃) :: Name -> Type -> Constraint -> Constraint
236237
(∃) = Bind Exists
238+
239+
(∀) :: Name -> Type -> Constraint -> Constraint
237240
(∀) = Bind Forall
238241

239242
infixr 0 <<$>
@@ -346,4 +349,4 @@ eta_expandAll mp (Spine s l) = case mp ! s of
346349
Nothing -> Spine s (eta_expandAll mp <$> l)
347350
Just t -> rebuildSpine (eta_expand t s) (eta_expandAll mp <$> l)
348351

349-
352+

0 commit comments

Comments
 (0)