Skip to content
Snippets Groups Projects
Commit ce952691 authored by chevalier@alum.wellesley.edu's avatar chevalier@alum.wellesley.edu
Browse files

ext-core library: Fix performance bug

isUtupleTy was implemented inefficiently (and is called a lot by the typechecker). Replaced with uglier but faster code.
parent 809c7e56
No related merge requests found
......@@ -5,6 +5,7 @@ import Language.Core.Encoding
import Data.Generics
import Data.List (elemIndex)
import Data.Char
data Module
= Module AnMname [Tdef] [Vdefg]
......@@ -102,7 +103,7 @@ data CoercionKind =
-- either type constructors or coercion names onto either
-- kinds or coercion kinds.
data KindOrCoercion = Kind Kind | Coercion CoercionKind
data Lit = Literal CoreLit Ty
deriving (Data, Typeable, Eq)
......@@ -251,7 +252,15 @@ tUtuple ts = foldl Tapp (Tcon (tcUtuple (length ts))) ts
isUtupleTy :: Ty -> Bool
isUtupleTy (Tapp t _) = isUtupleTy t
isUtupleTy (Tcon tc) = tc `elem` [tcUtuple n | n <- [1..maxUtuple]]
isUtupleTy (Tcon tc) =
case tc of
(Just pm, 'Z':rest) | pm == primMname && last rest == 'H' ->
let mid = take ((length rest) - 1) rest in
all isDigit mid && (let num = read mid in
1 <= num && num <= maxUtuple)
_ -> False
-- The above is ugly, but less ugly than this:
--tc `elem` [tcUtuple n | n <- [1..maxUtuple]]
isUtupleTy _ = False
dcUtuple :: Int -> Qual Dcon
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment